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