X-Git-Url: https://git.gag.com/?a=blobdiff_plain;f=src%2FSDCCglue.c;h=99a4f959e75783ef63558396f92a3e873310b522;hb=78ee1c4db56a72002884411196225f4c2d48204e;hp=1d6e0ed17af9004d721e878950183cbe6545df6d;hpb=91b0931c40c5cad20cf18aa66303f9cb850f5dbc;p=fw%2Fsdcc diff --git a/src/SDCCglue.c b/src/SDCCglue.c index 1d6e0ed1..99a4f959 100644 --- a/src/SDCCglue.c +++ b/src/SDCCglue.c @@ -60,7 +60,7 @@ DEFSETFUNC (closeTmpFiles) } /*-----------------------------------------------------------------*/ -/* rmTmpFiles - closes all tmp files created by the compiler */ +/* rmTmpFiles - unlinks all tmp files created by the compiler */ /* because of BRAIN DEAD MS/DOS & CYGNUS Libraries */ /*-----------------------------------------------------------------*/ DEFSETFUNC (rmTmpFiles) @@ -75,6 +75,21 @@ DEFSETFUNC (rmTmpFiles) return 0; } +/*-----------------------------------------------------------------*/ +/* rm_tmpfiles - close and remove temporary files and delete sets */ +/*-----------------------------------------------------------------*/ +void +rm_tmpfiles (void) +{ + /* close temporary files */ + applyToSet (tmpfileSet, closeTmpFiles); + /* remove temporary files */ + applyToSet (tmpfileNameSet, rmTmpFiles); + /* delete temorary file sets */ + deleteSet (&tmpfileSet); + deleteSet (&tmpfileNameSet); +} + /*-----------------------------------------------------------------*/ /* copyFile - copies source file to destination file */ /*-----------------------------------------------------------------*/ @@ -154,9 +169,11 @@ aopLiteral (value * val, int offset) static void emitRegularMap (memmap * map, bool addPublics, bool arFlag) { - symbol *sym, *symIval; + symbol *sym; ast *ival = NULL; - memmap *segment; + + if (!map) + return; if (addPublics) { @@ -170,16 +187,16 @@ emitRegularMap (memmap * map, bool addPublics, bool arFlag) else tfprintf (map->oFile, "\t!area\n", map->sname); } - - /* print the area name */ + for (sym = setFirstItem (map->syms); sym; sym = setNextItem (map->syms)) { + symbol *newSym=NULL; /* if extern then add it into the extern list */ if (IS_EXTERN (sym->etype)) { - addSetHead (&externs, sym); + addSetHead (&externs, sym); continue; } @@ -228,61 +245,86 @@ emitRegularMap (memmap * map, bool addPublics, bool arFlag) fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block); } - /* if is has an absolute address then generate - an equate for this no need to allocate space */ - if (SPEC_ABSA (sym->etype)) - { - if (options.debug) { - fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype)); - } - fprintf (map->oFile, "%s\t=\t0x%04x\n", - sym->rname, - SPEC_ADDR (sym->etype)); - } - else - { - /* allocate space */ - if (options.debug) { - fprintf (map->oFile, "==.\n"); - } - if (IS_STATIC (sym->etype)) - tfprintf (map->oFile, "!slabeldef\n", sym->rname); - else - tfprintf (map->oFile, "!labeldef\n", sym->rname); - tfprintf (map->oFile, "\t!ds\n", - (unsigned int) getSize (sym->type) & 0xffff); - } - /* if it has an initial value then do it only if it is a global variable */ - if (sym->ival && sym->level == 0) - { + if (sym->ival && sym->level == 0) { + if (SPEC_OCLS(sym->etype)==xidata) { + // create a new "XINIT (CODE)" symbol, that will be emitted later + newSym=copySymbol (sym); + SPEC_OCLS(newSym->etype)=xinit; + sprintf (newSym->name, "__xinit_%s", sym->name); + sprintf (newSym->rname,"__xinit_%s", sym->rname); + SPEC_CONST(newSym->etype)=1; + SPEC_STAT(newSym->etype)=1; + resolveIvalSym(newSym->ival); + + // add it to the "XINIT (CODE)" segment + addSet(&xinit->syms, newSym); + sym->ival=NULL; + } else { if (IS_AGGREGATE (sym->type)) { ival = initAggregates (sym, sym->ival, NULL); } else { + if (getNelements(sym->type, sym->ival)>1) { + werror (W_EXCESS_INITIALIZERS, "scalar", + sym->name, sym->lineDef); + } ival = newNode ('=', newAst_VALUE (symbolVal (sym)), - decorateType (resolveSymbols (list2expr (sym->ival)))); + decorateType (resolveSymbols (list2expr (sym->ival)))); } codeOutFile = statsg->oFile; - allocInfo = 0; - - // set ival's lineno to where the symbol was defined - if (ival) ival->lineno=sym->lineDef; - eBBlockFromiCode (iCodeFromAst (ival)); - allocInfo = 1; - - /* if the ival is a symbol assigned to an aggregate, - (bug #458099 -> #462479) - we don't need it anymore, so delete it from its segment */ - if (IS_AST_SYM_VALUE(sym->ival->init.node) && - IS_AGGREGATE (sym->type) ) { - symIval=AST_SYMBOL(sym->ival->init.node); - segment = SPEC_OCLS (symIval->etype); - deleteSetItem (&segment->syms, symIval); + + if (ival) { + // set ival's lineno to where the symbol was defined + setAstLineno (ival, lineno=sym->lineDef); + // check if this is not a constant expression + if (!constExprTree(ival)) { + werror (E_CONST_EXPECTED, "found expression"); + // but try to do it anyway + } + allocInfo = 0; + eBBlockFromiCode (iCodeFromAst (ival)); + allocInfo = 1; } + } + sym->ival = NULL; + } - sym->ival = NULL; + /* if is has an absolute address then generate + an equate for this no need to allocate space */ + if (SPEC_ABSA (sym->etype)) + { + char *equ="="; + if (options.debug) { + fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype)); + } + if (TARGET_IS_XA51) { + if (map==sfr) { + equ="sfr"; + } else if (map==bit || map==sfrbit) { + equ="bit"; + } + } + fprintf (map->oFile, "%s\t%s\t0x%04x\n", + sym->rname, equ, + SPEC_ADDR (sym->etype)); + } + else { + int size = getSize (sym->type); + if (size==0) { + werror(E_UNKNOWN_SIZE,sym->name); } + /* allocate space */ + if (options.debug) { + fprintf (map->oFile, "==.\n"); + } + if (IS_STATIC (sym->etype)) + tfprintf (map->oFile, "!slabeldef\n", sym->rname); + else + tfprintf (map->oFile, "!labeldef\n", sym->rname); + tfprintf (map->oFile, "\t!ds\n", + (unsigned int) size & 0xffff); + } } } @@ -290,7 +332,7 @@ emitRegularMap (memmap * map, bool addPublics, bool arFlag) /* initPointer - pointer initialization code massaging */ /*-----------------------------------------------------------------*/ value * -initPointer (initList * ilist) +initPointer (initList * ilist, sym_link *toType) { value *val; ast *expr = list2expr (ilist); @@ -302,6 +344,29 @@ initPointer (initList * ilist) if ((val = constExprValue (expr, FALSE))) return val; + /* ( ptr + constant ) */ + if (IS_AST_OP (expr) && + (expr->opval.op == '+' || expr->opval.op == '-') && + IS_AST_SYM_VALUE (expr->left) && + (IS_ARRAY(expr->left->ftype) || IS_PTR(expr->left->ftype)) && + compareType(toType, expr->left->ftype) && + IS_AST_LIT_VALUE (expr->right)) { + return valForCastAggr (expr->left, expr->left->ftype, + expr->right, + expr->opval.op); + } + + /* (char *)&a */ + if (IS_AST_OP(expr) && expr->opval.op==CAST && + IS_AST_OP(expr->right) && expr->right->opval.op=='&') { + if (compareType(toType, expr->left->ftype)!=1) { + werror (W_INIT_WRONG); + printFromToType(expr->left->ftype, toType); + } + // skip the cast ??? + expr=expr->right; + } + /* no then we have to do these cludgy checks */ /* pointers can be initialized with address of a variable or address of an array element */ @@ -345,10 +410,10 @@ initPointer (initList * ilist) (&some_struct)->element */ if (IS_AST_OP (expr->left) && expr->left->opval.op == PTR_OP && - IS_ADDRESS_OF_OP (expr->left->left)) - return valForStructElem (expr->left->left->left, - expr->left->right); - + IS_ADDRESS_OF_OP (expr->left->left)) { + return valForStructElem (expr->left->left->left, + expr->left->right); + } } /* case 3. (((char *) &a) +/- constant) */ if (IS_AST_OP (expr) && @@ -363,7 +428,6 @@ initPointer (initList * ilist) expr->right, expr->opval.op); } - /* case 4. (char *)(array type) */ if (IS_CAST_OP(expr) && IS_AST_SYM_VALUE (expr->right) && IS_ARRAY(expr->right->ftype)) { @@ -389,7 +453,7 @@ initPointer (initList * ilist) return val; } wrong: - werror (W_INIT_WRONG); + werror (E_INCOMPAT_PTYPES); return NULL; } @@ -453,20 +517,18 @@ pointerTypeToGPByte (const int p_type, const char *iname, const char *oname) { case IPOINTER: case POINTER: - return 0; + return GPTYPE_NEAR; case GPOINTER: - /* hack - if we get a generic pointer, we just assume - * it's an FPOINTER (i.e. in XDATA space). - */ - werror (E_CANNOT_USE_GENERIC_POINTER, iname, oname); + werror (E_CANNOT_USE_GENERIC_POINTER, + iname ? iname : "", + oname ? oname : ""); exit (1); - // fall through case FPOINTER: - return 1; + return GPTYPE_FAR; case CPOINTER: - return 2; + return GPTYPE_CODE; case PPOINTER: - return 3; + return GPTYPE_XSTACK; default: fprintf (stderr, "*** internal error: unknown pointer type %d in GPByte.\n", p_type); @@ -518,7 +580,7 @@ printGPointerType (FILE * oFile, const char *iname, const char *oname, /* printIvalType - generates ival for int/char */ /*-----------------------------------------------------------------*/ void -printIvalType (sym_link * type, initList * ilist, FILE * oFile) +printIvalType (symbol *sym, sym_link * type, initList * ilist, FILE * oFile) { value *val; @@ -526,7 +588,19 @@ printIvalType (sym_link * type, initList * ilist, FILE * oFile) if (ilist->type == INIT_DEEP) ilist = ilist->init.deep; - val = list2val (ilist); + 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"); + } + + if (val->type != type) { + val = valCastLiteral(type, floatFromVal(val)); + } + switch (getSize (type)) { case 1: if (!val) @@ -628,9 +702,12 @@ printIvalStruct (symbol * sym, sym_link * type, if (IS_BITFIELD(sflds->type)) { printIvalBitFields(&sflds,&iloop,oFile); } else { - printIval (sflds, sflds->type, iloop, oFile); + printIval (sym, sflds->type, iloop, oFile); } } + if (iloop) { + werror (W_EXCESS_INITIALIZERS, "struct", sym->name, sym->lineDef); + } return; } @@ -672,22 +749,27 @@ printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s) /*-----------------------------------------------------------------*/ /* printIvalArray - generates code for array initialization */ /*-----------------------------------------------------------------*/ -void +void printIvalArray (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) { initList *iloop; int lcnt = 0, size = 0; + sym_link *last_type; /* take care of the special case */ /* array of characters can be init */ /* by a string */ - if (IS_CHAR (type->next)) + if (IS_CHAR (type->next)) { + if (!IS_LITERAL(list2val(ilist)->etype)) { + werror (E_CONST_EXPECTED); + return; + } if (printIvalChar (type, (ilist->type == INIT_DEEP ? ilist->init.deep : ilist), oFile, SPEC_CVAL (sym->etype).v_char)) return; - + } /* not the special case */ if (ilist->type != INIT_DEEP) { @@ -697,6 +779,8 @@ printIvalArray (symbol * sym, sym_link * type, initList * ilist, 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 (;;) { @@ -715,7 +799,7 @@ printIvalArray (symbol * sym, sym_link * type, initList * ilist, if (!--lcnt) { /* if initializers left */ if (iloop) { - werror (W_EXESS_ARRAY_INITIALIZERS, sym->name, sym->lineDef); + werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef); } break; } @@ -738,6 +822,21 @@ printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile) int dLvl = 0; val = list2val (ilist); + + if (!val) { + // an error has been thrown allready + val=constVal("0"); + } + + if (IS_LITERAL(val->etype)) { + if (compareType(type,val->etype)==0) { + werror (E_INCOMPAT_TYPES); + printFromToType (val->type, type); + } + printIvalCharPtr (NULL, type, val, oFile); + return; + } + /* check the types */ if ((dLvl = compareType (val->type, type->next)) <= 0) { @@ -823,7 +922,7 @@ printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile) } else { - /* What is this case? Are these pointers? */ + // these are literals assigned to pointers switch (size) { case 1: @@ -837,9 +936,25 @@ printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile) aopLiteral (val, 0), aopLiteral (val, 1)); break; case 3: - /* PENDING: 0x02 or 0x%02x, CDATA? */ - fprintf (oFile, "\t.byte %s,%s,#0x02\n", - aopLiteral (val, 0), aopLiteral (val, 1)); + if (IS_GENPTR(type) && floatFromVal(val)!=0) { + // non-zero mcs51 generic pointer + werror (E_LITERAL_GENERIC); + } + 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); + } + 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); @@ -873,7 +988,7 @@ printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) return; } - if (!(val = initPointer (ilist))) + if (!(val = initPointer (ilist, type))) return; /* if character pointer */ @@ -882,8 +997,10 @@ printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) return; /* check the type */ - if (compareType (type, val->type) == 0) + if (compareType (type, val->type) == 0) { werror (W_INIT_WRONG); + printFromToType (val->type, type); + } /* if val is literal */ if (IS_LITERAL (val->etype)) @@ -899,9 +1016,9 @@ printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) else tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1)); break; - case 3: - fprintf (oFile, "\t.byte %s,%s,#0x02\n", - aopLiteral (val, 0), aopLiteral (val, 1)); + case 3: // how about '390?? + fprintf (oFile, "\t.byte %s,%s,#0x%d\n", + aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE); } return; } @@ -939,6 +1056,9 @@ printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) if (!ilist) return; + /* update line number for error msgs */ + lineno=sym->lineDef; + /* if structure then */ if (IS_STRUCT (type)) { @@ -963,7 +1083,7 @@ printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) /* if type is SPECIFIER */ if (IS_SPEC (type)) { - printIvalType (type, ilist, oFile); + printIvalType (sym, type, ilist, oFile); return; } } @@ -976,9 +1096,7 @@ emitStaticSeg (memmap * map, FILE * out) { symbol *sym; - /* fprintf(map->oFile,"\t.area\t%s\n",map->sname); */ - if (!out) - out = code->oFile; + /* fprintf(out, "\t.area\t%s\n", map->sname); */ /* for all variables in this segment do */ for (sym = setFirstItem (map->syms); sym; @@ -992,7 +1110,9 @@ emitStaticSeg (memmap * map, FILE * out) /* if it is not static add it to the public table */ if (!IS_STATIC (sym->etype)) - addSetHead (&publics, sym); + { + addSetHead (&publics, sym); + } /* print extra debug info if required */ if (options.debug) { @@ -1035,18 +1155,22 @@ emitStaticSeg (memmap * map, FILE * out) printIval (sym, sym->type, sym->ival, out); noAlloc--; } - else - { + else { /* allocate space */ + int size = getSize (sym->type); + + if (size==0) { + werror(E_UNKNOWN_SIZE,sym->name); + } fprintf (out, "%s:\n", sym->rname); /* special case for character strings */ if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) && SPEC_CVAL (sym->etype).v_char) - printChar (out, - SPEC_CVAL (sym->etype).v_char, - strlen (SPEC_CVAL (sym->etype).v_char) + 1); + printChar (out, + SPEC_CVAL (sym->etype).v_char, + strlen (SPEC_CVAL (sym->etype).v_char) + 1); else - tfprintf (out, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff); + tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff); } } } @@ -1056,7 +1180,7 @@ emitStaticSeg (memmap * map, FILE * out) /* emitMaps - emits the code for the data portion the code */ /*-----------------------------------------------------------------*/ void -emitMaps () +emitMaps (void) { inInitMode++; /* no special considerations for the following @@ -1065,12 +1189,19 @@ emitMaps () emitRegularMap (idata, TRUE, TRUE); emitRegularMap (bit, TRUE, FALSE); emitRegularMap (xdata, TRUE, TRUE); + if (port->genXINIT) { + emitRegularMap (xidata, TRUE, TRUE); + } emitRegularMap (sfr, FALSE, FALSE); emitRegularMap (sfrbit, FALSE, FALSE); emitRegularMap (home, TRUE, FALSE); emitRegularMap (code, TRUE, FALSE); emitStaticSeg (statsg, code->oFile); + if (port->genXINIT) { + tfprintf (code->oFile, "\t!area\n", xinit->sname); + emitStaticSeg (xinit, code->oFile); + } inInitMode--; } @@ -1119,7 +1250,6 @@ createInterruptVect (FILE * vFile) if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts))) { /* "generic" interrupt table header (if port doesn't specify one). - * Look suspiciously like 8051 code to me... */ @@ -1191,7 +1321,7 @@ printExterns (FILE * afile) for (sym = setFirstItem (externs); sym; sym = setNextItem (externs)) - tfprintf (afile, "\t!global\n", sym->rname); + tfprintf (afile, "\t!extern\n", sym->rname); } /*-----------------------------------------------------------------*/ @@ -1214,11 +1344,6 @@ emitOverlay (FILE * afile) if (elementsInSet (ovrset)) { - /* this dummy area is used to fool the assembler - otherwise the assembler will append each of these - declarations into one chunk and will not overlay - sad but true */ - fprintf (afile, "\t.area _DUMMY\n"); /* output the area informtion */ fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name); /* MOF */ } @@ -1226,8 +1351,7 @@ emitOverlay (FILE * afile) for (sym = setFirstItem (ovrset); sym; sym = setNextItem (ovrset)) { - - /* if extern then add it to the publics tabledo nothing */ + /* if extern then it is in the publics table: do nothing */ if (IS_EXTERN (sym->etype)) continue; @@ -1243,7 +1367,9 @@ emitOverlay (FILE * afile) and addPublics allowed then add it to the public set */ if ((sym->_isparm && !IS_REGPARM (sym->etype)) && !IS_STATIC (sym->etype)) - addSetHead (&publics, sym); + { + addSetHead (&publics, sym); + } /* if extern then do nothing or is a function then do nothing */ @@ -1281,16 +1407,20 @@ emitOverlay (FILE * afile) sym->rname, SPEC_ADDR (sym->etype)); } - else - { + else { + int size = getSize(sym->type); + + if (size==0) { + werror(E_UNKNOWN_SIZE,sym->name); + } if (options.debug) - fprintf (afile, "==.\n"); + fprintf (afile, "==.\n"); /* allocate space */ tfprintf (afile, "!labeldef\n", sym->rname); tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff); - } - + } + } } } @@ -1299,7 +1429,7 @@ emitOverlay (FILE * afile) /* glue - the final glue that hold the whole thing together */ /*-----------------------------------------------------------------*/ void -glue () +glue (void) { FILE *vFile; FILE *asmFile; @@ -1330,8 +1460,16 @@ glue () if (!options.c1mode) { - sprintf (scratchFileName, srcFileName); + /* -o option overrides default name? */ + if (noAssemble && fullDstFileName) + { + strcpy (scratchFileName, fullDstFileName); + } + else + { + strcpy (scratchFileName, dstFileName); strcat (scratchFileName, port->assembler.file_ext); + } } else { @@ -1373,6 +1511,25 @@ glue () fprintf (asmFile, "; special function bits \n"); fprintf (asmFile, "%s", iComments2); copyFile (asmFile, sfrbit->oFile); + + /*JCF: Create the areas for the register banks*/ + if( TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51 ) + { + if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3]) + { + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; overlayable register banks \n"); + fprintf (asmFile, "%s", iComments2); + if(RegBankUsed[0]) + fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n"); + if(RegBankUsed[1]||options.parms_in_bank1) + fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n"); + if(RegBankUsed[2]) + fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n"); + if(RegBankUsed[3]) + fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n"); + } + } /* copy the data segment */ fprintf (asmFile, "%s", iComments2); @@ -1382,10 +1539,12 @@ glue () /* create the overlay segments */ - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; overlayable items in internal ram \n"); - fprintf (asmFile, "%s", iComments2); - copyFile (asmFile, ovrFile); + if (overlay) { + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; overlayable items in internal ram \n"); + fprintf (asmFile, "%s", iComments2); + copyFile (asmFile, ovrFile); + } /* create the stack segment MOF */ if (mainf && IFFUNC_HASBODY(mainf->type)) @@ -1398,10 +1557,12 @@ glue () } /* create the idata segment */ - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; indirectly addressable internal ram data\n"); - fprintf (asmFile, "%s", iComments2); - copyFile (asmFile, idata->oFile); + if (idata) { + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; indirectly addressable internal ram data\n"); + fprintf (asmFile, "%s", iComments2); + copyFile (asmFile, idata->oFile); + } /* copy the bit segment */ fprintf (asmFile, "%s", iComments2); @@ -1426,6 +1587,12 @@ glue () fprintf (asmFile, "%s", iComments2); copyFile (asmFile, xdata->oFile); + /* copy xternal initialized ram data */ + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; external initialized ram data\n"); + fprintf (asmFile, "%s", iComments2); + copyFile (asmFile, xidata->oFile); + /* copy the interrupt vector table */ if (mainf && IFFUNC_HASBODY(mainf->type)) { @@ -1465,16 +1632,8 @@ glue () (unsigned int) options.xdata_loc & 0xff); } - /* initialise the stack pointer */ - /* if the user specified a value then use it */ - if (options.stack_loc) - fprintf (asmFile, "\tmov\tsp,#%d\n", options.stack_loc); - else - /* no: we have to compute it */ - if (!options.stackOnData && maxRegBank <= 3) - fprintf (asmFile, "\tmov\tsp,#%d\n", ((maxRegBank + 1) * 8) - 1); - else - fprintf (asmFile, "\tmov\tsp,#__start__stack\n"); /* MOF */ + /* 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"); @@ -1482,6 +1641,11 @@ glue () fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n"); fprintf (asmFile, "__sdcc_init_data:\n"); + // if the port can copy the XINIT segment to XISEG + if (port->genXINIT) { + port->genXINIT(asmFile); + } + } copyFile (asmFile, statsg->oFile); @@ -1531,19 +1695,13 @@ glue () } copyFile (asmFile, code->oFile); + if (port->genAssemblerEnd) { + port->genAssemblerEnd(asmFile); + } fclose (asmFile); - applyToSet (tmpfileSet, closeTmpFiles); - applyToSet (tmpfileNameSet, rmTmpFiles); -} -#if defined (__MINGW32__) || defined (__CYGWIN__) || defined (_MSC_VER) -void -rm_tmpfiles (void) -{ - applyToSet (tmpfileSet, closeTmpFiles); - applyToSet (tmpfileNameSet, rmTmpFiles); + rm_tmpfiles (); } -#endif /** Creates a temporary file name a'la tmpnam which avoids the bugs in cygwin wrt c:\tmp. @@ -1552,7 +1710,6 @@ rm_tmpfiles (void) char * tempfilename (void) { -#if !defined(_MSC_VER) const char *tmpdir = NULL; if (getenv ("TMP")) tmpdir = getenv ("TMP"); @@ -1568,7 +1725,6 @@ tempfilename (void) return name; } } -#endif return tmpnam (NULL); } @@ -1579,7 +1735,6 @@ tempfilename (void) FILE * tempfile (void) { -#if !defined(_MSC_VER) const char *tmpdir = NULL; if (getenv ("TMP")) tmpdir = getenv ("TMP"); @@ -1601,7 +1756,5 @@ tempfile (void) } return NULL; } -#endif return tmpfile (); } -