undid my latest fix for bug #436344
[fw/sdcc] / src / SDCCglue.c
1 /*-------------------------------------------------------------------------
2
3   SDCCglue.c - glues everything we have done together into one file.
4                 Written By -  Sandeep Dutta . sandeep.dutta@usa.net (1998)
5
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
9    later version.
10
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.
15
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.
19
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 -------------------------------------------------------------------------*/
24
25 #include "common.h"
26 #include "asm.h"
27 #include <time.h>
28 #include "newalloc.h"
29
30 #if !defined(__BORLANDC__) && !defined(_MSC_VER)
31 #include <unistd.h>
32 #endif
33
34 symbol *interrupts[256];
35
36 void printIval (symbol *, sym_link *, initList *, FILE *);
37 set *publics = NULL;            /* public variables */
38 set *externs = NULL;            /* Varibles that are declared as extern */
39
40 /* TODO: this should be configurable (DS803C90 uses more than 6) */
41 unsigned maxInterrupts = 6;
42 int allocInfo = 1;
43 symbol *mainf;
44 extern char *VersionString;
45 set *tmpfileSet = NULL;         /* set of tmp file created by the compiler */
46 set *tmpfileNameSet = NULL;     /* All are unlinked at close. */
47
48 /*-----------------------------------------------------------------*/
49 /* closeTmpFiles - closes all tmp files created by the compiler    */
50 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
51 /*-----------------------------------------------------------------*/
52 DEFSETFUNC (closeTmpFiles)
53 {
54   FILE *tfile = item;
55
56   if (tfile)
57     fclose (tfile);
58
59   return 0;
60 }
61
62 /*-----------------------------------------------------------------*/
63 /* rmTmpFiles - closes all tmp files created by the compiler    */
64 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
65 /*-----------------------------------------------------------------*/
66 DEFSETFUNC (rmTmpFiles)
67 {
68   char *name = item;
69
70   if (name)
71     {
72       unlink (name);
73       free (name);
74     }
75   return 0;
76 }
77
78 /*-----------------------------------------------------------------*/
79 /* copyFile - copies source file to destination file               */
80 /*-----------------------------------------------------------------*/
81 void 
82 copyFile (FILE * dest, FILE * src)
83 {
84   int ch;
85
86   rewind (src);
87   while (!feof (src))
88     if ((ch = fgetc (src)) != EOF)
89       fputc (ch, dest);
90 }
91
92 char *
93 aopLiteralLong (value * val, int offset, int size)
94 {
95         char *rs;
96         union {
97                 float f;
98                 unsigned char c[4];
99         }
100         fl;
101
102         /* if it is a float then it gets tricky */
103         /* otherwise it is fairly simple */
104         if (!IS_FLOAT (val->type)) {
105                 unsigned long v = (unsigned long) floatFromVal (val);
106
107                 v >>= (offset * 8);
108                 switch (size) {
109                 case 1:
110                         tsprintf (buffer, "!immedbyte", (unsigned int) v & 0xff);
111                         break;
112                 case 2:
113                         tsprintf (buffer, "!immedword", (unsigned int) v & 0xffff);
114                         break;
115                 default:
116                         /* Hmm.  Too big for now. */
117                         assert (0);
118                 }
119                 rs = Safe_calloc (1, strlen (buffer) + 1);
120                 return strcpy (rs, buffer);
121         }
122
123         /* PENDING: For now size must be 1 */
124         assert (size == 1);
125
126         /* it is type float */
127         fl.f = (float) floatFromVal (val);
128 #ifdef _BIG_ENDIAN
129         tsprintf (buffer, "!immedbyte", fl.c[3 - offset]);
130 #else
131         tsprintf (buffer, "!immedbyte", fl.c[offset]);
132 #endif
133         rs = Safe_calloc (1, strlen (buffer) + 1);
134         return strcpy (rs, buffer);
135 }
136
137 /*-----------------------------------------------------------------*/
138 /* aopLiteral - string from a literal value                        */
139 /*-----------------------------------------------------------------*/
140 char *
141 aopLiteral (value * val, int offset)
142 {
143         return aopLiteralLong (val, offset, 1);
144 }
145
146 /*-----------------------------------------------------------------*/
147 /* emitRegularMap - emit code for maps with no special cases       */
148 /*-----------------------------------------------------------------*/
149 static void 
150 emitRegularMap (memmap * map, bool addPublics, bool arFlag)
151 {
152   symbol *sym, *symIval;
153   ast *ival = NULL;
154   memmap *segment;
155
156   if (addPublics)
157     {
158       /* PENDING: special case here - should remove */
159       if (!strcmp (map->sname, CODE_NAME))
160         tfprintf (map->oFile, "\t!areacode\n", map->sname);
161       else if (!strcmp (map->sname, DATA_NAME))
162         tfprintf (map->oFile, "\t!areadata\n", map->sname);
163       else if (!strcmp (map->sname, HOME_NAME))
164         tfprintf (map->oFile, "\t!areahome\n", map->sname);
165       else
166         tfprintf (map->oFile, "\t!area\n", map->sname);
167     }
168
169   /* print the area name */
170   for (sym = setFirstItem (map->syms); sym;
171        sym = setNextItem (map->syms))
172     {
173
174       /* if extern then add it into the extern list */
175       if (IS_EXTERN (sym->etype))
176         {
177           addSetHead (&externs, sym);
178           continue;
179         }
180
181       /* if allocation required check is needed
182          then check if the symbol really requires
183          allocation only for local variables */
184       if (arFlag && !IS_AGGREGATE (sym->type) &&
185           !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
186           !sym->allocreq && sym->level)
187         continue;
188
189       /* if global variable & not static or extern
190          and addPublics allowed then add it to the public set */
191       if ((sym->level == 0 ||
192            (sym->_isparm && !IS_REGPARM (sym->etype))) &&
193           addPublics &&
194           !IS_STATIC (sym->etype) &&
195           (IS_FUNC(sym->type) ? (sym->used || sym->fbody) : 1))
196         {
197           addSetHead (&publics, sym);
198         }
199
200       /* if extern then do nothing or is a function
201          then do nothing */
202       if (IS_FUNC (sym->type))
203         continue;
204
205       /* print extra debug info if required */
206       if (options.debug) {
207         cdbSymbol (sym, cdbFile, FALSE, FALSE);
208         if (!sym->level) /* global */
209           if (IS_STATIC (sym->etype))
210             fprintf (map->oFile, "F%s$", moduleName); /* scope is file */
211           else
212             fprintf (map->oFile, "G$"); /* scope is global */
213         else
214           /* symbol is local */
215           fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-"));
216         fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block);
217       }
218       
219       /* if is has an absolute address then generate
220          an equate for this no need to allocate space */
221       if (SPEC_ABSA (sym->etype))
222         {
223           if (options.debug) {
224             fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
225           }
226           fprintf (map->oFile, "%s\t=\t0x%04x\n",
227                    sym->rname,
228                    SPEC_ADDR (sym->etype));
229         }
230       else
231         {
232           /* allocate space */
233           if (options.debug) {
234             fprintf (map->oFile, "==.\n");
235           }
236           if (IS_STATIC (sym->etype))
237             tfprintf (map->oFile, "!slabeldef\n", sym->rname);
238           else
239             tfprintf (map->oFile, "!labeldef\n", sym->rname);
240           tfprintf (map->oFile, "\t!ds\n", 
241                     (unsigned int) getSize (sym->type) & 0xffff);
242         }
243
244       /* if it has an initial value then do it only if
245          it is a global variable */
246       if (sym->ival && sym->level == 0)
247         {
248           if (IS_AGGREGATE (sym->type))
249             ival = initAggregates (sym, sym->ival, NULL);
250           else
251             ival = newNode ('=', newAst_VALUE (symbolVal (sym)),
252                      decorateType (resolveSymbols (list2expr (sym->ival))));
253           codeOutFile = statsg->oFile;
254           allocInfo = 0;
255
256           // set ival's lineno to where the symbol was defined
257           ival->lineno=sym->lineDef;
258
259           eBBlockFromiCode (iCodeFromAst (ival));
260           allocInfo = 1;
261
262           /* if the ival was a symbol, delete it from its segment */
263           if (IS_AST_SYM_VALUE(sym->ival->init.node)) {
264             symIval=AST_SYMBOL(sym->ival->init.node);
265             segment = SPEC_OCLS (symIval->etype);
266             deleteSetItem (&segment->syms, symIval);
267           }
268           sym->ival = NULL;
269         }
270     }
271 }
272
273 /*-----------------------------------------------------------------*/
274 /* initPointer - pointer initialization code massaging             */
275 /*-----------------------------------------------------------------*/
276 value *
277 initPointer (initList * ilist)
278 {
279         value *val;
280         ast *expr = list2expr (ilist);
281         
282         if (!expr)
283                 goto wrong;
284         
285         /* try it the oldway first */
286         if ((val = constExprValue (expr, FALSE)))
287                 return val;
288         
289         /* no then we have to do these cludgy checks */
290         /* pointers can be initialized with address of
291            a variable or address of an array element */
292         if (IS_AST_OP (expr) && expr->opval.op == '&') {
293                 /* address of symbol */
294                 if (IS_AST_SYM_VALUE (expr->left)) {
295                         val = copyValue (AST_VALUE (expr->left));
296                         val->type = newLink ();
297                         if (SPEC_SCLS (expr->left->etype) == S_CODE) {
298                                 DCL_TYPE (val->type) = CPOINTER;
299                                 DCL_PTR_CONST (val->type) = port->mem.code_ro;
300                         }
301                         else if (SPEC_SCLS (expr->left->etype) == S_XDATA)
302                                 DCL_TYPE (val->type) = FPOINTER;
303                         else if (SPEC_SCLS (expr->left->etype) == S_XSTACK)
304                                 DCL_TYPE (val->type) = PPOINTER;
305                         else if (SPEC_SCLS (expr->left->etype) == S_IDATA)
306                                 DCL_TYPE (val->type) = IPOINTER;
307                         else if (SPEC_SCLS (expr->left->etype) == S_EEPROM)
308                                 DCL_TYPE (val->type) = EEPPOINTER;
309                         else
310                                 DCL_TYPE (val->type) = POINTER;
311                         val->type->next = expr->left->ftype;
312                         val->etype = getSpec (val->type);
313                         return val;
314                 }
315
316                 /* if address of indexed array */
317                 if (IS_AST_OP (expr->left) && expr->left->opval.op == '[')
318                         return valForArray (expr->left);
319
320                 /* if address of structure element then
321                    case 1. a.b ; */
322                 if (IS_AST_OP (expr->left) &&
323                     expr->left->opval.op == '.') {
324                         return valForStructElem (expr->left->left,
325                                                  expr->left->right);
326                 }
327
328                 /* case 2. (&a)->b ;
329                    (&some_struct)->element */
330                 if (IS_AST_OP (expr->left) &&
331                     expr->left->opval.op == PTR_OP &&
332                     IS_ADDRESS_OF_OP (expr->left->left))
333                         return valForStructElem (expr->left->left->left,
334                                                  expr->left->right);
335
336         }
337         /* case 3. (((char *) &a) +/- constant) */
338         if (IS_AST_OP (expr) &&
339             (expr->opval.op == '+' || expr->opval.op == '-') &&
340             IS_AST_OP (expr->left) && expr->left->opval.op == CAST &&
341             IS_AST_OP (expr->left->right) &&
342             expr->left->right->opval.op == '&' &&
343             IS_AST_LIT_VALUE (expr->right)) {
344
345                 return valForCastAggr (expr->left->right->left,
346                                        expr->left->left->opval.lnk,
347                                        expr->right, expr->opval.op);
348
349         }
350         
351         /* case 4. (char *)(array type) */
352         if (IS_CAST_OP(expr) && IS_AST_SYM_VALUE (expr->right) &&
353             IS_ARRAY(expr->right->ftype)) {
354
355                 val = copyValue (AST_VALUE (expr->right));
356                 val->type = newLink ();
357                 if (SPEC_SCLS (expr->right->etype) == S_CODE) {
358                         DCL_TYPE (val->type) = CPOINTER;
359                         DCL_PTR_CONST (val->type) = port->mem.code_ro;
360                 }
361                 else if (SPEC_SCLS (expr->right->etype) == S_XDATA)
362                         DCL_TYPE (val->type) = FPOINTER;
363                 else if (SPEC_SCLS (expr->right->etype) == S_XSTACK)
364                         DCL_TYPE (val->type) = PPOINTER;
365                 else if (SPEC_SCLS (expr->right->etype) == S_IDATA)
366                         DCL_TYPE (val->type) = IPOINTER;
367                 else if (SPEC_SCLS (expr->right->etype) == S_EEPROM)
368                         DCL_TYPE (val->type) = EEPPOINTER;
369                 else
370                         DCL_TYPE (val->type) = POINTER;
371                 val->type->next = expr->right->ftype->next;
372                 val->etype = getSpec (val->type);
373                 return val;
374         }
375  wrong:
376         werror (E_INIT_WRONG);
377         return NULL;
378
379 }
380
381 /*-----------------------------------------------------------------*/
382 /* printChar - formats and prints a characater string with DB      */
383 /*-----------------------------------------------------------------*/
384 void 
385 printChar (FILE * ofile, char *s, int plen)
386 {
387   int i;
388   int len = strlen (s);
389   int pplen = 0;
390   char buf[100];
391   char *p = buf;
392
393   while (len && pplen < plen)
394     {
395       i = 60;
396       while (i && *s && pplen < plen)
397         {
398           if (*s < ' ' || *s == '\"' || *s=='\\')
399             {
400               *p = '\0';
401               if (p != buf)
402                 tfprintf (ofile, "\t!ascii\n", buf);
403               tfprintf (ofile, "\t!db !constbyte\n", (unsigned char)*s);
404               p = buf;
405             }
406           else
407             {
408               *p = *s;
409               p++;
410             }
411           s++;
412           pplen++;
413           i--;
414         }
415       if (p != buf)
416         {
417           *p = '\0';
418           tfprintf (ofile, "\t!ascii\n", buf);
419           p = buf;
420         }
421
422       if (len > 60)
423         len -= 60;
424       else
425         len = 0;
426     }
427   tfprintf (ofile, "\t!db !constbyte\n", 0);
428 }
429
430 /*-----------------------------------------------------------------*/
431 /* return the generic pointer high byte for a given pointer type.  */
432 /*-----------------------------------------------------------------*/
433 int 
434 pointerTypeToGPByte (const int p_type, const char *iname, const char *oname)
435 {
436   switch (p_type)
437     {
438     case IPOINTER:
439     case POINTER:
440       return 0;
441     case GPOINTER:
442       /* hack - if we get a generic pointer, we just assume
443        * it's an FPOINTER (i.e. in XDATA space).
444        */
445       werror (E_CANNOT_USE_GENERIC_POINTER, iname, oname);
446       exit (1);
447       // fall through
448     case FPOINTER:
449       return 1;
450     case CPOINTER:
451       return 2;
452     case PPOINTER:
453       return 3;
454     default:
455       fprintf (stderr, "*** internal error: unknown pointer type %d in GPByte.\n",
456                p_type);
457       break;
458     }
459   return -1;
460 }
461
462
463 /*-----------------------------------------------------------------*/
464 /* printPointerType - generates ival for pointer type              */
465 /*-----------------------------------------------------------------*/
466 void 
467 _printPointerType (FILE * oFile, const char *name)
468 {
469   /* if (TARGET_IS_DS390) */
470   if (options.model == MODEL_FLAT24)
471     {
472       fprintf (oFile, "\t.byte %s,(%s >> 8),(%s >> 16)", name, name, name);
473     }
474   else
475     {
476       fprintf (oFile, "\t.byte %s,(%s >> 8)", name, name);
477     }
478 }
479
480 /*-----------------------------------------------------------------*/
481 /* printPointerType - generates ival for pointer type              */
482 /*-----------------------------------------------------------------*/
483 void 
484 printPointerType (FILE * oFile, const char *name)
485 {
486   _printPointerType (oFile, name);
487   fprintf (oFile, "\n");
488 }
489
490 /*-----------------------------------------------------------------*/
491 /* printGPointerType - generates ival for generic pointer type     */
492 /*-----------------------------------------------------------------*/
493 void 
494 printGPointerType (FILE * oFile, const char *iname, const char *oname,
495                    const unsigned int type)
496 {
497   _printPointerType (oFile, iname);
498   fprintf (oFile, ",#0x%02x\n", pointerTypeToGPByte (type, iname, oname));
499 }
500
501 /*-----------------------------------------------------------------*/
502 /* printIvalType - generates ival for int/char                     */
503 /*-----------------------------------------------------------------*/
504 void 
505 printIvalType (sym_link * type, initList * ilist, FILE * oFile)
506 {
507         value *val;
508
509         /* if initList is deep */
510         if (ilist->type == INIT_DEEP)
511                 ilist = ilist->init.deep;
512
513         val = list2val (ilist);
514         switch (getSize (type)) {
515         case 1:
516                 if (!val)
517                         tfprintf (oFile, "\t!db !constbyte\n", 0);
518                 else
519                         tfprintf (oFile, "\t!dbs\n",
520                                   aopLiteral (val, 0));
521                 break;
522
523         case 2:
524                 if (port->use_dw_for_init)
525                         tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
526                 else
527                         fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
528                 break;
529         case 4:
530                 if (!val) {
531                         tfprintf (oFile, "\t!dw !constword\n", 0);
532                         tfprintf (oFile, "\t!dw !constword\n", 0);
533                 }
534                 else {
535                         fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
536                                  aopLiteral (val, 0), aopLiteral (val, 1),
537                                  aopLiteral (val, 2), aopLiteral (val, 3));
538                 }
539                 break;
540         }
541 }
542
543 /*-----------------------------------------------------------------*/
544 /* printIvalBitFields - generate initializer for bitfields         */
545 /*-----------------------------------------------------------------*/
546 void printIvalBitFields(symbol **sym, initList **ilist, FILE * oFile)
547 {
548         value *val ;
549         symbol *lsym = *sym;
550         initList *lilist = *ilist ;
551         unsigned long ival = 0;
552         int size =0;
553
554         
555         do {
556                 unsigned long i;
557                 val = list2val(lilist);
558                 if (size) {
559                         if (SPEC_BLEN(lsym->etype) > 8) {
560                                 size += ((SPEC_BLEN (lsym->etype) / 8) + 
561                                          (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
562                         }
563                 } else {
564                         size = ((SPEC_BLEN (lsym->etype) / 8) + 
565                                  (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
566                 }
567                 i = (unsigned long)floatFromVal(val);
568                 i <<= SPEC_BSTR (lsym->etype);
569                 ival |= i;
570                 if (! ( lsym->next &&
571                         (IS_BITFIELD(lsym->next->type)) &&
572                         (SPEC_BSTR(lsym->next->etype)))) break;
573                 lsym = lsym->next;
574                 lilist = lilist->next;
575         } while (1);
576         switch (size) {
577         case 1:
578                 tfprintf (oFile, "\t!db !constbyte\n",ival);
579                 break;
580
581         case 2:
582                 tfprintf (oFile, "\t!dw !constword\n",ival);
583                 break;
584         case 4:
585                 tfprintf (oFile, "\t!db  !constword,!constword\n",
586                          (ival >> 8) & 0xffff, (ival & 0xffff));
587                 break;
588         }
589         *sym = lsym;
590         *ilist = lilist;
591 }
592
593 /*-----------------------------------------------------------------*/
594 /* printIvalStruct - generates initial value for structures        */
595 /*-----------------------------------------------------------------*/
596 void 
597 printIvalStruct (symbol * sym, sym_link * type,
598                  initList * ilist, FILE * oFile)
599 {
600         symbol *sflds;
601         initList *iloop;
602
603         sflds = SPEC_STRUCT (type)->fields;
604         if (ilist->type != INIT_DEEP) {
605                 werror (E_INIT_STRUCT, sym->name);
606                 return;
607         }
608
609         iloop = ilist->init.deep;
610
611         for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) {
612                 if (IS_BITFIELD(sflds->type)) {
613                         printIvalBitFields(&sflds,&iloop,oFile);
614                 } else {
615                         printIval (sflds, sflds->type, iloop, oFile);
616                 }
617         }
618         return;
619 }
620
621 /*-----------------------------------------------------------------*/
622 /* printIvalChar - generates initital value for character array    */
623 /*-----------------------------------------------------------------*/
624 int 
625 printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s)
626 {
627   value *val;
628   int remain;
629
630   if (!s)
631     {
632
633       val = list2val (ilist);
634       /* if the value is a character string  */
635       if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
636         {
637           if (!DCL_ELEM (type))
638             DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1;
639
640           printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type));
641
642           if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) - 1)) > 0)
643             while (remain--)
644               tfprintf (oFile, "\t!db !constbyte\n", 0);
645
646           return 1;
647         }
648       else
649         return 0;
650     }
651   else
652     printChar (oFile, s, strlen (s) + 1);
653   return 1;
654 }
655
656 /*-----------------------------------------------------------------*/
657 /* printIvalArray - generates code for array initialization        */
658 /*-----------------------------------------------------------------*/
659 void 
660 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
661                 FILE * oFile)
662 {
663   initList *iloop;
664   int lcnt = 0, size = 0;
665
666   /* take care of the special   case  */
667   /* array of characters can be init  */
668   /* by a string                      */
669   if (IS_CHAR (type->next))
670     if (printIvalChar (type,
671                        (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
672                        oFile, SPEC_CVAL (sym->etype).v_char))
673       return;
674
675   /* not the special case             */
676   if (ilist->type != INIT_DEEP)
677     {
678       werror (E_INIT_STRUCT, sym->name);
679       return;
680     }
681
682   iloop = ilist->init.deep;
683   lcnt = DCL_ELEM (type);
684
685   for (;;)
686     {
687       size++;
688       printIval (sym, type->next, iloop, oFile);
689       iloop = (iloop ? iloop->next : NULL);
690
691
692       /* if not array limits given & we */
693       /* are out of initialisers then   */
694       if (!DCL_ELEM (type) && !iloop)
695         break;
696
697       /* no of elements given and we    */
698       /* have generated for all of them */
699       if (!--lcnt) {
700         /* if initializers left */
701         if (iloop) {
702           werror (W_EXESS_ARRAY_INITIALIZERS, sym->name, sym->lineDef);
703         }
704         break;
705       }
706     }
707
708   /* if we have not been given a size  */
709   if (!DCL_ELEM (type))
710     DCL_ELEM (type) = size;
711
712   return;
713 }
714
715 /*-----------------------------------------------------------------*/
716 /* printIvalFuncPtr - generate initial value for function pointers */
717 /*-----------------------------------------------------------------*/
718 void 
719 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
720 {
721   value *val;
722   int dLvl = 0;
723
724   val = list2val (ilist);
725   /* check the types   */
726   if ((dLvl = compareType (val->type, type->next)) <= 0)
727     {
728       tfprintf (oFile, "\t!dw !constword\n", 0);
729       return;
730     }
731
732   /* now generate the name */
733   if (!val->sym)
734     {
735       if (port->use_dw_for_init)
736         {
737           tfprintf (oFile, "\t!dws\n", val->name);
738         }
739       else
740         {
741           printPointerType (oFile, val->name);
742         }
743     }
744   else if (port->use_dw_for_init)
745     {
746       tfprintf (oFile, "\t!dws\n", val->sym->rname);
747     }
748   else
749     {
750       printPointerType (oFile, val->sym->rname);
751     }
752
753   return;
754 }
755
756 /*-----------------------------------------------------------------*/
757 /* printIvalCharPtr - generates initial values for character pointers */
758 /*-----------------------------------------------------------------*/
759 int 
760 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
761 {
762   int size = 0;
763
764   /* PENDING: this is _very_ mcs51 specific, including a magic
765      number...
766      It's also endin specific.
767    */
768   size = getSize (type);
769
770   if (val->name && strlen (val->name))
771     {
772       if (size == 1)            /* This appears to be Z80 specific?? */
773         {
774           tfprintf (oFile,
775                     "\t!dbs\n", val->name);
776         }
777       else if (size == FPTRSIZE)
778         {
779           if (port->use_dw_for_init)
780             {
781               tfprintf (oFile, "\t!dws\n", val->name);
782             }
783           else
784             {
785               printPointerType (oFile, val->name);
786             }
787         }
788       else if (size == GPTRSIZE)
789         {
790           int type;
791           if (IS_PTR (val->type)) {
792             type = DCL_TYPE (val->type);
793           } else {
794             type = PTR_TYPE (SPEC_OCLS (val->etype));
795           }
796           if (val->sym && val->sym->isstrlit) {
797             // this is a literal string
798             type=CPOINTER;
799           }
800           printGPointerType (oFile, val->name, sym->name, type);
801         }
802       else
803         {
804           fprintf (stderr, "*** internal error: unknown size in "
805                    "printIvalCharPtr.\n");
806         }
807     }
808   else
809     {
810       /* What is this case? Are these pointers? */
811       switch (size)
812         {
813         case 1:
814           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
815           break;
816         case 2:
817           if (port->use_dw_for_init)
818             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
819           else
820             tfprintf (oFile, "\t.byte %s,%s\n",
821                       aopLiteral (val, 0), aopLiteral (val, 1));
822           break;
823         case 3:
824           /* PENDING: 0x02 or 0x%02x, CDATA? */
825           fprintf (oFile, "\t.byte %s,%s,#0x02\n",
826                    aopLiteral (val, 0), aopLiteral (val, 1));
827           break;
828         default:
829           assert (0);
830         }
831     }
832
833   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
834     addSet (&statsg->syms, val->sym);
835   }
836
837   return 1;
838 }
839
840 /*-----------------------------------------------------------------*/
841 /* printIvalPtr - generates initial value for pointers             */
842 /*-----------------------------------------------------------------*/
843 void 
844 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
845 {
846   value *val;
847   int size;
848
849   /* if deep then   */
850   if (ilist->type == INIT_DEEP)
851     ilist = ilist->init.deep;
852
853   /* function pointer     */
854   if (IS_FUNC (type->next))
855     {
856       printIvalFuncPtr (type, ilist, oFile);
857       return;
858     }
859
860   if (!(val = initPointer (ilist)))
861     return;
862
863   /* if character pointer */
864   if (IS_CHAR (type->next))
865     if (printIvalCharPtr (sym, type, val, oFile))
866       return;
867
868   /* check the type      */
869   if (compareType (type, val->type) == 0)
870     werror (E_INIT_WRONG);
871
872   /* if val is literal */
873   if (IS_LITERAL (val->etype))
874     {
875       switch (getSize (type))
876         {
877         case 1:
878           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
879           break;
880         case 2:
881           if (port->use_dw_for_init)
882             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
883           else
884             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
885           break;
886         case 3:
887           fprintf (oFile, "\t.byte %s,%s,#0x02\n",
888                    aopLiteral (val, 0), aopLiteral (val, 1));
889         }
890       return;
891     }
892
893
894   size = getSize (type);
895
896   if (size == 1)                /* Z80 specific?? */
897     {
898       tfprintf (oFile, "\t!dbs\n", val->name);
899     }
900   else if (size == FPTRSIZE)
901     {
902       if (port->use_dw_for_init) {
903         tfprintf (oFile, "\t!dws\n", val->name);
904       } else {
905         printPointerType (oFile, val->name);
906       }
907     }
908   else if (size == GPTRSIZE)
909     {
910       printGPointerType (oFile, val->name, sym->name,
911                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
912                           PTR_TYPE (SPEC_OCLS (val->etype))));
913     }
914   return;
915 }
916
917 /*-----------------------------------------------------------------*/
918 /* printIval - generates code for initial value                    */
919 /*-----------------------------------------------------------------*/
920 void 
921 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
922 {
923   if (!ilist)
924     return;
925
926   /* if structure then    */
927   if (IS_STRUCT (type))
928     {
929       printIvalStruct (sym, type, ilist, oFile);
930       return;
931     }
932
933   /* if this is a pointer */
934   if (IS_PTR (type))
935     {
936       printIvalPtr (sym, type, ilist, oFile);
937       return;
938     }
939
940   /* if this is an array   */
941   if (IS_ARRAY (type))
942     {
943       printIvalArray (sym, type, ilist, oFile);
944       return;
945     }
946
947   /* if type is SPECIFIER */
948   if (IS_SPEC (type))
949     {
950       printIvalType (type, ilist, oFile);
951       return;
952     }
953 }
954
955 /*-----------------------------------------------------------------*/
956 /* emitStaticSeg - emitcode for the static segment                 */
957 /*-----------------------------------------------------------------*/
958 void 
959 emitStaticSeg (memmap * map, FILE * out)
960 {
961   symbol *sym;
962
963   /*     fprintf(map->oFile,"\t.area\t%s\n",map->sname); */
964   if (!out)
965     out = code->oFile;
966
967   /* for all variables in this segment do */
968   for (sym = setFirstItem (map->syms); sym;
969        sym = setNextItem (map->syms))
970     {
971
972       /* if it is "extern" then do nothing */
973       if (IS_EXTERN (sym->etype))
974         continue;
975
976       /* if it is not static add it to the public
977          table */
978       if (!IS_STATIC (sym->etype))
979         addSetHead (&publics, sym);
980
981       /* print extra debug info if required */
982       if (options.debug) {
983         cdbSymbol (sym, cdbFile, FALSE, FALSE);
984         if (!sym->level)
985           {                     /* global */
986             if (IS_STATIC (sym->etype))
987               fprintf (out, "F%s$", moduleName);        /* scope is file */
988             else
989               fprintf (out, "G$");      /* scope is global */
990           }
991         else
992           /* symbol is local */
993           fprintf (out, "L%s$",
994                    (sym->localof ? sym->localof->name : "-null-"));
995         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
996       }
997       
998       /* if it has an absolute address */
999       if (SPEC_ABSA (sym->etype))
1000         {
1001           if (options.debug)
1002             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1003           
1004           fprintf (out, "%s\t=\t0x%04x\n",
1005                    sym->rname,
1006                    SPEC_ADDR (sym->etype));
1007         }
1008       else
1009         {
1010           if (options.debug)
1011             fprintf (out, " == .\n");
1012           
1013           /* if it has an initial value */
1014           if (sym->ival)
1015             {
1016               fprintf (out, "%s:\n", sym->rname);
1017               noAlloc++;
1018               resolveIvalSym (sym->ival);
1019               printIval (sym, sym->type, sym->ival, out);
1020               noAlloc--;
1021             }
1022           else
1023             {
1024               /* allocate space */
1025               fprintf (out, "%s:\n", sym->rname);
1026               /* special case for character strings */
1027               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1028                   SPEC_CVAL (sym->etype).v_char)
1029                 printChar (out,
1030                            SPEC_CVAL (sym->etype).v_char,
1031                            strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1032               else
1033                 tfprintf (out, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1034             }
1035         }
1036     }
1037 }
1038
1039 /*-----------------------------------------------------------------*/
1040 /* emitMaps - emits the code for the data portion the code         */
1041 /*-----------------------------------------------------------------*/
1042 void 
1043 emitMaps ()
1044 {
1045   inInitMode++;
1046   /* no special considerations for the following
1047      data, idata & bit & xdata */
1048   emitRegularMap (data, TRUE, TRUE);
1049   emitRegularMap (idata, TRUE, TRUE);
1050   emitRegularMap (bit, TRUE, FALSE);
1051   emitRegularMap (xdata, TRUE, TRUE);
1052   emitRegularMap (sfr, FALSE, FALSE);
1053   emitRegularMap (sfrbit, FALSE, FALSE);
1054   emitRegularMap (home, TRUE, FALSE);
1055   emitRegularMap (code, TRUE, FALSE);
1056
1057   emitStaticSeg (statsg, code->oFile);
1058   inInitMode--;
1059 }
1060
1061 /*-----------------------------------------------------------------*/
1062 /* flushStatics - flush all currently defined statics out to file  */
1063 /*  and delete.  Temporary function                                */
1064 /*-----------------------------------------------------------------*/
1065 void 
1066 flushStatics (void)
1067 {
1068   emitStaticSeg (statsg, codeOutFile);
1069   statsg->syms = NULL;
1070 }
1071
1072 /*-----------------------------------------------------------------*/
1073 /* createInterruptVect - creates the interrupt vector              */
1074 /*-----------------------------------------------------------------*/
1075 void 
1076 createInterruptVect (FILE * vFile)
1077 {
1078   unsigned i = 0;
1079   mainf = newSymbol ("main", 0);
1080   mainf->block = 0;
1081
1082   /* only if the main function exists */
1083   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1084     {
1085       if (!options.cc_only && !noAssemble)
1086         werror (E_NO_MAIN);
1087       return;
1088     }
1089
1090   /* if the main is only a prototype ie. no body then do nothing */
1091   if (!mainf->fbody)
1092     {
1093       /* if ! compile only then main function should be present */
1094       if (!options.cc_only && !noAssemble)
1095         werror (E_NO_MAIN);
1096       return;
1097     }
1098
1099   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1100   fprintf (vFile, "__interrupt_vect:\n");
1101
1102
1103   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1104     {
1105       /* "generic" interrupt table header (if port doesn't specify one).
1106
1107        * Look suspiciously like 8051 code to me...
1108        */
1109
1110       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1111
1112
1113       /* now for the other interrupts */
1114       for (; i < maxInterrupts; i++)
1115         {
1116           if (interrupts[i])
1117             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1118           else
1119             fprintf (vFile, "\treti\n\t.ds\t7\n");
1120         }
1121     }
1122 }
1123
1124 char *iComments1 =
1125 {
1126   ";--------------------------------------------------------\n"
1127   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1128
1129 char *iComments2 =
1130 {
1131   ";--------------------------------------------------------\n"};
1132
1133
1134 /*-----------------------------------------------------------------*/
1135 /* initialComments - puts in some initial comments                 */
1136 /*-----------------------------------------------------------------*/
1137 void 
1138 initialComments (FILE * afile)
1139 {
1140   time_t t;
1141   time (&t);
1142   fprintf (afile, "%s", iComments1);
1143   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1144   fprintf (afile, "%s", iComments2);
1145 }
1146
1147 /*-----------------------------------------------------------------*/
1148 /* printPublics - generates .global for publics                    */
1149 /*-----------------------------------------------------------------*/
1150 void 
1151 printPublics (FILE * afile)
1152 {
1153   symbol *sym;
1154
1155   fprintf (afile, "%s", iComments2);
1156   fprintf (afile, "; Public variables in this module\n");
1157   fprintf (afile, "%s", iComments2);
1158
1159   for (sym = setFirstItem (publics); sym;
1160        sym = setNextItem (publics))
1161     tfprintf (afile, "\t!global\n", sym->rname);
1162 }
1163
1164 /*-----------------------------------------------------------------*/
1165 /* printExterns - generates .global for externs                    */
1166 /*-----------------------------------------------------------------*/
1167 void 
1168 printExterns (FILE * afile)
1169 {
1170   symbol *sym;
1171
1172   fprintf (afile, "%s", iComments2);
1173   fprintf (afile, "; Externals used\n");
1174   fprintf (afile, "%s", iComments2);
1175
1176   for (sym = setFirstItem (externs); sym;
1177        sym = setNextItem (externs))
1178     tfprintf (afile, "\t!global\n", sym->rname);
1179 }
1180
1181 /*-----------------------------------------------------------------*/
1182 /* emitOverlay - will emit code for the overlay stuff              */
1183 /*-----------------------------------------------------------------*/
1184 static void 
1185 emitOverlay (FILE * afile)
1186 {
1187   set *ovrset;
1188
1189   if (!elementsInSet (ovrSetSets))
1190     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1191
1192   /* for each of the sets in the overlay segment do */
1193   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1194        ovrset = setNextItem (ovrSetSets))
1195     {
1196
1197       symbol *sym;
1198
1199       if (elementsInSet (ovrset))
1200         {
1201           /* this dummy area is used to fool the assembler
1202              otherwise the assembler will append each of these
1203              declarations into one chunk and will not overlay
1204              sad but true */
1205           fprintf (afile, "\t.area _DUMMY\n");
1206           /* output the area informtion */
1207           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1208         }
1209
1210       for (sym = setFirstItem (ovrset); sym;
1211            sym = setNextItem (ovrset))
1212         {
1213
1214           /* if extern then add it to the publics tabledo nothing */
1215           if (IS_EXTERN (sym->etype))
1216             continue;
1217
1218           /* if allocation required check is needed
1219              then check if the symbol really requires
1220              allocation only for local variables */
1221           if (!IS_AGGREGATE (sym->type) &&
1222               !(sym->_isparm && !IS_REGPARM (sym->etype))
1223               && !sym->allocreq && sym->level)
1224             continue;
1225
1226           /* if global variable & not static or extern
1227              and addPublics allowed then add it to the public set */
1228           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1229               && !IS_STATIC (sym->etype))
1230             addSetHead (&publics, sym);
1231
1232           /* if extern then do nothing or is a function
1233              then do nothing */
1234           if (IS_FUNC (sym->type))
1235             continue;
1236
1237           /* print extra debug info if required */
1238           if (options.debug)
1239             {
1240               cdbSymbol (sym, cdbFile, FALSE, FALSE);
1241
1242               if (!sym->level)
1243                 {               /* global */
1244                   if (IS_STATIC (sym->etype))
1245                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1246                   else
1247                     fprintf (afile, "G$");      /* scope is global */
1248                 }
1249               else
1250                 /* symbol is local */
1251                 fprintf (afile, "L%s$",
1252                          (sym->localof ? sym->localof->name : "-null-"));
1253               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1254             }
1255
1256           /* if is has an absolute address then generate
1257              an equate for this no need to allocate space */
1258           if (SPEC_ABSA (sym->etype))
1259             {
1260
1261               if (options.debug)
1262                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1263
1264               fprintf (afile, "%s\t=\t0x%04x\n",
1265                        sym->rname,
1266                        SPEC_ADDR (sym->etype));
1267             }
1268           else
1269             {
1270               if (options.debug)
1271                 fprintf (afile, "==.\n");
1272               
1273               /* allocate space */
1274               tfprintf (afile, "!labeldef\n", sym->rname);
1275               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1276             }
1277
1278         }
1279     }
1280 }
1281
1282 /*-----------------------------------------------------------------*/
1283 /* glue - the final glue that hold the whole thing together        */
1284 /*-----------------------------------------------------------------*/
1285 void 
1286 glue ()
1287 {
1288   FILE *vFile;
1289   FILE *asmFile;
1290   FILE *ovrFile = tempfile ();
1291
1292   addSetHead (&tmpfileSet, ovrFile);
1293   /* print the global struct definitions */
1294   if (options.debug)
1295     cdbStructBlock (0, cdbFile);
1296
1297   vFile = tempfile ();
1298   /* PENDING: this isnt the best place but it will do */
1299   if (port->general.glue_up_main)
1300     {
1301       /* create the interrupt vector table */
1302       createInterruptVect (vFile);
1303     }
1304
1305   addSetHead (&tmpfileSet, vFile);
1306
1307   /* emit code for the all the variables declared */
1308   emitMaps ();
1309   /* do the overlay segments */
1310   emitOverlay (ovrFile);
1311
1312   /* now put it all together into the assembler file */
1313   /* create the assembler file name */
1314
1315   if (!options.c1mode)
1316     {
1317       sprintf (scratchFileName, srcFileName);
1318       strcat (scratchFileName, port->assembler.file_ext);
1319     }
1320   else
1321     {
1322       strcpy (scratchFileName, options.out_name);
1323     }
1324
1325   if (!(asmFile = fopen (scratchFileName, "w")))
1326     {
1327       werror (E_FILE_OPEN_ERR, scratchFileName);
1328       exit (1);
1329     }
1330
1331   /* initial comments */
1332   initialComments (asmFile);
1333
1334   /* print module name */
1335   tfprintf (asmFile, "\t!module\n", moduleName);
1336   tfprintf (asmFile, "\t!fileprelude\n");
1337
1338   /* Let the port generate any global directives, etc. */
1339   if (port->genAssemblerPreamble)
1340     {
1341       port->genAssemblerPreamble (asmFile);
1342     }
1343
1344   /* print the global variables in this module */
1345   printPublics (asmFile);
1346   if (port->assembler.externGlobal)
1347     printExterns (asmFile);
1348
1349   /* copy the sfr segment */
1350   fprintf (asmFile, "%s", iComments2);
1351   fprintf (asmFile, "; special function registers\n");
1352   fprintf (asmFile, "%s", iComments2);
1353   copyFile (asmFile, sfr->oFile);
1354
1355   /* copy the sbit segment */
1356   fprintf (asmFile, "%s", iComments2);
1357   fprintf (asmFile, "; special function bits \n");
1358   fprintf (asmFile, "%s", iComments2);
1359   copyFile (asmFile, sfrbit->oFile);
1360
1361   /* copy the data segment */
1362   fprintf (asmFile, "%s", iComments2);
1363   fprintf (asmFile, "; internal ram data\n");
1364   fprintf (asmFile, "%s", iComments2);
1365   copyFile (asmFile, data->oFile);
1366
1367
1368   /* create the overlay segments */
1369   fprintf (asmFile, "%s", iComments2);
1370   fprintf (asmFile, "; overlayable items in internal ram \n");
1371   fprintf (asmFile, "%s", iComments2);
1372   copyFile (asmFile, ovrFile);
1373
1374   /* create the stack segment MOF */
1375   if (mainf && mainf->fbody)
1376     {
1377       fprintf (asmFile, "%s", iComments2);
1378       fprintf (asmFile, "; Stack segment in internal ram \n");
1379       fprintf (asmFile, "%s", iComments2);
1380       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1381                "__start__stack:\n\t.ds\t1\n\n");
1382     }
1383
1384   /* create the idata segment */
1385   fprintf (asmFile, "%s", iComments2);
1386   fprintf (asmFile, "; indirectly addressable internal ram data\n");
1387   fprintf (asmFile, "%s", iComments2);
1388   copyFile (asmFile, idata->oFile);
1389
1390   /* copy the bit segment */
1391   fprintf (asmFile, "%s", iComments2);
1392   fprintf (asmFile, "; bit data\n");
1393   fprintf (asmFile, "%s", iComments2);
1394   copyFile (asmFile, bit->oFile);
1395
1396   /* if external stack then reserve space of it */
1397   if (mainf && mainf->fbody && options.useXstack)
1398     {
1399       fprintf (asmFile, "%s", iComments2);
1400       fprintf (asmFile, "; external stack \n");
1401       fprintf (asmFile, "%s", iComments2);
1402       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1403       fprintf (asmFile, "\t.ds 256\n");
1404     }
1405
1406
1407   /* copy xtern ram data */
1408   fprintf (asmFile, "%s", iComments2);
1409   fprintf (asmFile, "; external ram data\n");
1410   fprintf (asmFile, "%s", iComments2);
1411   copyFile (asmFile, xdata->oFile);
1412
1413   /* copy the interrupt vector table */
1414   if (mainf && mainf->fbody)
1415     {
1416       fprintf (asmFile, "%s", iComments2);
1417       fprintf (asmFile, "; interrupt vector \n");
1418       fprintf (asmFile, "%s", iComments2);
1419       copyFile (asmFile, vFile);
1420     }
1421
1422   /* copy global & static initialisations */
1423   fprintf (asmFile, "%s", iComments2);
1424   fprintf (asmFile, "; global & static initialisations\n");
1425   fprintf (asmFile, "%s", iComments2);
1426
1427   /* Everywhere we generate a reference to the static_name area,
1428    * (which is currently only here), we immediately follow it with a
1429    * definition of the post_static_name area. This guarantees that
1430    * the post_static_name area will immediately follow the static_name
1431    * area.
1432    */
1433   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1434   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1435   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1436
1437   if (mainf && mainf->fbody)
1438     {
1439       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1440       /* if external stack is specified then the
1441          higher order byte of the xdatalocation is
1442          going into P2 and the lower order going into
1443          spx */
1444       if (options.useXstack)
1445         {
1446           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1447                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1448           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1449                    (unsigned int) options.xdata_loc & 0xff);
1450         }
1451
1452       /* initialise the stack pointer */
1453       /* if the user specified a value then use it */
1454       if (options.stack_loc)
1455         fprintf (asmFile, "\tmov\tsp,#%d\n", options.stack_loc);
1456       else
1457         /* no: we have to compute it */
1458       if (!options.stackOnData && maxRegBank <= 3)
1459         fprintf (asmFile, "\tmov\tsp,#%d\n", ((maxRegBank + 1) * 8) - 1);
1460       else
1461         fprintf (asmFile, "\tmov\tsp,#__start__stack\n");       /* MOF */
1462
1463       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1464       fprintf (asmFile, "\tmov\ta,dpl\n");
1465       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1466       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1467       fprintf (asmFile, "__sdcc_init_data:\n");
1468
1469     }
1470   copyFile (asmFile, statsg->oFile);
1471
1472   if (port->general.glue_up_main && mainf && mainf->fbody)
1473     {
1474       /* This code is generated in the post-static area.
1475        * This area is guaranteed to follow the static area
1476        * by the ugly shucking and jiving about 20 lines ago.
1477        */
1478       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1479       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1480     }
1481
1482   fprintf (asmFile,
1483            "%s"
1484            "; Home\n"
1485            "%s", iComments2, iComments2);
1486   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1487   copyFile (asmFile, home->oFile);
1488
1489   /* copy over code */
1490   fprintf (asmFile, "%s", iComments2);
1491   fprintf (asmFile, "; code\n");
1492   fprintf (asmFile, "%s", iComments2);
1493   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1494   if (mainf && mainf->fbody)
1495     {
1496
1497       /* entry point @ start of CSEG */
1498       fprintf (asmFile, "__sdcc_program_startup:\n");
1499
1500       /* put in the call to main */
1501       fprintf (asmFile, "\tlcall\t_main\n");
1502       if (options.mainreturn)
1503         {
1504
1505           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1506           fprintf (asmFile, "\tret\n");
1507
1508         }
1509       else
1510         {
1511
1512           fprintf (asmFile, ";\treturn from main will lock up\n");
1513           fprintf (asmFile, "\tsjmp .\n");
1514         }
1515     }
1516   copyFile (asmFile, code->oFile);
1517
1518   fclose (asmFile);
1519   applyToSet (tmpfileSet, closeTmpFiles);
1520   applyToSet (tmpfileNameSet, rmTmpFiles);
1521 }
1522
1523 #if defined (__MINGW32__) || defined (__CYGWIN__) || defined (_MSC_VER)
1524 void
1525 rm_tmpfiles (void)
1526 {
1527   applyToSet (tmpfileSet, closeTmpFiles);
1528   applyToSet (tmpfileNameSet, rmTmpFiles);
1529 }
1530 #endif
1531
1532 /** Creates a temporary file a'la tmpfile which avoids the bugs
1533     in cygwin wrt c:\tmp.
1534     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1535 */
1536 FILE *
1537 tempfile (void)
1538 {
1539 #if !defined(_MSC_VER)
1540   const char *tmpdir = NULL;
1541   if (getenv ("TMP"))
1542     tmpdir = getenv ("TMP");
1543   else if (getenv ("TEMP"))
1544     tmpdir = getenv ("TEMP");
1545   else if (getenv ("TMPDIR"))
1546     tmpdir = getenv ("TMPDIR");
1547   if (tmpdir)
1548     {
1549       char *name = tempnam (tmpdir, "sdcc");
1550       if (name)
1551         {
1552           FILE *fp = fopen (name, "w+b");
1553           if (fp)
1554             {
1555               addSetHead (&tmpfileNameSet, name);
1556             }
1557           return fp;
1558         }
1559       return NULL;
1560     }
1561 #endif
1562   return tmpfile ();
1563 }
1564
1565 char *
1566 gc_strdup (const char *s)
1567 {
1568   char *ret;
1569   ret = Safe_calloc (1, strlen (s) + 1);
1570   strcpy (ret, s);
1571   return ret;
1572 }