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