1 /*-------------------------------------------------------------------------
3 SDCCglue.c - glues everything we have done together into one file.
4 Written By - Sandeep Dutta . sandeep.dutta@usa.net (1998)
6 This program is free software; you can redistribute it and/or modify it
7 under the terms of the GNU General Public License as published by the
8 Free Software Foundation; either version 2, or (at your option) any
11 This program is distributed in the hope that it will be useful,
12 but WITHOUT ANY WARRANTY; without even the implied warranty of
13 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
14 GNU General Public License for more details.
16 You should have received a copy of the GNU General Public License
17 along with this program; if not, write to the Free Software
18 Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
20 In other words, you are welcome to use, share and improve this program.
21 You are forbidden to forbid anyone else to use, share and improve
22 what you give them. Help stamp out software-hoarding!
23 -------------------------------------------------------------------------*/
38 symbol *interrupts[INTNO_MAX+1];
40 void printIval (symbol *, sym_link *, initList *, FILE *);
41 set *publics = NULL; /* public variables */
42 set *externs = NULL; /* Variables that are declared as extern */
44 unsigned maxInterrupts = 0;
47 set *pipeSet = NULL; /* set of pipes */
48 set *tmpfileSet = NULL; /* set of tmp file created by the compiler */
49 set *tmpfileNameSet = NULL; /* All are unlinked at close. */
51 /*-----------------------------------------------------------------*/
52 /* closePipes - closes all pipes created by the compiler */
53 /*-----------------------------------------------------------------*/
54 DEFSETFUNC (closePipes)
67 /*-----------------------------------------------------------------*/
68 /* closeTmpFiles - closes all tmp files created by the compiler */
69 /* because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
70 /*-----------------------------------------------------------------*/
71 DEFSETFUNC (closeTmpFiles)
84 /*-----------------------------------------------------------------*/
85 /* rmTmpFiles - unlinks all tmp files created by the compiler */
86 /* because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
87 /*-----------------------------------------------------------------*/
88 DEFSETFUNC (rmTmpFiles)
102 /*-----------------------------------------------------------------*/
103 /* rm_tmpfiles - close and remove temporary files and delete sets */
104 /*-----------------------------------------------------------------*/
108 /* close temporary files */
109 applyToSet (pipeSet, closePipes);
110 /* close temporary files */
111 deleteSet (&pipeSet);
113 applyToSet (tmpfileSet, closeTmpFiles);
114 /* remove temporary files */
115 applyToSet (tmpfileNameSet, rmTmpFiles);
116 /* delete temorary file sets */
117 deleteSet (&tmpfileSet);
118 deleteSet (&tmpfileNameSet);
121 /*-----------------------------------------------------------------*/
122 /* copyFile - copies source file to destination file */
123 /*-----------------------------------------------------------------*/
125 copyFile (FILE * dest, FILE * src)
131 if ((ch = fgetc (src)) != EOF)
136 aopLiteralLong (value * val, int offset, int size)
145 // assuming we have been warned before
149 /* if it is a float then it gets tricky */
150 /* otherwise it is fairly simple */
151 if (!IS_FLOAT (val->type)) {
152 unsigned long v = (unsigned long) floatFromVal (val);
157 tsprintf (buffer, sizeof(buffer),
158 "!immedbyte", (unsigned int) v & 0xff);
161 tsprintf (buffer, sizeof(buffer),
162 "!immedword", (unsigned int) v & 0xffff);
165 /* Hmm. Too big for now. */
168 return Safe_strdup (buffer);
171 /* PENDING: For now size must be 1 */
174 /* it is type float */
175 fl.f = (float) floatFromVal (val);
176 #ifdef WORDS_BIGENDIAN
177 tsprintf (buffer, sizeof(buffer),
178 "!immedbyte", fl.c[3 - offset]);
180 tsprintf (buffer, sizeof(buffer),
181 "!immedbyte", fl.c[offset]);
183 return Safe_strdup (buffer);
186 /*-----------------------------------------------------------------*/
187 /* aopLiteral - string from a literal value */
188 /*-----------------------------------------------------------------*/
190 aopLiteral (value * val, int offset)
192 return aopLiteralLong (val, offset, 1);
195 /*-----------------------------------------------------------------*/
196 /* emitRegularMap - emit code for maps with no special cases */
197 /*-----------------------------------------------------------------*/
199 emitRegularMap (memmap * map, bool addPublics, bool arFlag)
209 /* PENDING: special case here - should remove */
210 if (!strcmp (map->sname, CODE_NAME))
211 tfprintf (map->oFile, "\t!areacode\n", map->sname);
212 else if (!strcmp (map->sname, DATA_NAME))
213 tfprintf (map->oFile, "\t!areadata\n", map->sname);
214 else if (!strcmp (map->sname, HOME_NAME))
215 tfprintf (map->oFile, "\t!areahome\n", map->sname);
217 tfprintf (map->oFile, "\t!area\n", map->sname);
220 for (sym = setFirstItem (map->syms); sym;
221 sym = setNextItem (map->syms))
225 /* if extern then add it into the extern list */
226 if (IS_EXTERN (sym->etype))
228 addSetHead (&externs, sym);
232 /* if allocation required check is needed
233 then check if the symbol really requires
234 allocation only for local variables */
236 if (arFlag && !IS_AGGREGATE (sym->type) &&
237 !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
238 !sym->allocreq && sym->level)
241 /* for bitvar locals and parameters */
242 if (!arFlag && !sym->allocreq && sym->level
243 && !SPEC_ABSA (sym->etype)) {
247 /* if global variable & not static or extern
248 and addPublics allowed then add it to the public set */
249 if ((sym->level == 0 ||
250 (sym->_isparm && !IS_REGPARM (sym->etype))) &&
252 !IS_STATIC (sym->etype) &&
253 (IS_FUNC(sym->type) ? (sym->used || IFFUNC_HASBODY(sym->type)) : 1))
255 addSetHead (&publics, sym);
258 /* if extern then do nothing or is a function
260 if (IS_FUNC (sym->type) && !(sym->isitmp))
263 /* print extra debug info if required */
266 if (!sym->level) /* global */
268 if (IS_STATIC (sym->etype))
269 fprintf (map->oFile, "F%s$", moduleName); /* scope is file */
271 fprintf (map->oFile, "G$"); /* scope is global */
275 /* symbol is local */
276 fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-"));
278 fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block);
281 /* if it has an initial value then do it only if
282 it is a global variable */
283 if (sym->ival && sym->level == 0) {
284 if (SPEC_OCLS(sym->etype)==xidata) {
285 /* create a new "XINIT (CODE)" symbol, that will be emitted later
287 newSym=copySymbol (sym);
288 SPEC_OCLS(newSym->etype)=xinit;
289 SNPRINTF (newSym->name, sizeof(newSym->name), "__xinit_%s", sym->name);
290 SNPRINTF (newSym->rname, sizeof(newSym->rname), "__xinit_%s", sym->rname);
291 if (IS_SPEC (newSym->type))
292 SPEC_CONST (newSym->type) = 1;
294 DCL_PTR_CONST (newSym->type) = 1;
295 SPEC_STAT(newSym->etype)=1;
296 resolveIvalSym(newSym->ival, newSym->type);
298 // add it to the "XINIT (CODE)" segment
299 addSet(&xinit->syms, newSym);
301 if (!SPEC_ABSA (sym->etype))
303 FILE *tmpFile = tempfile ();
304 addSetHead (&tmpfileSet, tmpFile);
305 // before allocation we must parse the sym->ival tree
306 // but without actually generating initialization code
308 resolveIvalSym (sym->ival, sym->type);
309 printIval (sym, sym->type, sym->ival, tmpFile);
315 if (IS_AGGREGATE (sym->type)) {
316 ival = initAggregates (sym, sym->ival, NULL);
318 if (getNelements(sym->type, sym->ival)>1) {
319 werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "scalar",
322 ival = newNode ('=', newAst_VALUE (symbolVal (sym)),
323 decorateType (resolveSymbols (list2expr (sym->ival)), RESULT_TYPE_NONE));
325 codeOutFile = statsg->oFile;
328 // set ival's lineno to where the symbol was defined
329 setAstLineno (ival, lineno=sym->lineDef);
330 // check if this is not a constant expression
331 if (!constExprTree(ival)) {
332 werror (E_CONST_EXPECTED, "found expression");
333 // but try to do it anyway
336 if (!astErrors(ival))
337 eBBlockFromiCode (iCodeFromAst (ival));
344 /* if it has an absolute address then generate
345 an equate for this no need to allocate space */
346 if (SPEC_ABSA (sym->etype))
350 fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
352 if (TARGET_IS_XA51) {
355 } else if (map==bit || map==sfrbit) {
359 fprintf (map->oFile, "%s\t%s\t0x%04x\n",
361 SPEC_ADDR (sym->etype));
364 int size = getSize (sym->type) + sym->flexArrayLength;
366 werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE, sym->name);
370 fprintf (map->oFile, "==.\n");
372 if (IS_STATIC (sym->etype))
373 tfprintf (map->oFile, "!slabeldef\n", sym->rname);
375 tfprintf (map->oFile, "!labeldef\n", sym->rname);
376 tfprintf (map->oFile, "\t!ds\n",
377 (unsigned int) size & 0xffff);
382 /*-----------------------------------------------------------------*/
383 /* initPointer - pointer initialization code massaging */
384 /*-----------------------------------------------------------------*/
386 initPointer (initList * ilist, sym_link *toType)
392 return valCastLiteral(toType, 0.0);
395 expr = list2expr (ilist);
400 /* try it the old way first */
401 if ((val = constExprValue (expr, FALSE)))
404 /* ( ptr + constant ) */
405 if (IS_AST_OP (expr) &&
406 (expr->opval.op == '+' || expr->opval.op == '-') &&
407 IS_AST_SYM_VALUE (expr->left) &&
408 (IS_ARRAY(expr->left->ftype) || IS_PTR(expr->left->ftype)) &&
409 compareType(toType, expr->left->ftype) &&
410 IS_AST_LIT_VALUE (expr->right)) {
411 return valForCastAggr (expr->left, expr->left->ftype,
417 if (IS_AST_OP(expr) && expr->opval.op==CAST &&
418 IS_AST_OP(expr->right) && expr->right->opval.op=='&') {
419 if (compareType(toType, expr->left->ftype)!=1) {
420 werror (W_INIT_WRONG);
421 printFromToType(expr->left->ftype, toType);
427 /* no then we have to do these cludgy checks */
428 /* pointers can be initialized with address of
429 a variable or address of an array element */
430 if (IS_AST_OP (expr) && expr->opval.op == '&') {
431 /* address of symbol */
432 if (IS_AST_SYM_VALUE (expr->left)) {
433 val = copyValue (AST_VALUE (expr->left));
434 val->type = newLink (DECLARATOR);
435 if (SPEC_SCLS (expr->left->etype) == S_CODE) {
436 DCL_TYPE (val->type) = CPOINTER;
437 DCL_PTR_CONST (val->type) = port->mem.code_ro;
439 else if (SPEC_SCLS (expr->left->etype) == S_XDATA)
440 DCL_TYPE (val->type) = FPOINTER;
441 else if (SPEC_SCLS (expr->left->etype) == S_XSTACK)
442 DCL_TYPE (val->type) = PPOINTER;
443 else if (SPEC_SCLS (expr->left->etype) == S_IDATA)
444 DCL_TYPE (val->type) = IPOINTER;
445 else if (SPEC_SCLS (expr->left->etype) == S_EEPROM)
446 DCL_TYPE (val->type) = EEPPOINTER;
448 DCL_TYPE (val->type) = POINTER;
449 val->type->next = expr->left->ftype;
450 val->etype = getSpec (val->type);
454 /* if address of indexed array */
455 if (IS_AST_OP (expr->left) && expr->left->opval.op == '[')
456 return valForArray (expr->left);
458 /* if address of structure element then
460 if (IS_AST_OP (expr->left) &&
461 expr->left->opval.op == '.') {
462 return valForStructElem (expr->left->left,
467 (&some_struct)->element */
468 if (IS_AST_OP (expr->left) &&
469 expr->left->opval.op == PTR_OP &&
470 IS_ADDRESS_OF_OP (expr->left->left)) {
471 return valForStructElem (expr->left->left->left,
475 /* case 3. (((char *) &a) +/- constant) */
476 if (IS_AST_OP (expr) &&
477 (expr->opval.op == '+' || expr->opval.op == '-') &&
478 IS_AST_OP (expr->left) && expr->left->opval.op == CAST &&
479 IS_AST_OP (expr->left->right) &&
480 expr->left->right->opval.op == '&' &&
481 IS_AST_LIT_VALUE (expr->right)) {
483 return valForCastAggr (expr->left->right->left,
484 expr->left->left->opval.lnk,
485 expr->right, expr->opval.op);
488 /* case 4. (char *)(array type) */
489 if (IS_CAST_OP(expr) && IS_AST_SYM_VALUE (expr->right) &&
490 IS_ARRAY(expr->right->ftype)) {
492 val = copyValue (AST_VALUE (expr->right));
493 val->type = newLink (DECLARATOR);
494 if (SPEC_SCLS (expr->right->etype) == S_CODE) {
495 DCL_TYPE (val->type) = CPOINTER;
496 DCL_PTR_CONST (val->type) = port->mem.code_ro;
498 else if (SPEC_SCLS (expr->right->etype) == S_XDATA)
499 DCL_TYPE (val->type) = FPOINTER;
500 else if (SPEC_SCLS (expr->right->etype) == S_XSTACK)
501 DCL_TYPE (val->type) = PPOINTER;
502 else if (SPEC_SCLS (expr->right->etype) == S_IDATA)
503 DCL_TYPE (val->type) = IPOINTER;
504 else if (SPEC_SCLS (expr->right->etype) == S_EEPROM)
505 DCL_TYPE (val->type) = EEPPOINTER;
507 DCL_TYPE (val->type) = POINTER;
508 val->type->next = expr->right->ftype->next;
509 val->etype = getSpec (val->type);
514 werrorfl (expr->filename, expr->lineno, E_INCOMPAT_PTYPES);
516 werror (E_INCOMPAT_PTYPES);
521 /*-----------------------------------------------------------------*/
522 /* printChar - formats and prints a characater string with DB */
523 /*-----------------------------------------------------------------*/
525 printChar (FILE * ofile, char *s, int plen)
533 while (len && pplen < plen)
536 while (i && pplen < plen)
538 if (*s < ' ' || *s == '\"' || *s=='\\')
542 tfprintf (ofile, "\t!ascii\n", buf);
543 tfprintf (ofile, "\t!db !constbyte\n", (unsigned char)*s);
558 tfprintf (ofile, "\t!ascii\n", buf);
569 tfprintf (ofile, "\t!db !constbyte\n", 0);
574 /*-----------------------------------------------------------------*/
575 /* return the generic pointer high byte for a given pointer type. */
576 /*-----------------------------------------------------------------*/
578 pointerTypeToGPByte (const int p_type, const char *iname, const char *oname)
586 werror (E_CANNOT_USE_GENERIC_POINTER,
587 iname ? iname : "<null>",
588 oname ? oname : "<null>");
595 return GPTYPE_XSTACK;
597 fprintf (stderr, "*** internal error: unknown pointer type %d in GPByte.\n",
605 /*-----------------------------------------------------------------*/
606 /* printPointerType - generates ival for pointer type */
607 /*-----------------------------------------------------------------*/
609 _printPointerType (FILE * oFile, const char *name)
611 if (options.model == MODEL_FLAT24)
613 if (port->little_endian)
614 fprintf (oFile, "\t.byte %s,(%s >> 8),(%s >> 16)", name, name, name);
616 fprintf (oFile, "\t.byte (%s >> 16),(%s >> 8),%s", name, name, name);
620 if (port->little_endian)
621 fprintf (oFile, "\t.byte %s,(%s >> 8)", name, name);
623 fprintf (oFile, "\t.byte (%s >> 8),%s", name, name);
627 /*-----------------------------------------------------------------*/
628 /* printPointerType - generates ival for pointer type */
629 /*-----------------------------------------------------------------*/
631 printPointerType (FILE * oFile, const char *name)
633 _printPointerType (oFile, name);
634 fprintf (oFile, "\n");
637 /*-----------------------------------------------------------------*/
638 /* printGPointerType - generates ival for generic pointer type */
639 /*-----------------------------------------------------------------*/
641 printGPointerType (FILE * oFile, const char *iname, const char *oname,
642 const unsigned int type)
644 _printPointerType (oFile, iname);
645 fprintf (oFile, ",#0x%02x\n", pointerTypeToGPByte (type, iname, oname));
648 /*-----------------------------------------------------------------*/
649 /* printIvalType - generates ival for int/char */
650 /*-----------------------------------------------------------------*/
652 printIvalType (symbol *sym, sym_link * type, initList * ilist, FILE * oFile)
656 /* if initList is deep */
657 if (ilist && (ilist->type == INIT_DEEP))
658 ilist = ilist->init.deep;
660 if (!(val = list2val (ilist))) {
661 // assuming a warning has been thrown
665 if (val->type != type) {
666 val = valCastLiteral(type, floatFromVal(val));
669 switch (getSize (type)) {
672 tfprintf (oFile, "\t!db !constbyte\n", 0);
674 tfprintf (oFile, "\t!dbs\n",
675 aopLiteral (val, 0));
679 if (port->use_dw_for_init)
680 tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
681 else if (port->little_endian)
682 fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
684 fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 1), aopLiteral (val, 0));
688 tfprintf (oFile, "\t!dw !constword\n", 0);
689 tfprintf (oFile, "\t!dw !constword\n", 0);
691 else if (port->little_endian) {
692 fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
693 aopLiteral (val, 0), aopLiteral (val, 1),
694 aopLiteral (val, 2), aopLiteral (val, 3));
697 fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
698 aopLiteral (val, 3), aopLiteral (val, 2),
699 aopLiteral (val, 1), aopLiteral (val, 0));
705 /*-----------------------------------------------------------------*/
706 /* printIvalBitFields - generate initializer for bitfields */
707 /*-----------------------------------------------------------------*/
708 void printIvalBitFields(symbol **sym, initList **ilist, FILE * oFile)
712 initList *lilist = *ilist ;
713 unsigned long ival = 0;
719 val = list2val(lilist);
721 if (SPEC_BLEN(lsym->etype) > 8) {
722 size += ((SPEC_BLEN (lsym->etype) / 8) +
723 (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
726 size = ((SPEC_BLEN (lsym->etype) / 8) +
727 (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
729 i = (unsigned long)floatFromVal(val);
730 i <<= SPEC_BSTR (lsym->etype);
732 if (! ( lsym->next &&
733 (IS_BITFIELD(lsym->next->type)) &&
734 (SPEC_BSTR(lsym->next->etype)))) break;
736 lilist = lilist->next;
740 tfprintf (oFile, "\t!db !constbyte\n",ival);
744 tfprintf (oFile, "\t!dw !constword\n",ival);
746 case 4: /* EEP: why is this db and not dw? */
747 tfprintf (oFile, "\t!db !constword,!constword\n",
748 (ival >> 8) & 0xffff, (ival & 0xffff));
755 /*-----------------------------------------------------------------*/
756 /* printIvalStruct - generates initial value for structures */
757 /*-----------------------------------------------------------------*/
759 printIvalStruct (symbol * sym, sym_link * type,
760 initList * ilist, FILE * oFile)
763 initList *iloop = NULL;
765 sflds = SPEC_STRUCT (type)->fields;
768 if (ilist->type != INIT_DEEP) {
769 werrorfl (sym->fileDef, sym->lineDef, E_INIT_STRUCT, sym->name);
773 iloop = ilist->init.deep;
776 if (SPEC_STRUCT (type)->type == UNION) {
777 printIval (sym, sflds->type, iloop, oFile);
780 for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) {
781 if (IS_BITFIELD(sflds->type)) {
782 printIvalBitFields(&sflds,&iloop,oFile);
784 printIval (sym, sflds->type, iloop, oFile);
789 werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "struct", sym->name);
794 /*-----------------------------------------------------------------*/
795 /* printIvalChar - generates initital value for character array */
796 /*-----------------------------------------------------------------*/
798 printIvalChar (symbol * sym, sym_link * type, initList * ilist, FILE * oFile, char *s)
801 unsigned int size = DCL_ELEM (type);
805 val = list2val (ilist);
806 /* if the value is a character string */
807 if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
811 /* we have not been given a size, but now we know it */
812 size = strlen (SPEC_CVAL (val->etype).v_char) + 1;
813 /* but first check, if it's a flexible array */
814 if (sym && IS_STRUCT (sym->type))
815 sym->flexArrayLength = size;
817 DCL_ELEM (type) = size;
820 printChar (oFile, SPEC_CVAL (val->etype).v_char, size);
828 printChar (oFile, s, strlen (s) + 1);
832 /*-----------------------------------------------------------------*/
833 /* printIvalArray - generates code for array initialization */
834 /*-----------------------------------------------------------------*/
836 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
841 unsigned int size = 0;
844 /* take care of the special case */
845 /* array of characters can be init */
847 if (IS_CHAR (type->next)) {
848 val = list2val(ilist);
850 werrorfl (ilist->filename, ilist->lineno, E_INIT_STRUCT, sym->name);
853 if (!IS_LITERAL(val->etype)) {
854 werrorfl (ilist->filename, ilist->lineno, E_CONST_EXPECTED);
857 if (printIvalChar (sym, type,
858 (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
859 oFile, SPEC_CVAL (sym->etype).v_char))
862 /* not the special case */
863 if (ilist->type != INIT_DEEP) {
864 werrorfl (ilist->filename, ilist->lineno, E_INIT_STRUCT, sym->name);
868 for (iloop=ilist->init.deep; iloop; iloop=iloop->next) {
869 if ((++size > DCL_ELEM(type)) && DCL_ELEM(type)) {
870 werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "array", sym->name);
873 printIval (sym, type->next, iloop, oFile);
877 if (DCL_ELEM(type)) {
878 // pad with zeros if needed
879 if (size<DCL_ELEM(type)) {
880 size = (DCL_ELEM(type) - size) * getSize(type->next);
882 tfprintf (oFile, "\t!db !constbyte\n", 0);
886 /* we have not been given a size, but now we know it */
887 /* but first check, if it's a flexible array */
888 if (IS_STRUCT (sym->type))
889 sym->flexArrayLength = size * getSize (type->next);
891 DCL_ELEM (type) = size;
897 /*-----------------------------------------------------------------*/
898 /* printIvalFuncPtr - generate initial value for function pointers */
899 /*-----------------------------------------------------------------*/
901 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
907 val = list2val (ilist);
909 val = valCastLiteral(type, 0.0);
912 // an error has been thrown already
916 if (IS_LITERAL(val->etype)) {
917 if (compareType(type, val->etype) == 0) {
918 werrorfl (ilist->filename, ilist->lineno, E_INCOMPAT_TYPES);
919 printFromToType (val->type, type);
921 printIvalCharPtr (NULL, type, val, oFile);
925 /* check the types */
926 if ((dLvl = compareType (val->type, type->next)) <= 0)
928 tfprintf (oFile, "\t!dw !constword\n", 0);
932 /* now generate the name */
935 if (port->use_dw_for_init)
937 tfprintf (oFile, "\t!dws\n", val->name);
941 printPointerType (oFile, val->name);
944 else if (port->use_dw_for_init)
946 tfprintf (oFile, "\t!dws\n", val->sym->rname);
950 printPointerType (oFile, val->sym->rname);
956 /*-----------------------------------------------------------------*/
957 /* printIvalCharPtr - generates initial values for character pointers */
958 /*-----------------------------------------------------------------*/
960 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
964 /* PENDING: this is _very_ mcs51 specific, including a magic
966 It's also endin specific.
968 size = getSize (type);
970 if (val->name && strlen (val->name))
972 if (size == 1) /* This appears to be Z80 specific?? */
975 "\t!dbs\n", val->name);
977 else if (size == FPTRSIZE)
979 if (port->use_dw_for_init)
981 tfprintf (oFile, "\t!dws\n", val->name);
985 printPointerType (oFile, val->name);
988 else if (size == GPTRSIZE)
991 if (IS_PTR (val->type)) {
992 type = DCL_TYPE (val->type);
994 type = PTR_TYPE (SPEC_OCLS (val->etype));
996 if (val->sym && val->sym->isstrlit) {
997 // this is a literal string
1000 printGPointerType (oFile, val->name, sym->name, type);
1004 fprintf (stderr, "*** internal error: unknown size in "
1005 "printIvalCharPtr.\n");
1010 // these are literals assigned to pointers
1014 tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
1017 if (port->use_dw_for_init)
1018 tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
1019 else if (port->little_endian)
1020 tfprintf (oFile, "\t.byte %s,%s\n",
1021 aopLiteral (val, 0), aopLiteral (val, 1));
1023 tfprintf (oFile, "\t.byte %s,%s\n",
1024 aopLiteral (val, 1), aopLiteral (val, 0));
1027 if (IS_GENPTR(type) && floatFromVal(val)!=0) {
1028 // non-zero mcs51 generic pointer
1029 werrorfl (sym->fileDef, sym->lineDef, E_LITERAL_GENERIC);
1031 if (port->little_endian) {
1032 fprintf (oFile, "\t.byte %s,%s,%s\n",
1033 aopLiteral (val, 0),
1034 aopLiteral (val, 1),
1035 aopLiteral (val, 2));
1037 fprintf (oFile, "\t.byte %s,%s,%s\n",
1038 aopLiteral (val, 2),
1039 aopLiteral (val, 1),
1040 aopLiteral (val, 0));
1044 if (IS_GENPTR(type) && floatFromVal(val)!=0) {
1045 // non-zero ds390 generic pointer
1046 werrorfl (sym->fileDef, sym->lineDef, E_LITERAL_GENERIC);
1048 if (port->little_endian) {
1049 fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
1050 aopLiteral (val, 0),
1051 aopLiteral (val, 1),
1052 aopLiteral (val, 2),
1053 aopLiteral (val, 3));
1055 fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
1056 aopLiteral (val, 3),
1057 aopLiteral (val, 2),
1058 aopLiteral (val, 1),
1059 aopLiteral (val, 0));
1067 if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
1068 addSet (&statsg->syms, val->sym);
1074 /*-----------------------------------------------------------------*/
1075 /* printIvalPtr - generates initial value for pointers */
1076 /*-----------------------------------------------------------------*/
1078 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1084 if (ilist && (ilist->type == INIT_DEEP))
1085 ilist = ilist->init.deep;
1087 /* function pointer */
1088 if (IS_FUNC (type->next))
1090 printIvalFuncPtr (type, ilist, oFile);
1094 if (!(val = initPointer (ilist, type)))
1097 /* if character pointer */
1098 if (IS_CHAR (type->next))
1099 if (printIvalCharPtr (sym, type, val, oFile))
1102 /* check the type */
1103 if (compareType (type, val->type) == 0) {
1104 werrorfl (ilist->filename, ilist->lineno, W_INIT_WRONG);
1105 printFromToType (val->type, type);
1108 /* if val is literal */
1109 if (IS_LITERAL (val->etype))
1111 switch (getSize (type))
1114 tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
1117 if (port->use_dw_for_init)
1118 tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
1119 else if (port->little_endian)
1120 tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1122 tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 1), aopLiteral (val, 0));
1124 case 3: // how about '390??
1125 fprintf (oFile, "; generic printIvalPtr\n");
1126 if (port->little_endian)
1128 fprintf (oFile, "\t.byte %s,%s",
1129 aopLiteral (val, 0), aopLiteral (val, 1));
1133 fprintf (oFile, "\t.byte %s,%s",
1134 aopLiteral (val, 1), aopLiteral (val, 0));
1136 if (IS_GENPTR (val->type))
1137 fprintf (oFile, ",%s\n", aopLiteral (val, 2));
1138 else if (IS_PTR (val->type))
1139 fprintf (oFile, ",#%x\n", pointerTypeToGPByte (DCL_TYPE (val->type), NULL, NULL));
1141 fprintf (oFile, ",%s\n", aopLiteral (val, 2));
1147 size = getSize (type);
1149 if (size == 1) /* Z80 specific?? */
1151 tfprintf (oFile, "\t!dbs\n", val->name);
1153 else if (size == FPTRSIZE)
1155 if (port->use_dw_for_init) {
1156 tfprintf (oFile, "\t!dws\n", val->name);
1158 printPointerType (oFile, val->name);
1161 else if (size == GPTRSIZE)
1163 printGPointerType (oFile, val->name, sym->name,
1164 (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1165 PTR_TYPE (SPEC_OCLS (val->etype))));
1170 /*-----------------------------------------------------------------*/
1171 /* printIval - generates code for initial value */
1172 /*-----------------------------------------------------------------*/
1174 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1178 /* if structure then */
1179 if (IS_STRUCT (type))
1181 printIvalStruct (sym, type, ilist, oFile);
1185 /* if this is an array */
1186 if (IS_ARRAY (type))
1188 printIvalArray (sym, type, ilist, oFile);
1194 // not an aggregate, ilist must be a node
1195 if (ilist->type!=INIT_NODE) {
1196 // or a 1-element list
1197 if (ilist->init.deep->next) {
1198 werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "scalar",
1201 ilist=ilist->init.deep;
1205 // and the type must match
1206 itype=ilist->init.node->ftype;
1208 if (compareType(type, itype)==0) {
1209 // special case for literal strings
1210 if (IS_ARRAY (itype) && IS_CHAR (getSpec(itype)) &&
1211 // which are really code pointers
1212 IS_PTR(type) && DCL_TYPE(type)==CPOINTER) {
1215 werrorfl (ilist->filename, ilist->lineno, E_TYPE_MISMATCH, "assignment", " ");
1216 printFromToType(itype, type);
1221 /* if this is a pointer */
1224 printIvalPtr (sym, type, ilist, oFile);
1228 /* if type is SPECIFIER */
1231 printIvalType (sym, type, ilist, oFile);
1236 /*-----------------------------------------------------------------*/
1237 /* emitStaticSeg - emitcode for the static segment */
1238 /*-----------------------------------------------------------------*/
1240 emitStaticSeg (memmap * map, FILE * out)
1244 /* fprintf(out, "\t.area\t%s\n", map->sname); */
1246 /* for all variables in this segment do */
1247 for (sym = setFirstItem (map->syms); sym;
1248 sym = setNextItem (map->syms))
1251 /* if it is "extern" then do nothing */
1252 if (IS_EXTERN (sym->etype))
1255 /* if it is not static add it to the public
1257 if (!IS_STATIC (sym->etype))
1259 addSetHead (&publics, sym);
1262 /* print extra debug info if required */
1263 if (options.debug) {
1267 if (IS_STATIC (sym->etype))
1268 fprintf (out, "F%s$", moduleName); /* scope is file */
1270 fprintf (out, "G$"); /* scope is global */
1273 /* symbol is local */
1274 fprintf (out, "L%s$",
1275 (sym->localof ? sym->localof->name : "-null-"));
1276 fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1279 /* if it has an absolute address */
1280 if (SPEC_ABSA (sym->etype))
1283 fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1285 fprintf (out, "%s\t=\t0x%04x\n",
1287 SPEC_ADDR (sym->etype));
1292 fprintf (out, " == .\n");
1294 /* if it has an initial value */
1297 fprintf (out, "%s:\n", sym->rname);
1299 resolveIvalSym (sym->ival, sym->type);
1300 printIval (sym, sym->type, sym->ival, out);
1302 /* if sym is a simple string and sym->ival is a string,
1303 WE don't need it anymore */
1304 if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) &&
1305 IS_AST_SYM_VALUE(list2expr(sym->ival)) &&
1306 list2val(sym->ival)->sym->isstrlit) {
1307 freeStringSymbol(list2val(sym->ival)->sym);
1311 /* allocate space */
1312 int size = getSize (sym->type);
1315 werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE,sym->name);
1317 fprintf (out, "%s:\n", sym->rname);
1318 /* special case for character strings */
1319 if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1320 SPEC_CVAL (sym->etype).v_char)
1322 SPEC_CVAL (sym->etype).v_char,
1325 tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1331 /*-----------------------------------------------------------------*/
1332 /* emitMaps - emits the code for the data portion the code */
1333 /*-----------------------------------------------------------------*/
1337 int publicsfr = TARGET_IS_MCS51; /* Ideally, this should be true for all */
1338 /* ports but let's be conservative - EEP */
1341 /* no special considerations for the following
1342 data, idata & bit & xdata */
1343 emitRegularMap (data, TRUE, TRUE);
1344 emitRegularMap (idata, TRUE, TRUE);
1345 emitRegularMap (bit, TRUE, TRUE);
1346 emitRegularMap (pdata, TRUE, TRUE);
1347 emitRegularMap (xdata, TRUE, TRUE);
1348 if (port->genXINIT) {
1349 emitRegularMap (xidata, TRUE, TRUE);
1351 emitRegularMap (sfr, publicsfr, FALSE);
1352 emitRegularMap (sfrbit, publicsfr, FALSE);
1353 emitRegularMap (home, TRUE, FALSE);
1354 emitRegularMap (code, TRUE, FALSE);
1356 if (options.const_seg) {
1357 tfprintf (code->oFile, "\t!area\n", options.const_seg);
1359 emitStaticSeg (statsg, code->oFile);
1360 if (port->genXINIT) {
1361 tfprintf (code->oFile, "\t!area\n", xinit->sname);
1362 emitStaticSeg (xinit, code->oFile);
1367 /*-----------------------------------------------------------------*/
1368 /* flushStatics - flush all currently defined statics out to file */
1369 /* and delete. Temporary function */
1370 /*-----------------------------------------------------------------*/
1374 emitStaticSeg (statsg, codeOutFile);
1375 statsg->syms = NULL;
1378 /*-----------------------------------------------------------------*/
1379 /* createInterruptVect - creates the interrupt vector */
1380 /*-----------------------------------------------------------------*/
1382 createInterruptVect (FILE * vFile)
1384 mainf = newSymbol ("main", 0);
1387 /* only if the main function exists */
1388 if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1390 if (!options.cc_only && !noAssemble && !options.c1mode)
1395 /* if the main is only a prototype ie. no body then do nothing */
1396 if (!IFFUNC_HASBODY(mainf->type))
1398 /* if ! compile only then main function should be present */
1399 if (!options.cc_only && !noAssemble)
1404 tfprintf (vFile, "\t!areacode\n", HOME_NAME);
1405 fprintf (vFile, "__interrupt_vect:\n");
1408 if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1410 /* There's no such thing as a "generic" interrupt table header. */
1417 ";--------------------------------------------------------\n"
1418 "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1422 ";--------------------------------------------------------\n"};
1425 /*-----------------------------------------------------------------*/
1426 /* initialComments - puts in some initial comments */
1427 /*-----------------------------------------------------------------*/
1429 initialComments (FILE * afile)
1433 fprintf (afile, "%s", iComments1);
1434 fprintf (afile, "; Version " SDCC_VERSION_STR " #%s (%s)\n", getBuildNumber(), __DATE__);
1435 fprintf (afile, "; This file generated %s", asctime (localtime (&t)));
1436 fprintf (afile, "%s", iComments2);
1439 /*-----------------------------------------------------------------*/
1440 /* printPublics - generates .global for publics */
1441 /*-----------------------------------------------------------------*/
1443 printPublics (FILE * afile)
1447 fprintf (afile, "%s", iComments2);
1448 fprintf (afile, "; Public variables in this module\n");
1449 fprintf (afile, "%s", iComments2);
1451 for (sym = setFirstItem (publics); sym;
1452 sym = setNextItem (publics))
1453 tfprintf (afile, "\t!global\n", sym->rname);
1456 /*-----------------------------------------------------------------*/
1457 /* printExterns - generates .global for externs */
1458 /*-----------------------------------------------------------------*/
1460 printExterns (FILE * afile)
1464 fprintf (afile, "%s", iComments2);
1465 fprintf (afile, "; Externals used\n");
1466 fprintf (afile, "%s", iComments2);
1468 for (sym = setFirstItem (externs); sym;
1469 sym = setNextItem (externs))
1470 tfprintf (afile, "\t!extern\n", sym->rname);
1473 /*-----------------------------------------------------------------*/
1474 /* emitOverlay - will emit code for the overlay stuff */
1475 /*-----------------------------------------------------------------*/
1477 emitOverlay (FILE * afile)
1481 if (!elementsInSet (ovrSetSets))
1482 tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1484 /* for each of the sets in the overlay segment do */
1485 for (ovrset = setFirstItem (ovrSetSets); ovrset;
1486 ovrset = setNextItem (ovrSetSets))
1491 if (elementsInSet (ovrset))
1493 /* output the area informtion */
1494 fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name); /* MOF */
1497 for (sym = setFirstItem (ovrset); sym;
1498 sym = setNextItem (ovrset))
1500 /* if extern then it is in the publics table: do nothing */
1501 if (IS_EXTERN (sym->etype))
1504 /* if allocation required check is needed
1505 then check if the symbol really requires
1506 allocation only for local variables */
1507 if (!IS_AGGREGATE (sym->type) &&
1508 !(sym->_isparm && !IS_REGPARM (sym->etype))
1509 && !sym->allocreq && sym->level)
1512 /* if global variable & not static or extern
1513 and addPublics allowed then add it to the public set */
1514 if ((sym->_isparm && !IS_REGPARM (sym->etype))
1515 && !IS_STATIC (sym->etype))
1517 addSetHead (&publics, sym);
1520 /* if extern then do nothing or is a function
1522 if (IS_FUNC (sym->type))
1525 /* print extra debug info if required */
1530 if (IS_STATIC (sym->etype))
1531 fprintf (afile, "F%s$", moduleName); /* scope is file */
1533 fprintf (afile, "G$"); /* scope is global */
1536 /* symbol is local */
1537 fprintf (afile, "L%s$",
1538 (sym->localof ? sym->localof->name : "-null-"));
1539 fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1542 /* if is has an absolute address then generate
1543 an equate for this no need to allocate space */
1544 if (SPEC_ABSA (sym->etype))
1548 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1550 fprintf (afile, "%s\t=\t0x%04x\n",
1552 SPEC_ADDR (sym->etype));
1555 int size = getSize(sym->type);
1558 werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE);
1561 fprintf (afile, "==.\n");
1563 /* allocate space */
1564 tfprintf (afile, "!labeldef\n", sym->rname);
1565 tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1573 /*-----------------------------------------------------------------*/
1574 /* spacesToUnderscores - replace spaces with underscores */
1575 /*-----------------------------------------------------------------*/
1577 spacesToUnderscores (char *dest, const char *src, size_t len)
1582 assert(dest != NULL);
1583 assert(src != NULL);
1587 for (p = dest, i = 0; *src != '\0' && i < len; ++src, ++i) {
1588 *p++ = isspace((unsigned char)*src) ? '_' : *src;
1596 /*-----------------------------------------------------------------*/
1597 /* glue - the final glue that hold the whole thing together */
1598 /*-----------------------------------------------------------------*/
1604 FILE *ovrFile = tempfile ();
1605 char moduleBuf[PATH_MAX];
1608 if(port->general.glue_up_main &&
1609 (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51 || TARGET_IS_DS400))
1611 mcs51_like=1; /*So it has bits, sfr, sbits, data, idata, etc...*/
1618 addSetHead (&tmpfileSet, ovrFile);
1619 /* print the global struct definitions */
1623 vFile = tempfile ();
1624 /* PENDING: this isn't the best place but it will do */
1625 if (port->general.glue_up_main)
1627 /* create the interrupt vector table */
1628 createInterruptVect (vFile);
1631 addSetHead (&tmpfileSet, vFile);
1633 /* emit code for the all the variables declared */
1635 /* do the overlay segments */
1636 emitOverlay (ovrFile);
1638 outputDebugSymbols();
1640 /* now put it all together into the assembler file */
1641 /* create the assembler file name */
1643 /* -o option overrides default name? */
1644 if ((noAssemble || options.c1mode) && fullDstFileName)
1646 strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1650 strncpyz (scratchFileName, dstFileName, PATH_MAX);
1651 strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1654 if (!(asmFile = fopen (scratchFileName, "w")))
1656 werror (E_FILE_OPEN_ERR, scratchFileName);
1660 /* initial comments */
1661 initialComments (asmFile);
1663 /* print module name */
1664 tfprintf (asmFile, "\t!module\n",
1665 spacesToUnderscores (moduleBuf, moduleName, sizeof moduleBuf));
1668 fprintf (asmFile, "\t.optsdcc -m%s", port->target);
1670 switch(options.model)
1672 case MODEL_SMALL: fprintf (asmFile, " --model-small"); break;
1673 case MODEL_COMPACT: fprintf (asmFile, " --model-compact"); break;
1674 case MODEL_MEDIUM: fprintf (asmFile, " --model-medium"); break;
1675 case MODEL_LARGE: fprintf (asmFile, " --model-large"); break;
1676 case MODEL_FLAT24: fprintf (asmFile, " --model-flat24"); break;
1677 case MODEL_PAGE0: fprintf (asmFile, " --model-page0"); break;
1680 /*if(options.stackAuto) fprintf (asmFile, " --stack-auto");*/
1681 if(options.useXstack) fprintf (asmFile, " --xstack");
1682 /*if(options.intlong_rent) fprintf (asmFile, " --int-long-rent");*/
1683 /*if(options.float_rent) fprintf (asmFile, " --float-rent");*/
1684 if(options.noRegParams) fprintf (asmFile, " --no-reg-params");
1685 if(options.parms_in_bank1) fprintf (asmFile, " --parms-in-bank1");
1686 fprintf (asmFile, "\n");
1688 else if(TARGET_IS_Z80 || TARGET_IS_GBZ80 || TARGET_IS_HC08)
1690 fprintf (asmFile, "\t.optsdcc -m%s\n", port->target);
1693 tfprintf (asmFile, "\t!fileprelude\n");
1695 /* Let the port generate any global directives, etc. */
1696 if (port->genAssemblerPreamble)
1698 port->genAssemblerPreamble (asmFile);
1701 /* print the global variables in this module */
1702 printPublics (asmFile);
1703 if (port->assembler.externGlobal)
1704 printExterns (asmFile);
1707 ||( TARGET_IS_Z80 )) /*.p.t.20030924 need to output SFR table for Z80 as well */
1709 /* copy the sfr segment */
1710 fprintf (asmFile, "%s", iComments2);
1711 fprintf (asmFile, "; special function registers\n");
1712 fprintf (asmFile, "%s", iComments2);
1713 copyFile (asmFile, sfr->oFile);
1718 /* copy the sbit segment */
1719 fprintf (asmFile, "%s", iComments2);
1720 fprintf (asmFile, "; special function bits\n");
1721 fprintf (asmFile, "%s", iComments2);
1722 copyFile (asmFile, sfrbit->oFile);
1724 /*JCF: Create the areas for the register banks*/
1725 if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1727 fprintf (asmFile, "%s", iComments2);
1728 fprintf (asmFile, "; overlayable register banks\n");
1729 fprintf (asmFile, "%s", iComments2);
1731 fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1732 if(RegBankUsed[1]||options.parms_in_bank1)
1733 fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1735 fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1737 fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1741 fprintf (asmFile, "%s", iComments2);
1742 fprintf (asmFile, "; overlayable bit register bank\n");
1743 fprintf (asmFile, "%s", iComments2);
1744 fprintf (asmFile, "\t.area BIT_BANK\t(REL,OVR,DATA)\n");
1745 fprintf (asmFile, "bits:\n\t.ds 1\n");
1746 fprintf (asmFile, "\tb0 = bits[0]\n");
1747 fprintf (asmFile, "\tb1 = bits[1]\n");
1748 fprintf (asmFile, "\tb2 = bits[2]\n");
1749 fprintf (asmFile, "\tb3 = bits[3]\n");
1750 fprintf (asmFile, "\tb4 = bits[4]\n");
1751 fprintf (asmFile, "\tb5 = bits[5]\n");
1752 fprintf (asmFile, "\tb6 = bits[6]\n");
1753 fprintf (asmFile, "\tb7 = bits[7]\n");
1757 /* copy the data segment */
1758 fprintf (asmFile, "%s", iComments2);
1759 fprintf (asmFile, "; %s ram data\n", mcs51_like?"internal":"");
1760 fprintf (asmFile, "%s", iComments2);
1761 copyFile (asmFile, data->oFile);
1764 /* create the overlay segments */
1766 fprintf (asmFile, "%s", iComments2);
1767 fprintf (asmFile, "; overlayable items in %s ram \n", mcs51_like?"internal":"");
1768 fprintf (asmFile, "%s", iComments2);
1769 copyFile (asmFile, ovrFile);
1772 /* create the stack segment MOF */
1773 if (mainf && IFFUNC_HASBODY(mainf->type))
1775 fprintf (asmFile, "%s", iComments2);
1776 fprintf (asmFile, "; Stack segment in internal ram \n");
1777 fprintf (asmFile, "%s", iComments2);
1778 fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1779 "__start__stack:\n\t.ds\t1\n\n");
1782 /* create the idata segment */
1783 if ( (idata) && (mcs51_like) ) {
1784 fprintf (asmFile, "%s", iComments2);
1785 fprintf (asmFile, "; indirectly addressable internal ram data\n");
1786 fprintf (asmFile, "%s", iComments2);
1787 copyFile (asmFile, idata->oFile);
1790 /* copy the bit segment */
1792 fprintf (asmFile, "%s", iComments2);
1793 fprintf (asmFile, "; bit data\n");
1794 fprintf (asmFile, "%s", iComments2);
1795 copyFile (asmFile, bit->oFile);
1798 /* copy paged external ram data */
1801 fprintf (asmFile, "%s", iComments2);
1802 fprintf (asmFile, "; paged external ram data\n");
1803 fprintf (asmFile, "%s", iComments2);
1804 copyFile (asmFile, pdata->oFile);
1807 /* if external stack then reserve space for it */
1808 if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1810 fprintf (asmFile, "%s", iComments2);
1811 fprintf (asmFile, "; external stack \n");
1812 fprintf (asmFile, "%s", iComments2);
1813 fprintf (asmFile, "\t.area XSTK (PAG,XDATA)\n"
1814 "__start__xstack:\n\t.ds\t1\n\n");
1817 /* copy external ram data */
1819 fprintf (asmFile, "%s", iComments2);
1820 fprintf (asmFile, "; external ram data\n");
1821 fprintf (asmFile, "%s", iComments2);
1822 copyFile (asmFile, xdata->oFile);
1825 /* copy external initialized ram data */
1826 fprintf (asmFile, "%s", iComments2);
1827 fprintf (asmFile, "; external initialized ram data\n");
1828 fprintf (asmFile, "%s", iComments2);
1829 copyFile (asmFile, xidata->oFile);
1831 /* If the port wants to generate any extra areas, let it do so. */
1832 if (port->extraAreas.genExtraAreaDeclaration)
1834 port->extraAreas.genExtraAreaDeclaration(asmFile,
1835 mainf && IFFUNC_HASBODY(mainf->type));
1838 /* copy the interrupt vector table */
1839 if (mainf && IFFUNC_HASBODY(mainf->type))
1841 fprintf (asmFile, "%s", iComments2);
1842 fprintf (asmFile, "; interrupt vector \n");
1843 fprintf (asmFile, "%s", iComments2);
1844 copyFile (asmFile, vFile);
1847 /* copy global & static initialisations */
1848 fprintf (asmFile, "%s", iComments2);
1849 fprintf (asmFile, "; global & static initialisations\n");
1850 fprintf (asmFile, "%s", iComments2);
1852 /* Everywhere we generate a reference to the static_name area,
1853 * (which is currently only here), we immediately follow it with a
1854 * definition of the post_static_name area. This guarantees that
1855 * the post_static_name area will immediately follow the static_name
1858 tfprintf (asmFile, "\t!area\n", port->mem.home_name);
1859 tfprintf (asmFile, "\t!area\n", port->mem.static_name); /* MOF */
1860 tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1861 tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1863 if (mainf && IFFUNC_HASBODY(mainf->type))
1865 if (port->genInitStartup)
1867 port->genInitStartup(asmFile);
1871 fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1872 /* if external stack is specified then the
1873 higher order byte of the xdatalocation is
1874 going into P2 and the lower order going into
1876 if (options.useXstack)
1878 fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1879 (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1880 fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1881 (unsigned int) options.xdata_loc & 0xff);
1884 // This should probably be a port option, but I'm being lazy.
1885 // on the 400, the firmware boot loader gives us a valid stack
1886 // (see '400 data sheet pg. 85 (TINI400 ROM Initialization code)
1887 if (!TARGET_IS_DS400)
1889 /* initialise the stack pointer. JCF: aslink takes care of the location */
1890 fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n"); /* MOF */
1893 fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1894 fprintf (asmFile, "\tmov\ta,dpl\n");
1895 fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1896 fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1897 fprintf (asmFile, "__sdcc_init_data:\n");
1899 // if the port can copy the XINIT segment to XISEG
1902 port->genXINIT(asmFile);
1907 copyFile (asmFile, statsg->oFile);
1909 if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1911 /* This code is generated in the post-static area.
1912 * This area is guaranteed to follow the static area
1913 * by the ugly shucking and jiving about 20 lines ago.
1915 tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1916 fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1922 "%s", iComments2, iComments2);
1923 tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1924 copyFile (asmFile, home->oFile);
1926 if (mainf && IFFUNC_HASBODY(mainf->type))
1929 /* entry point @ start of HOME */
1930 fprintf (asmFile, "__sdcc_program_startup:\n");
1932 /* put in jump or call to main */
1933 if (options.mainreturn)
1935 fprintf (asmFile, "\tljmp\t_main\n"); /* needed? */
1936 fprintf (asmFile, ";\treturn from main will return to caller\n");
1940 fprintf (asmFile, "\tlcall\t_main\n");
1941 fprintf (asmFile, ";\treturn from main will lock up\n");
1942 fprintf (asmFile, "\tsjmp .\n");
1945 /* copy over code */
1946 fprintf (asmFile, "%s", iComments2);
1947 fprintf (asmFile, "; code\n");
1948 fprintf (asmFile, "%s", iComments2);
1949 tfprintf (asmFile, "\t!areacode\n", options.code_seg);
1950 copyFile (asmFile, code->oFile);
1952 if (port->genAssemblerEnd) {
1953 port->genAssemblerEnd(asmFile);
1961 /** Creates a temporary file with unique file name
1963 - TMP, TEMP, TMPDIR env. variables
1964 - if Un*x system: /usr/tmp and /tmp
1965 - root directory using mkstemp() if available
1966 - default location using tempnam()
1969 tempfileandname(char *fname, size_t len)
1971 #define TEMPLATE "sdccXXXXXX"
1972 #define TEMPLATE_LEN ((sizeof TEMPLATE) - 1)
1974 const char *tmpdir = NULL;
1977 if ((tmpdir = getenv ("TMP")) == NULL)
1978 if ((tmpdir = getenv ("TEMP")) == NULL)
1979 tmpdir = getenv ("TMPDIR");
1983 static int warning_emitted;
1988 if (!warning_emitted)
1990 fprintf (stderr, "TMP not defined in environment, using %s for temporary files\n.", tmpdir);
1991 warning_emitted = 1;
1997 /* try with /usr/tmp and /tmp on Un*x systems */
1998 struct stat statbuf;
2000 if (tmpdir == NULL) {
2001 if (stat("/usr/tmp", &statbuf) != -1)
2002 tmpdir = "/usr/tmp";
2003 else if (stat("/tmp", &statbuf) != -1)
2011 char fnamebuf[PATH_MAX];
2014 if (fname == NULL || len == 0) {
2016 len = sizeof fnamebuf;
2020 name_len = strlen(tmpdir) + 1 + TEMPLATE_LEN;
2022 assert(name_len < len);
2023 if (!(name_len < len)) /* in NDEBUG is defined */
2024 return -1; /* buffer too small, temporary file can not be created */
2026 sprintf(fname, "%s" DIR_SEPARATOR_STRING TEMPLATE, tmpdir);
2029 name_len = TEMPLATE_LEN;
2031 assert(name_len < len);
2032 if (!(name_len < len)) /* in NDEBUG is defined */
2033 return -1; /* buffer too small, temporary file can not be created */
2035 strcpy(fname, TEMPLATE);
2038 fd = mkstemp(fname);
2042 char *name = tempnam(tmpdir, "sdcc");
2045 perror("Can't create temporary file name");
2049 assert(strlen(name) < len);
2050 if (!(strlen(name) < len)) /* in NDEBUG is defined */
2051 return -1; /* buffer too small, temporary file can not be created */
2053 strcpy(fname, name);
2055 fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IREAD | S_IWRITE);
2057 fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IRUSR | S_IWUSR);
2063 perror("Can't create temporary file");
2071 /** Create a temporary file name
2077 static char fnamebuf[PATH_MAX];
2079 if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
2080 fprintf(stderr, "Can't create temporary file name!");
2091 /** Create a temporary file and add it to tmpfileNameSet,
2092 so that it is removed explicitly by rm_tmpfiles()
2093 or implicitly at program extit.
2101 char fnamebuf[PATH_MAX];
2103 if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
2104 fprintf(stderr, "Can't create temporary file!");
2108 tmp = Safe_strdup(fnamebuf);
2110 addSetHead(&tmpfileNameSet, tmp);
2112 if ((fp = fdopen(fd, "w+b")) == NULL) {
2113 perror("Can't create temporary file!");