X-Git-Url: https://git.gag.com/?a=blobdiff_plain;f=src%2FSDCCglue.c;h=1a4913767ad331b6a58c8b801cf55487f272b63d;hb=238e1b53dc1ac88bd559c93bd7f355d0887d39e1;hp=dcca79fe1c0886dc67acd611ca822e08488ded96;hpb=f80a8832b0d235e6c4e83a023d9d5a4085364f99;p=fw%2Fsdcc diff --git a/src/SDCCglue.c b/src/SDCCglue.c index dcca79fe..1a491376 100644 --- a/src/SDCCglue.c +++ b/src/SDCCglue.c @@ -35,7 +35,7 @@ #include #endif -symbol *interrupts[256]; +symbol *interrupts[INTNO_MAX+1]; void printIval (symbol *, sym_link *, initList *, FILE *); set *publics = NULL; /* public variables */ @@ -45,7 +45,6 @@ set *externs = NULL; /* Varibles that are declared as extern */ unsigned maxInterrupts = 6; int allocInfo = 1; symbol *mainf; -extern char *VersionString; set *pipeSet = NULL; /* set of pipes */ set *tmpfileSet = NULL; /* set of tmp file created by the compiler */ set *tmpfileNameSet = NULL; /* All are unlinked at close. */ @@ -259,35 +258,43 @@ emitRegularMap (memmap * map, bool addPublics, bool arFlag) /* if extern then do nothing or is a function then do nothing */ - if (IS_FUNC (sym->type)) + if (IS_FUNC (sym->type) && !(sym->isitmp)) continue; /* print extra debug info if required */ - if (options.debug) { - cdbSymbol (sym, cdbFile, FALSE, FALSE); - if (!sym->level) /* global */ - if (IS_STATIC (sym->etype)) - fprintf (map->oFile, "F%s$", moduleName); /* scope is file */ + if (options.debug) + { + if (!sym->level) /* global */ + { + if (IS_STATIC (sym->etype)) + fprintf (map->oFile, "F%s$", moduleName); /* scope is file */ + else + fprintf (map->oFile, "G$"); /* scope is global */ + } else - fprintf (map->oFile, "G$"); /* scope is global */ - else - /* symbol is local */ - fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-")); - fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block); - } + { + /* symbol is local */ + fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-")); + } + fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block); + } /* if it has an initial value then do it only if it is a global variable */ if (sym->ival && sym->level == 0) { if (SPEC_OCLS(sym->etype)==xidata) { - // create a new "XINIT (CODE)" symbol, that will be emitted later + /* create a new "XINIT (CODE)" symbol, that will be emitted later + in the static seg */ newSym=copySymbol (sym); SPEC_OCLS(newSym->etype)=xinit; SNPRINTF (newSym->name, sizeof(newSym->name), "__xinit_%s", sym->name); SNPRINTF (newSym->rname, sizeof(newSym->rname), "__xinit_%s", sym->rname); - SPEC_CONST(newSym->etype)=1; + if (IS_SPEC (newSym->type)) + SPEC_CONST (newSym->type) = 1; + else + DCL_PTR_CONST (newSym->type) = 1; SPEC_STAT(newSym->etype)=1; - resolveIvalSym(newSym->ival); + resolveIvalSym(newSym->ival, newSym->type); // add it to the "XINIT (CODE)" segment addSet(&xinit->syms, newSym); @@ -297,11 +304,11 @@ emitRegularMap (memmap * map, bool addPublics, bool arFlag) ival = initAggregates (sym, sym->ival, NULL); } else { if (getNelements(sym->type, sym->ival)>1) { - werror (W_EXCESS_INITIALIZERS, "scalar", - sym->name, sym->lineDef); + werrorfl (filename, sym->lineDef, W_EXCESS_INITIALIZERS, "scalar", + sym->name); } ival = newNode ('=', newAst_VALUE (symbolVal (sym)), - decorateType (resolveSymbols (list2expr (sym->ival)))); + decorateType (resolveSymbols (list2expr (sym->ival)), RESULT_CHECK)); } codeOutFile = statsg->oFile; @@ -314,7 +321,8 @@ emitRegularMap (memmap * map, bool addPublics, bool arFlag) // but try to do it anyway } allocInfo = 0; - eBBlockFromiCode (iCodeFromAst (ival)); + if (!astErrors(ival)) + eBBlockFromiCode (iCodeFromAst (ival)); allocInfo = 1; } } @@ -343,7 +351,7 @@ emitRegularMap (memmap * map, bool addPublics, bool arFlag) else { int size = getSize (sym->type); if (size==0) { - werror(E_UNKNOWN_SIZE,sym->name); + werrorfl (filename, sym->lineDef, E_UNKNOWN_SIZE, sym->name); } /* allocate space */ if (options.debug) { @@ -405,7 +413,7 @@ initPointer (initList * ilist, sym_link *toType) /* address of symbol */ if (IS_AST_SYM_VALUE (expr->left)) { val = copyValue (AST_VALUE (expr->left)); - val->type = newLink (); + val->type = newLink (DECLARATOR); if (SPEC_SCLS (expr->left->etype) == S_CODE) { DCL_TYPE (val->type) = CPOINTER; DCL_PTR_CONST (val->type) = port->mem.code_ro; @@ -464,7 +472,7 @@ initPointer (initList * ilist, sym_link *toType) IS_ARRAY(expr->right->ftype)) { val = copyValue (AST_VALUE (expr->right)); - val->type = newLink (); + val->type = newLink (DECLARATOR); if (SPEC_SCLS (expr->right->etype) == S_CODE) { DCL_TYPE (val->type) = CPOINTER; DCL_PTR_CONST (val->type) = port->mem.code_ro; @@ -484,7 +492,10 @@ initPointer (initList * ilist, sym_link *toType) return val; } wrong: - werror (E_INCOMPAT_PTYPES); + if (expr) + werrorfl (expr->filename, expr->lineno, E_INCOMPAT_PTYPES); + else + werror (E_INCOMPAT_PTYPES); return NULL; } @@ -504,7 +515,7 @@ printChar (FILE * ofile, char *s, int plen) while (len && pplen < plen) { i = 60; - while (i && *s && pplen < plen) + while (i && pplen < plen) { if (*s < ' ' || *s == '\"' || *s=='\\') { @@ -535,7 +546,11 @@ printChar (FILE * ofile, char *s, int plen) else len = 0; } - tfprintf (ofile, "\t!db !constbyte\n", 0); + while (pplen < plen) + { + tfprintf (ofile, "\t!db !constbyte\n", 0); + pplen++; + } } /*-----------------------------------------------------------------*/ @@ -575,14 +590,19 @@ pointerTypeToGPByte (const int p_type, const char *iname, const char *oname) void _printPointerType (FILE * oFile, const char *name) { - /* if (TARGET_IS_DS390) */ if (options.model == MODEL_FLAT24) { - fprintf (oFile, "\t.byte %s,(%s >> 8),(%s >> 16)", name, name, name); + if (port->little_endian) + fprintf (oFile, "\t.byte %s,(%s >> 8),(%s >> 16)", name, name, name); + else + fprintf (oFile, "\t.byte (%s >> 16),(%s >> 8),%s", name, name, name); } else { - fprintf (oFile, "\t.byte %s,(%s >> 8)", name, name); + if (port->little_endian) + fprintf (oFile, "\t.byte %s,(%s >> 8)", name, name); + else + fprintf (oFile, "\t.byte (%s >> 8),%s", name, name); } } @@ -619,10 +639,6 @@ printIvalType (symbol *sym, sym_link * type, initList * ilist, FILE * oFile) if (ilist->type == INIT_DEEP) ilist = ilist->init.deep; - if (!IS_AGGREGATE(sym->type) && getNelements(type, ilist)>1) { - werror (W_EXCESS_INITIALIZERS, "scalar", sym->name, sym->lineDef); - } - if (!(val = list2val (ilist))) { // assuming a warning has been thrown val=constVal("0"); @@ -644,19 +660,26 @@ printIvalType (symbol *sym, sym_link * type, initList * ilist, FILE * oFile) case 2: if (port->use_dw_for_init) tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2)); - else + else if (port->little_endian) fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1)); + else + fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 1), aopLiteral (val, 0)); break; case 4: if (!val) { tfprintf (oFile, "\t!dw !constword\n", 0); tfprintf (oFile, "\t!dw !constword\n", 0); } - else { + else if (port->little_endian) { fprintf (oFile, "\t.byte %s,%s,%s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1), aopLiteral (val, 2), aopLiteral (val, 3)); } + else { + fprintf (oFile, "\t.byte %s,%s,%s,%s\n", + aopLiteral (val, 3), aopLiteral (val, 2), + aopLiteral (val, 1), aopLiteral (val, 0)); + } break; } } @@ -702,7 +725,7 @@ void printIvalBitFields(symbol **sym, initList **ilist, FILE * oFile) case 2: tfprintf (oFile, "\t!dw !constword\n",ival); break; - case 4: + case 4: /* EEP: why is this db and not dw? */ tfprintf (oFile, "\t!db !constword,!constword\n", (ival >> 8) & 0xffff, (ival & 0xffff)); break; @@ -723,7 +746,7 @@ printIvalStruct (symbol * sym, sym_link * type, sflds = SPEC_STRUCT (type)->fields; if (ilist->type != INIT_DEEP) { - werror (E_INIT_STRUCT, sym->name); + werrorfl (filename, sym->lineDef, E_INIT_STRUCT, sym->name); return; } @@ -737,7 +760,7 @@ printIvalStruct (symbol * sym, sym_link * type, } } if (iloop) { - werror (W_EXCESS_INITIALIZERS, "struct", sym->name, sym->lineDef); + werrorfl (filename, sym->lineDef, W_EXCESS_INITIALIZERS, "struct", sym->name); } return; } @@ -749,7 +772,6 @@ int printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s) { value *val; - int remain; if (!s) { @@ -763,10 +785,6 @@ printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s) printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type)); - if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) - 1)) > 0) - while (remain--) - tfprintf (oFile, "\t!db !constbyte\n", 0); - return 1; } else @@ -785,15 +803,14 @@ printIvalArray (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) { initList *iloop; - int lcnt = 0, size = 0; - sym_link *last_type; + int size = 0; /* take care of the special case */ /* array of characters can be init */ /* by a string */ if (IS_CHAR (type->next)) { if (!IS_LITERAL(list2val(ilist)->etype)) { - werror (E_CONST_EXPECTED); + werrorfl (filename, ilist->lineno, E_CONST_EXPECTED); return; } if (printIvalChar (type, @@ -804,41 +821,32 @@ printIvalArray (symbol * sym, sym_link * type, initList * ilist, /* not the special case */ if (ilist->type != INIT_DEEP) { - werror (E_INIT_STRUCT, sym->name); + werrorfl (filename, ilist->lineno, E_INIT_STRUCT, sym->name); return; } - iloop = ilist->init.deep; - lcnt = DCL_ELEM (type); - for (last_type = type->next; last_type && DCL_ELEM (last_type); last_type = last_type->next) - lcnt *= DCL_ELEM (last_type); - - for (;;) + for (iloop=ilist->init.deep; iloop; iloop=iloop->next) { - size++; printIval (sym, type->next, iloop, oFile); - iloop = (iloop ? iloop->next : NULL); - - - /* if not array limits given & we */ - /* are out of initialisers then */ - if (!DCL_ELEM (type) && !iloop) - break; - - /* no of elements given and we */ - /* have generated for all of them */ - if (!--lcnt) { - /* if initializers left */ - if (iloop) { - werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef); - } + + if (++size > DCL_ELEM(type)) { + werrorfl (filename, sym->lineDef, W_EXCESS_INITIALIZERS, "array", sym->name); break; } } - - /* if we have not been given a size */ - if (!DCL_ELEM (type)) + + if (DCL_ELEM(type)) { + // pad with zeros if needed + if (sizenext); + while (size--) { + tfprintf (oFile, "\t!db !constbyte\n", 0); + } + } + } else { + // we have not been given a size, but we now know it DCL_ELEM (type) = size; + } return; } @@ -861,7 +869,7 @@ printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile) if (IS_LITERAL(val->etype)) { if (compareType(type,val->etype)==0) { - werror (E_INCOMPAT_TYPES); + werrorfl (filename, ilist->lineno, E_INCOMPAT_TYPES); printFromToType (val->type, type); } printIvalCharPtr (NULL, type, val, oFile); @@ -962,30 +970,48 @@ printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile) case 2: if (port->use_dw_for_init) tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size)); - else + else if (port->little_endian) tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1)); + else + tfprintf (oFile, "\t.byte %s,%s\n", + aopLiteral (val, 1), aopLiteral (val, 0)); break; case 3: if (IS_GENPTR(type) && floatFromVal(val)!=0) { // non-zero mcs51 generic pointer - werror (E_LITERAL_GENERIC); + werrorfl (filename, sym->lineDef, E_LITERAL_GENERIC); + } + if (port->little_endian) { + fprintf (oFile, "\t.byte %s,%s,%s\n", + aopLiteral (val, 0), + aopLiteral (val, 1), + aopLiteral (val, 2)); + } else { + fprintf (oFile, "\t.byte %s,%s,%s\n", + aopLiteral (val, 2), + aopLiteral (val, 1), + aopLiteral (val, 0)); } - fprintf (oFile, "\t.byte %s,%s,%s\n", - aopLiteral (val, 0), - aopLiteral (val, 1), - aopLiteral (val, 2)); break; case 4: if (IS_GENPTR(type) && floatFromVal(val)!=0) { // non-zero ds390 generic pointer - werror (E_LITERAL_GENERIC); + werrorfl (filename, sym->lineDef, E_LITERAL_GENERIC); + } + if (port->little_endian) { + fprintf (oFile, "\t.byte %s,%s,%s,%s\n", + aopLiteral (val, 0), + aopLiteral (val, 1), + aopLiteral (val, 2), + aopLiteral (val, 3)); + } else { + fprintf (oFile, "\t.byte %s,%s,%s,%s\n", + aopLiteral (val, 3), + aopLiteral (val, 2), + aopLiteral (val, 1), + aopLiteral (val, 0)); } - fprintf (oFile, "\t.byte %s,%s,%s,%s\n", - aopLiteral (val, 0), - aopLiteral (val, 1), - aopLiteral (val, 2), - aopLiteral (val, 3)); break; default: assert (0); @@ -1029,7 +1055,7 @@ printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) /* check the type */ if (compareType (type, val->type) == 0) { - werror (W_INIT_WRONG); + werrorfl (filename, ilist->lineno, W_INIT_WRONG); printFromToType (val->type, type); } @@ -1044,12 +1070,22 @@ printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) case 2: if (port->use_dw_for_init) tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2)); - else + else if (port->little_endian) tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1)); + else + tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 1), aopLiteral (val, 0)); break; case 3: // how about '390?? - fprintf (oFile, "\t.byte %s,%s,#0x%d\n", - aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE); + if (port->little_endian) + { + fprintf (oFile, "\t.byte %s,%s,#0x%d\n", + aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE); + } + else + { + fprintf (oFile, "\t.byte %s,%s,#0x%d\n", + aopLiteral (val, 1), aopLiteral (val, 0), GPTYPE_CODE); + } } return; } @@ -1084,12 +1120,11 @@ printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) void printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) { + sym_link *itype; + if (!ilist) return; - /* update line number for error msgs */ - lineno=sym->lineDef; - /* if structure then */ if (IS_STRUCT (type)) { @@ -1097,17 +1132,43 @@ printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) return; } - /* if this is a pointer */ - if (IS_PTR (type)) + /* if this is an array */ + if (IS_ARRAY (type)) { - printIvalPtr (sym, type, ilist, oFile); + printIvalArray (sym, type, ilist, oFile); return; } - /* if this is an array */ - if (IS_ARRAY (type)) + // not an aggregate, ilist must be a node + if (ilist->type!=INIT_NODE) { + // or a 1-element list + if (ilist->init.deep->next) { + werrorfl (filename, sym->lineDef, W_EXCESS_INITIALIZERS, "scalar", + sym->name); + } else { + ilist=ilist->init.deep; + } + } + + // and the type must match + itype=ilist->init.node->ftype; + + if (compareType(type, itype)==0) { + // special case for literal strings + if (IS_ARRAY (itype) && IS_CHAR (getSpec(itype)) && + // which are really code pointers + IS_PTR(type) && DCL_TYPE(type)==CPOINTER) { + // no sweat + } else { + werrorfl (filename, ilist->lineno, E_TYPE_MISMATCH, "assignment", " "); + printFromToType(itype, type); + } + } + + /* if this is a pointer */ + if (IS_PTR (type)) { - printIvalArray (sym, type, ilist, oFile); + printIvalPtr (sym, type, ilist, oFile); return; } @@ -1147,7 +1208,7 @@ emitStaticSeg (memmap * map, FILE * out) /* print extra debug info if required */ if (options.debug) { - cdbSymbol (sym, cdbFile, FALSE, FALSE); + if (!sym->level) { /* global */ if (IS_STATIC (sym->etype)) @@ -1182,11 +1243,13 @@ emitStaticSeg (memmap * map, FILE * out) { fprintf (out, "%s:\n", sym->rname); noAlloc++; - resolveIvalSym (sym->ival); + resolveIvalSym (sym->ival, sym->type); printIval (sym, sym->type, sym->ival, out); noAlloc--; - // if sym->ival is a string, WE don't need it anymore - if (IS_AST_SYM_VALUE(list2expr(sym->ival)) && + /* if sym is a simple string and sym->ival is a string, + WE don't need it anymore */ + if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) && + IS_AST_SYM_VALUE(list2expr(sym->ival)) && list2val(sym->ival)->sym->isstrlit) { freeStringSymbol(list2val(sym->ival)->sym); } @@ -1196,7 +1259,7 @@ emitStaticSeg (memmap * map, FILE * out) int size = getSize (sym->type); if (size==0) { - werror(E_UNKNOWN_SIZE,sym->name); + werrorfl (filename, sym->lineDef, E_UNKNOWN_SIZE,sym->name); } fprintf (out, "%s:\n", sym->rname); /* special case for character strings */ @@ -1204,7 +1267,7 @@ emitStaticSeg (memmap * map, FILE * out) SPEC_CVAL (sym->etype).v_char) printChar (out, SPEC_CVAL (sym->etype).v_char, - strlen (SPEC_CVAL (sym->etype).v_char) + 1); + size); else tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff); } @@ -1291,14 +1354,21 @@ createInterruptVect (FILE * vFile) fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n"); - /* now for the other interrupts */ for (; i < maxInterrupts; i++) { if (interrupts[i]) - fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname); + { + fprintf (vFile, "\tljmp\t%s\n", interrupts[i]->rname); + if ( i != maxInterrupts - 1 ) + fprintf (vFile, "\t.ds\t5\n"); + } else - fprintf (vFile, "\treti\n\t.ds\t7\n"); + { + fprintf (vFile, "\treti\n"); + if ( i != maxInterrupts - 1 ) + fprintf (vFile, "\t.ds\t7\n"); + } } } } @@ -1322,7 +1392,7 @@ initialComments (FILE * afile) time_t t; time (&t); fprintf (afile, "%s", iComments1); - fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t))); + fprintf (afile, "; Version " SDCC_VERSION_STR " %s\n", asctime (localtime (&t))); fprintf (afile, "%s", iComments2); } @@ -1415,8 +1485,6 @@ emitOverlay (FILE * afile) /* print extra debug info if required */ if (options.debug) { - cdbSymbol (sym, cdbFile, FALSE, FALSE); - if (!sym->level) { /* global */ if (IS_STATIC (sym->etype)) @@ -1447,7 +1515,7 @@ emitOverlay (FILE * afile) int size = getSize(sym->type); if (size==0) { - werror(E_UNKNOWN_SIZE,sym->name); + werrorfl (filename, sym->lineDef, E_UNKNOWN_SIZE); } if (options.debug) fprintf (afile, "==.\n"); @@ -1461,6 +1529,30 @@ emitOverlay (FILE * afile) } } + +/*-----------------------------------------------------------------*/ +/* spacesToUnderscores - replace spaces with underscores */ +/*-----------------------------------------------------------------*/ +static char * +spacesToUnderscores (char *dest, const char *src, size_t len) +{ + int i; + char *p; + + assert(dest != NULL); + assert(src != NULL); + assert(len > 0); + + --len; + for (p = dest, i = 0; *src != '\0' && i < len; ++src, ++i) { + *p++ = isspace(*src) ? '_' : *src; + } + *p = '\0'; + + return dest; +} + + /*-----------------------------------------------------------------*/ /* glue - the final glue that hold the whole thing together */ /*-----------------------------------------------------------------*/ @@ -1470,11 +1562,23 @@ glue (void) FILE *vFile; FILE *asmFile; FILE *ovrFile = tempfile (); + char moduleBuf[PATH_MAX]; + int mcs51_like; + + if(port->general.glue_up_main && + (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51 || TARGET_IS_DS400)) + { + mcs51_like=1; /*So it has bits, sfr, sbits, data, idata, etc...*/ + } + else + { + mcs51_like=0; + } addSetHead (&tmpfileSet, ovrFile); /* print the global struct definitions */ if (options.debug) - cdbStructBlock (0, cdbFile); + cdbStructBlock (0); vFile = tempfile (); /* PENDING: this isnt the best place but it will do */ @@ -1491,6 +1595,8 @@ glue (void) /* do the overlay segments */ emitOverlay (ovrFile); + outputDebugSymbols(); + /* now put it all together into the assembler file */ /* create the assembler file name */ @@ -1515,7 +1621,35 @@ glue (void) initialComments (asmFile); /* print module name */ - tfprintf (asmFile, "\t!module\n", moduleName); + tfprintf (asmFile, "\t!module\n", + spacesToUnderscores (moduleBuf, moduleName, sizeof moduleBuf)); + if(mcs51_like) + { + fprintf (asmFile, "\t.optsdcc -m%s", port->target); + + switch(options.model) + { + case MODEL_SMALL: fprintf (asmFile, " --model-small"); break; + case MODEL_COMPACT: fprintf (asmFile, " --model-compact"); break; + case MODEL_MEDIUM: fprintf (asmFile, " --model-medium"); break; + case MODEL_LARGE: fprintf (asmFile, " --model-large"); break; + case MODEL_FLAT24: fprintf (asmFile, " --model-flat24"); break; + case MODEL_PAGE0: fprintf (asmFile, " --model-page0"); break; + default: break; + } + /*if(options.stackAuto) fprintf (asmFile, " --stack-auto");*/ + if(options.useXstack) fprintf (asmFile, " --xstack"); + /*if(options.intlong_rent) fprintf (asmFile, " --int-long-rent");*/ + /*if(options.float_rent) fprintf (asmFile, " --float-rent");*/ + if(options.noRegParams) fprintf (asmFile, " --no-reg-params"); + if(options.parms_in_bank1) fprintf (asmFile, " --parms-in-bank1"); + fprintf (asmFile, "\n"); + } + else if(TARGET_IS_Z80 || TARGET_IS_GBZ80 ) + { + fprintf (asmFile, "\t.optsdcc -m%s\n", port->target); + } + tfprintf (asmFile, "\t!fileprelude\n"); /* Let the port generate any global directives, etc. */ @@ -1529,22 +1663,25 @@ glue (void) if (port->assembler.externGlobal) printExterns (asmFile); - /* copy the sfr segment */ - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; special function registers\n"); - fprintf (asmFile, "%s", iComments2); - copyFile (asmFile, sfr->oFile); - - /* copy the sbit segment */ - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; special function bits \n"); - fprintf (asmFile, "%s", iComments2); - copyFile (asmFile, sfrbit->oFile); + if(( mcs51_like ) + ||( TARGET_IS_Z80 )) /*.p.t.20030924 need to output SFR table for Z80 as well */ + { + /* copy the sfr segment */ + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; special function registers\n"); + fprintf (asmFile, "%s", iComments2); + copyFile (asmFile, sfr->oFile); + } - /*JCF: Create the areas for the register banks*/ - if(port->general.glue_up_main && - (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51)) + if(mcs51_like) { + /* copy the sbit segment */ + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; special function bits \n"); + fprintf (asmFile, "%s", iComments2); + copyFile (asmFile, sfrbit->oFile); + + /*JCF: Create the areas for the register banks*/ if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3]) { fprintf (asmFile, "%s", iComments2); @@ -1563,7 +1700,7 @@ glue (void) /* copy the data segment */ fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; internal ram data\n"); + fprintf (asmFile, "; %s ram data\n", mcs51_like?"internal":""); fprintf (asmFile, "%s", iComments2); copyFile (asmFile, data->oFile); @@ -1571,7 +1708,7 @@ glue (void) /* create the overlay segments */ if (overlay) { fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; overlayable items in internal ram \n"); + fprintf (asmFile, "; overlayable items in %s ram \n", mcs51_like?"internal":""); fprintf (asmFile, "%s", iComments2); copyFile (asmFile, ovrFile); } @@ -1587,7 +1724,7 @@ glue (void) } /* create the idata segment */ - if (idata) { + if ( (idata) && (mcs51_like) ) { fprintf (asmFile, "%s", iComments2); fprintf (asmFile, "; indirectly addressable internal ram data\n"); fprintf (asmFile, "%s", iComments2); @@ -1595,10 +1732,12 @@ glue (void) } /* copy the bit segment */ - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; bit data\n"); - fprintf (asmFile, "%s", iComments2); - copyFile (asmFile, bit->oFile); + if (mcs51_like) { + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; bit data\n"); + fprintf (asmFile, "%s", iComments2); + copyFile (asmFile, bit->oFile); + } /* if external stack then reserve space of it */ if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack) @@ -1612,10 +1751,12 @@ glue (void) /* copy xtern ram data */ - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; external ram data\n"); - fprintf (asmFile, "%s", iComments2); - copyFile (asmFile, xdata->oFile); + if (mcs51_like) { + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; external ram data\n"); + fprintf (asmFile, "%s", iComments2); + copyFile (asmFile, xdata->oFile); + } /* copy xternal initialized ram data */ fprintf (asmFile, "%s", iComments2); @@ -1623,6 +1764,13 @@ glue (void) fprintf (asmFile, "%s", iComments2); copyFile (asmFile, xidata->oFile); + /* If the port wants to generate any extra areas, let it do so. */ + if (port->extraAreas.genExtraAreaDeclaration) + { + port->extraAreas.genExtraAreaDeclaration(asmFile, + mainf && IFFUNC_HASBODY(mainf->type)); + } + /* copy the interrupt vector table */ if (mainf && IFFUNC_HASBODY(mainf->type)) { @@ -1662,8 +1810,14 @@ glue (void) (unsigned int) options.xdata_loc & 0xff); } - /* initialise the stack pointer. JCF: aslink takes care of the location */ - fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n"); /* MOF */ + // This should probably be a port option, but I'm being lazy. + // on the 400, the firmware boot loader gives us a valid stack + // (see '400 data sheet pg. 85 (TINI400 ROM Initialization code) + if (!TARGET_IS_DS400) + { + /* initialise the stack pointer. JCF: aslink takes care of the location */ + fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n"); /* MOF */ + } fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n"); fprintf (asmFile, "\tmov\ta,dpl\n"); @@ -1754,7 +1908,21 @@ tempfileandname(char *fname, size_t len) if ((tmpdir = getenv ("TEMP")) == NULL) tmpdir = getenv ("TMPDIR"); -#ifndef _WIN32 +#if defined(_WIN32) + { + static int warning_emitted; + + if (tmpdir == NULL) + { + tmpdir = "c:\\"; + if (!warning_emitted) + { + fprintf (stderr, "TMP not defined in environment, using %s for temporary files\n.", tmpdir); + warning_emitted = 1; + } + } + } +#else { /* try with /usr/tmp and /tmp on Un*x systems */ struct stat statbuf;