a fix for the initialized structs and some others, see
[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 #if 0                           /* This should no longer be necessary. */
32 // This is a bit messy because we define link ourself
33 #define link NoLiNk
34 #include <unistd.h>
35 #undef link
36 #else
37
38 #include <unistd.h>
39 #endif
40 #else
41 // No unistd.h in Borland C++
42 #endif
43
44 symbol *interrupts[256];
45
46 void printIval (symbol *, sym_link *, initList *, FILE *);
47 set *publics = NULL;            /* public variables */
48 set *externs = NULL;            /* Varibles that are declared as extern */
49
50 /* TODO: this should be configurable (DS803C90 uses more than 6) */
51 unsigned maxInterrupts = 6;
52 int allocInfo = 1;
53 symbol *mainf;
54 extern char *VersionString;
55 set *tmpfileSet = NULL;         /* set of tmp file created by the compiler */
56 set *tmpfileNameSet = NULL;     /* All are unlinked at close. */
57
58 /*-----------------------------------------------------------------*/
59 /* closeTmpFiles - closes all tmp files created by the compiler    */
60 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
61 /*-----------------------------------------------------------------*/
62 DEFSETFUNC (closeTmpFiles)
63 {
64   FILE *tfile = item;
65
66   if (tfile)
67     fclose (tfile);
68
69   return 0;
70 }
71
72 /*-----------------------------------------------------------------*/
73 /* rmTmpFiles - closes all tmp files created by the compiler    */
74 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
75 /*-----------------------------------------------------------------*/
76 DEFSETFUNC (rmTmpFiles)
77 {
78   char *name = item;
79
80   if (name)
81     {
82       unlink (name);
83       free (name);
84     }
85   return 0;
86 }
87
88 /*-----------------------------------------------------------------*/
89 /* copyFile - copies source file to destination file               */
90 /*-----------------------------------------------------------------*/
91 void 
92 copyFile (FILE * dest, FILE * src)
93 {
94   int ch;
95
96   rewind (src);
97   while (!feof (src))
98     if ((ch = fgetc (src)) != EOF)
99       fputc (ch, dest);
100 }
101
102 char *
103 aopLiteralLong (value * val, int offset, int size)
104 {
105         char *rs;
106         union {
107                 float f;
108                 unsigned char c[4];
109         }
110         fl;
111
112         /* if it is a float then it gets tricky */
113         /* otherwise it is fairly simple */
114         if (!IS_FLOAT (val->type)) {
115                 unsigned long v = (unsigned long) floatFromVal (val);
116
117                 v >>= (offset * 8);
118                 switch (size) {
119                 case 1:
120                         tsprintf (buffer, "!immedbyte", (unsigned int) v & 0xff);
121                         break;
122                 case 2:
123                         tsprintf (buffer, "!immedword", (unsigned int) v & 0xffff);
124                         break;
125                 default:
126                         /* Hmm.  Too big for now. */
127                         assert (0);
128                 }
129                 rs = Safe_calloc (1, strlen (buffer) + 1);
130                 return strcpy (rs, buffer);
131         }
132
133         /* PENDING: For now size must be 1 */
134         assert (size == 1);
135
136         /* it is type float */
137         fl.f = (float) floatFromVal (val);
138 #ifdef _BIG_ENDIAN
139         tsprintf (buffer, "!immedbyte", fl.c[3 - offset]);
140 #else
141         tsprintf (buffer, "!immedbyte", fl.c[offset]);
142 #endif
143         rs = Safe_calloc (1, strlen (buffer) + 1);
144         return strcpy (rs, buffer);
145 }
146
147 /*-----------------------------------------------------------------*/
148 /* aopLiteral - string from a literal value                        */
149 /*-----------------------------------------------------------------*/
150 char *
151 aopLiteral (value * val, int offset)
152 {
153         return aopLiteralLong (val, offset, 1);
154 }
155
156 /*-----------------------------------------------------------------*/
157 /* emitRegularMap - emit code for maps with no special cases       */
158 /*-----------------------------------------------------------------*/
159 static void 
160 emitRegularMap (memmap * map, bool addPublics, bool arFlag)
161 {
162   symbol *sym;
163   ast *ival = NULL;
164
165   if (addPublics)
166     {
167       /* PENDING: special case here - should remove */
168       if (!strcmp (map->sname, CODE_NAME))
169         tfprintf (map->oFile, "\t!areacode\n", map->sname);
170       else if (!strcmp (map->sname, DATA_NAME))
171         tfprintf (map->oFile, "\t!areadata\n", map->sname);
172       else if (!strcmp (map->sname, HOME_NAME))
173         tfprintf (map->oFile, "\t!areahome\n", map->sname);
174       else
175         tfprintf (map->oFile, "\t!area\n", map->sname);
176     }
177
178   /* print the area name */
179   for (sym = setFirstItem (map->syms); sym;
180        sym = setNextItem (map->syms))
181     {
182
183       /* if extern then add it into the extern list */
184       if (IS_EXTERN (sym->etype))
185         {
186           addSetHead (&externs, sym);
187           continue;
188         }
189
190       /* if allocation required check is needed
191          then check if the symbol really requires
192          allocation only for local variables */
193       if (arFlag && !IS_AGGREGATE (sym->type) &&
194           !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
195           !sym->allocreq && sym->level)
196         continue;
197
198       /* if global variable & not static or extern
199          and addPublics allowed then add it to the public set */
200       if ((sym->level == 0 ||
201            (sym->_isparm && !IS_REGPARM (sym->etype))) &&
202           addPublics &&
203           !IS_STATIC (sym->etype) &&
204           (sym->used || sym->fbody))
205         {
206           addSetHead (&publics, sym);
207         }
208
209       /* if extern then do nothing or is a function
210          then do nothing */
211       if (IS_FUNC (sym->type))
212         continue;
213
214       /* print extra debug info if required */
215       if ((options.debug || sym->level == 0) && !options.nodebug)
216         {
217
218           cdbSymbol (sym, cdbFile, FALSE, FALSE);
219
220           if (!sym->level)      /* global */
221             if (IS_STATIC (sym->etype))
222               fprintf (map->oFile, "F%s$", moduleName);         /* scope is file */
223             else
224               fprintf (map->oFile, "G$");       /* scope is global */
225           else
226             /* symbol is local */
227             fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-"));
228           fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block);
229         }
230
231       /* if is has an absolute address then generate
232          an equate for this no need to allocate space */
233       if (SPEC_ABSA (sym->etype))
234         {
235           if ((options.debug || sym->level == 0) && !options.nodebug)
236             fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
237
238           fprintf (map->oFile, "%s\t=\t0x%04x\n",
239                    sym->rname,
240                    SPEC_ADDR (sym->etype));
241         }
242       else
243         {
244           /* allocate space */
245           if ((options.debug || sym->level == 0) && !options.nodebug)
246             fprintf (map->oFile, "==.\n");
247           if (IS_STATIC (sym->etype))
248             tfprintf (map->oFile, "!slabeldef\n", sym->rname);
249           else
250             tfprintf (map->oFile, "!labeldef\n", sym->rname);
251           tfprintf (map->oFile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
252         }
253
254       /* if it has an initial value then do it only if
255          it is a global variable */
256       if (sym->ival && sym->level == 0)
257         {
258
259           if (IS_AGGREGATE (sym->type))
260             ival = initAggregates (sym, sym->ival, NULL);
261           else
262             ival = newNode ('=', newAst_VALUE (symbolVal (sym)),
263                      decorateType (resolveSymbols (list2expr (sym->ival))));
264           codeOutFile = statsg->oFile;
265           allocInfo = 0;
266
267           // set ival's lineno to where the symbol was defined
268           ival->lineno=sym->lineDef;
269
270           eBBlockFromiCode (iCodeFromAst (ival));
271           allocInfo = 1;
272           sym->ival = NULL;
273         }
274     }
275 }
276
277 /*-----------------------------------------------------------------*/
278 /* initPointer - pointer initialization code massaging             */
279 /*-----------------------------------------------------------------*/
280 value *
281 initPointer (initList * ilist)
282 {
283         value *val;
284         ast *expr = list2expr (ilist);
285         
286         if (!expr)
287                 goto wrong;
288         
289         /* try it the oldway first */
290         if ((val = constExprValue (expr, FALSE)))
291                 return val;
292         
293         /* no then we have to do these cludgy checks */
294         /* pointers can be initialized with address of
295            a variable or address of an array element */
296         if (IS_AST_OP (expr) && expr->opval.op == '&') {
297                 /* address of symbol */
298                 if (IS_AST_SYM_VALUE (expr->left)) {
299                         val = copyValue (AST_VALUE (expr->left));
300                         val->type = newLink ();
301                         if (SPEC_SCLS (expr->left->etype) == S_CODE) {
302                                 DCL_TYPE (val->type) = CPOINTER;
303                                 DCL_PTR_CONST (val->type) = port->mem.code_ro;
304                         }
305                         else if (SPEC_SCLS (expr->left->etype) == S_XDATA)
306                                 DCL_TYPE (val->type) = FPOINTER;
307                         else if (SPEC_SCLS (expr->left->etype) == S_XSTACK)
308                                 DCL_TYPE (val->type) = PPOINTER;
309                         else if (SPEC_SCLS (expr->left->etype) == S_IDATA)
310                                 DCL_TYPE (val->type) = IPOINTER;
311                         else if (SPEC_SCLS (expr->left->etype) == S_EEPROM)
312                                 DCL_TYPE (val->type) = EEPPOINTER;
313                         else
314                                 DCL_TYPE (val->type) = POINTER;
315                         val->type->next = expr->left->ftype;
316                         val->etype = getSpec (val->type);
317                         return val;
318                 }
319
320                 /* if address of indexed array */
321                 if (IS_AST_OP (expr->left) && expr->left->opval.op == '[')
322                         return valForArray (expr->left);
323
324                 /* if address of structure element then
325                    case 1. a.b ; */
326                 if (IS_AST_OP (expr->left) &&
327                     expr->left->opval.op == '.') {
328                         return valForStructElem (expr->left->left,
329                                                  expr->left->right);
330                 }
331
332                 /* case 2. (&a)->b ;
333                    (&some_struct)->element */
334                 if (IS_AST_OP (expr->left) &&
335                     expr->left->opval.op == PTR_OP &&
336                     IS_ADDRESS_OF_OP (expr->left->left))
337                         return valForStructElem (expr->left->left->left,
338                                                  expr->left->right);
339
340         }
341         /* case 3. (((char *) &a) +/- constant) */
342         if (IS_AST_OP (expr) &&
343             (expr->opval.op == '+' || expr->opval.op == '-') &&
344             IS_AST_OP (expr->left) && expr->left->opval.op == CAST &&
345             IS_AST_OP (expr->left->right) &&
346             expr->left->right->opval.op == '&' &&
347             IS_AST_LIT_VALUE (expr->right)) {
348
349                 return valForCastAggr (expr->left->right->left,
350                                        expr->left->left->opval.lnk,
351                                        expr->right, expr->opval.op);
352
353         }
354         
355         /* case 4. (char *)(array type) */
356         if (IS_CAST_OP(expr) && IS_AST_SYM_VALUE (expr->right) &&
357             IS_ARRAY(expr->right->ftype)) {
358
359                 val = copyValue (AST_VALUE (expr->right));
360                 val->type = newLink ();
361                 if (SPEC_SCLS (expr->right->etype) == S_CODE) {
362                         DCL_TYPE (val->type) = CPOINTER;
363                         DCL_PTR_CONST (val->type) = port->mem.code_ro;
364                 }
365                 else if (SPEC_SCLS (expr->right->etype) == S_XDATA)
366                         DCL_TYPE (val->type) = FPOINTER;
367                 else if (SPEC_SCLS (expr->right->etype) == S_XSTACK)
368                         DCL_TYPE (val->type) = PPOINTER;
369                 else if (SPEC_SCLS (expr->right->etype) == S_IDATA)
370                         DCL_TYPE (val->type) = IPOINTER;
371                 else if (SPEC_SCLS (expr->right->etype) == S_EEPROM)
372                         DCL_TYPE (val->type) = EEPPOINTER;
373                 else
374                         DCL_TYPE (val->type) = POINTER;
375                 val->type->next = expr->right->ftype->next;
376                 val->etype = getSpec (val->type);
377                 return val;
378         }
379  wrong:
380         werror (E_INIT_WRONG);
381         return NULL;
382
383 }
384
385 /*-----------------------------------------------------------------*/
386 /* printChar - formats and prints a characater string with DB      */
387 /*-----------------------------------------------------------------*/
388 void 
389 printChar (FILE * ofile, char *s, int plen)
390 {
391   int i;
392   int len = strlen (s);
393   int pplen = 0;
394   char buf[100];
395   char *p = buf;
396
397   while (len && pplen < plen)
398     {
399       i = 60;
400       while (i && *s && pplen < plen)
401         {
402           if (*s < ' ' || *s == '\"' || *s=='\\')
403             {
404               *p = '\0';
405               if (p != buf)
406                 tfprintf (ofile, "\t!ascii\n", buf);
407               tfprintf (ofile, "\t!db !constbyte\n", (unsigned char)*s);
408               p = buf;
409             }
410           else
411             {
412               *p = *s;
413               p++;
414             }
415           s++;
416           pplen++;
417           i--;
418         }
419       if (p != buf)
420         {
421           *p = '\0';
422           tfprintf (ofile, "\t!ascii\n", buf);
423           p = buf;
424         }
425
426       if (len > 60)
427         len -= 60;
428       else
429         len = 0;
430     }
431   tfprintf (ofile, "\t!db !constbyte\n", 0);
432 }
433
434 /*-----------------------------------------------------------------*/
435 /* return the generic pointer high byte for a given pointer type.  */
436 /*-----------------------------------------------------------------*/
437 int 
438 pointerTypeToGPByte (const int p_type, const char *iname, const char *oname)
439 {
440   switch (p_type)
441     {
442     case IPOINTER:
443     case POINTER:
444       return 0;
445     case GPOINTER:
446       /* hack - if we get a generic pointer, we just assume
447        * it's an FPOINTER (i.e. in XDATA space).
448        */
449       werror (E_CANNOT_USE_GENERIC_POINTER, iname, oname);
450       exit (1);
451       // fall through
452     case FPOINTER:
453       return 1;
454     case CPOINTER:
455       return 2;
456     case PPOINTER:
457       return 3;
458     default:
459       fprintf (stderr, "*** internal error: unknown pointer type %d in GPByte.\n",
460                p_type);
461       break;
462     }
463   return -1;
464 }
465
466
467 /*-----------------------------------------------------------------*/
468 /* printPointerType - generates ival for pointer type              */
469 /*-----------------------------------------------------------------*/
470 void 
471 _printPointerType (FILE * oFile, const char *name)
472 {
473   if (TARGET_IS_DS390)
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 (E_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 || sym->level == 0) && !options.nodebug)
986         {
987
988           cdbSymbol (sym, cdbFile, FALSE, FALSE);
989
990           if (!sym->level)
991             {                   /* global */
992               if (IS_STATIC (sym->etype))
993                 fprintf (out, "F%s$", moduleName);      /* scope is file */
994               else
995                 fprintf (out, "G$");    /* scope is global */
996             }
997           else
998             /* symbol is local */
999             fprintf (out, "L%s$",
1000                      (sym->localof ? sym->localof->name : "-null-"));
1001           fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1002         }
1003
1004       /* if it has an absolute address */
1005       if (SPEC_ABSA (sym->etype))
1006         {
1007           if ((options.debug || sym->level == 0) && !options.nodebug)
1008             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1009
1010           fprintf (out, "%s\t=\t0x%04x\n",
1011                    sym->rname,
1012                    SPEC_ADDR (sym->etype));
1013         }
1014       else
1015         {
1016           if ((options.debug || sym->level == 0) && !options.nodebug)
1017             fprintf (out, " == .\n");
1018
1019           /* if it has an initial value */
1020           if (sym->ival)
1021             {
1022               fprintf (out, "%s:\n", sym->rname);
1023               noAlloc++;
1024               resolveIvalSym (sym->ival);
1025               printIval (sym, sym->type, sym->ival, out);
1026               noAlloc--;
1027             }
1028           else
1029             {
1030               /* allocate space */
1031               fprintf (out, "%s:\n", sym->rname);
1032               /* special case for character strings */
1033               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1034                   SPEC_CVAL (sym->etype).v_char)
1035                 printChar (out,
1036                            SPEC_CVAL (sym->etype).v_char,
1037                            strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1038               else
1039                 tfprintf (out, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1040             }
1041         }
1042     }
1043 }
1044
1045 /*-----------------------------------------------------------------*/
1046 /* emitMaps - emits the code for the data portion the code         */
1047 /*-----------------------------------------------------------------*/
1048 void 
1049 emitMaps ()
1050 {
1051   inInitMode++;
1052   /* no special considerations for the following
1053      data, idata & bit & xdata */
1054   emitRegularMap (data, TRUE, TRUE);
1055   emitRegularMap (idata, TRUE, TRUE);
1056   emitRegularMap (bit, TRUE, FALSE);
1057   emitRegularMap (xdata, TRUE, TRUE);
1058   emitRegularMap (sfr, FALSE, FALSE);
1059   emitRegularMap (sfrbit, FALSE, FALSE);
1060   emitRegularMap (home, TRUE, FALSE);
1061   emitRegularMap (code, TRUE, FALSE);
1062
1063   emitStaticSeg (statsg, code->oFile);
1064   inInitMode--;
1065 }
1066
1067 /*-----------------------------------------------------------------*/
1068 /* flushStatics - flush all currently defined statics out to file  */
1069 /*  and delete.  Temporary function                                */
1070 /*-----------------------------------------------------------------*/
1071 void 
1072 flushStatics (void)
1073 {
1074   emitStaticSeg (statsg, codeOutFile);
1075   statsg->syms = NULL;
1076 }
1077
1078 /*-----------------------------------------------------------------*/
1079 /* createInterruptVect - creates the interrupt vector              */
1080 /*-----------------------------------------------------------------*/
1081 void 
1082 createInterruptVect (FILE * vFile)
1083 {
1084   unsigned i = 0;
1085   mainf = newSymbol ("main", 0);
1086   mainf->block = 0;
1087
1088   /* only if the main function exists */
1089   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1090     {
1091       if (!options.cc_only)
1092         werror (E_NO_MAIN);
1093       return;
1094     }
1095
1096   /* if the main is only a prototype ie. no body then do nothing */
1097   if (!mainf->fbody)
1098     {
1099       /* if ! compile only then main function should be present */
1100       if (!options.cc_only)
1101         werror (E_NO_MAIN);
1102       return;
1103     }
1104
1105   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1106   fprintf (vFile, "__interrupt_vect:\n");
1107
1108
1109   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1110     {
1111       /* "generic" interrupt table header (if port doesn't specify one).
1112
1113        * Look suspiciously like 8051 code to me...
1114        */
1115
1116       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1117
1118
1119       /* now for the other interrupts */
1120       for (; i < maxInterrupts; i++)
1121         {
1122           if (interrupts[i])
1123             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1124           else
1125             fprintf (vFile, "\treti\n\t.ds\t7\n");
1126         }
1127     }
1128 }
1129
1130 char *iComments1 =
1131 {
1132   ";--------------------------------------------------------\n"
1133   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1134
1135 char *iComments2 =
1136 {
1137   ";--------------------------------------------------------\n"};
1138
1139
1140 /*-----------------------------------------------------------------*/
1141 /* initialComments - puts in some initial comments                 */
1142 /*-----------------------------------------------------------------*/
1143 void 
1144 initialComments (FILE * afile)
1145 {
1146   time_t t;
1147   time (&t);
1148   fprintf (afile, "%s", iComments1);
1149   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1150   fprintf (afile, "%s", iComments2);
1151 }
1152
1153 /*-----------------------------------------------------------------*/
1154 /* printPublics - generates .global for publics                    */
1155 /*-----------------------------------------------------------------*/
1156 void 
1157 printPublics (FILE * afile)
1158 {
1159   symbol *sym;
1160
1161   fprintf (afile, "%s", iComments2);
1162   fprintf (afile, "; Public variables in this module\n");
1163   fprintf (afile, "%s", iComments2);
1164
1165   for (sym = setFirstItem (publics); sym;
1166        sym = setNextItem (publics))
1167     tfprintf (afile, "\t!global\n", sym->rname);
1168 }
1169
1170 /*-----------------------------------------------------------------*/
1171 /* printExterns - generates .global for externs                    */
1172 /*-----------------------------------------------------------------*/
1173 void 
1174 printExterns (FILE * afile)
1175 {
1176   symbol *sym;
1177
1178   fprintf (afile, "%s", iComments2);
1179   fprintf (afile, "; Externals used\n");
1180   fprintf (afile, "%s", iComments2);
1181
1182   for (sym = setFirstItem (externs); sym;
1183        sym = setNextItem (externs))
1184     tfprintf (afile, "\t!global\n", sym->rname);
1185 }
1186
1187 /*-----------------------------------------------------------------*/
1188 /* emitOverlay - will emit code for the overlay stuff              */
1189 /*-----------------------------------------------------------------*/
1190 static void 
1191 emitOverlay (FILE * afile)
1192 {
1193   set *ovrset;
1194
1195   if (!elementsInSet (ovrSetSets))
1196     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1197
1198   /* for each of the sets in the overlay segment do */
1199   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1200        ovrset = setNextItem (ovrSetSets))
1201     {
1202
1203       symbol *sym;
1204
1205       if (elementsInSet (ovrset))
1206         {
1207           /* this dummy area is used to fool the assembler
1208              otherwise the assembler will append each of these
1209              declarations into one chunk and will not overlay
1210              sad but true */
1211           fprintf (afile, "\t.area _DUMMY\n");
1212           /* output the area informtion */
1213           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1214         }
1215
1216       for (sym = setFirstItem (ovrset); sym;
1217            sym = setNextItem (ovrset))
1218         {
1219
1220           /* if extern then add it to the publics tabledo nothing */
1221           if (IS_EXTERN (sym->etype))
1222             continue;
1223
1224           /* if allocation required check is needed
1225              then check if the symbol really requires
1226              allocation only for local variables */
1227           if (!IS_AGGREGATE (sym->type) &&
1228               !(sym->_isparm && !IS_REGPARM (sym->etype))
1229               && !sym->allocreq && sym->level)
1230             continue;
1231
1232           /* if global variable & not static or extern
1233              and addPublics allowed then add it to the public set */
1234           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1235               && !IS_STATIC (sym->etype))
1236             addSetHead (&publics, sym);
1237
1238           /* if extern then do nothing or is a function
1239              then do nothing */
1240           if (IS_FUNC (sym->type))
1241             continue;
1242
1243           /* print extra debug info if required */
1244           if ((options.debug || sym->level == 0) && !options.nodebug)
1245             {
1246
1247               cdbSymbol (sym, cdbFile, FALSE, FALSE);
1248
1249               if (!sym->level)
1250                 {               /* global */
1251                   if (IS_STATIC (sym->etype))
1252                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1253                   else
1254                     fprintf (afile, "G$");      /* scope is global */
1255                 }
1256               else
1257                 /* symbol is local */
1258                 fprintf (afile, "L%s$",
1259                          (sym->localof ? sym->localof->name : "-null-"));
1260               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1261             }
1262
1263           /* if is has an absolute address then generate
1264              an equate for this no need to allocate space */
1265           if (SPEC_ABSA (sym->etype))
1266             {
1267
1268               if ((options.debug || sym->level == 0) && !options.nodebug)
1269                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1270
1271               fprintf (afile, "%s\t=\t0x%04x\n",
1272                        sym->rname,
1273                        SPEC_ADDR (sym->etype));
1274             }
1275           else
1276             {
1277               if ((options.debug || sym->level == 0) && !options.nodebug)
1278                 fprintf (afile, "==.\n");
1279
1280               /* allocate space */
1281               tfprintf (afile, "!labeldef\n", sym->rname);
1282               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1283             }
1284
1285         }
1286     }
1287 }
1288
1289 /*-----------------------------------------------------------------*/
1290 /* glue - the final glue that hold the whole thing together        */
1291 /*-----------------------------------------------------------------*/
1292 void 
1293 glue ()
1294 {
1295   FILE *vFile;
1296   FILE *asmFile;
1297   FILE *ovrFile = tempfile ();
1298
1299   addSetHead (&tmpfileSet, ovrFile);
1300   /* print the global struct definitions */
1301   if (options.debug && !options.nodebug)
1302     cdbStructBlock (0, cdbFile);
1303
1304   vFile = tempfile ();
1305   /* PENDING: this isnt the best place but it will do */
1306   if (port->general.glue_up_main)
1307     {
1308       /* create the interrupt vector table */
1309       createInterruptVect (vFile);
1310     }
1311
1312   addSetHead (&tmpfileSet, vFile);
1313
1314   /* emit code for the all the variables declared */
1315   emitMaps ();
1316   /* do the overlay segments */
1317   emitOverlay (ovrFile);
1318
1319   /* now put it all together into the assembler file */
1320   /* create the assembler file name */
1321
1322   if (!options.c1mode)
1323     {
1324       sprintf (scratchFileName, srcFileName);
1325       strcat (scratchFileName, port->assembler.file_ext);
1326     }
1327   else
1328     {
1329       strcpy (scratchFileName, options.out_name);
1330     }
1331
1332   if (!(asmFile = fopen (scratchFileName, "w")))
1333     {
1334       werror (E_FILE_OPEN_ERR, scratchFileName);
1335       exit (1);
1336     }
1337
1338   /* initial comments */
1339   initialComments (asmFile);
1340
1341   /* print module name */
1342   tfprintf (asmFile, "\t!module\n", moduleName);
1343   tfprintf (asmFile, "\t!fileprelude\n");
1344
1345   /* Let the port generate any global directives, etc. */
1346   if (port->genAssemblerPreamble)
1347     {
1348       port->genAssemblerPreamble (asmFile);
1349     }
1350
1351   /* print the global variables in this module */
1352   printPublics (asmFile);
1353   if (port->assembler.externGlobal)
1354     printExterns (asmFile);
1355
1356   /* copy the sfr segment */
1357   fprintf (asmFile, "%s", iComments2);
1358   fprintf (asmFile, "; special function registers\n");
1359   fprintf (asmFile, "%s", iComments2);
1360   copyFile (asmFile, sfr->oFile);
1361
1362   /* copy the sbit segment */
1363   fprintf (asmFile, "%s", iComments2);
1364   fprintf (asmFile, "; special function bits \n");
1365   fprintf (asmFile, "%s", iComments2);
1366   copyFile (asmFile, sfrbit->oFile);
1367
1368   /* copy the data segment */
1369   fprintf (asmFile, "%s", iComments2);
1370   fprintf (asmFile, "; internal ram data\n");
1371   fprintf (asmFile, "%s", iComments2);
1372   copyFile (asmFile, data->oFile);
1373
1374
1375   /* create the overlay segments */
1376   fprintf (asmFile, "%s", iComments2);
1377   fprintf (asmFile, "; overlayable items in internal ram \n");
1378   fprintf (asmFile, "%s", iComments2);
1379   copyFile (asmFile, ovrFile);
1380
1381   /* create the stack segment MOF */
1382   if (mainf && mainf->fbody)
1383     {
1384       fprintf (asmFile, "%s", iComments2);
1385       fprintf (asmFile, "; Stack segment in internal ram \n");
1386       fprintf (asmFile, "%s", iComments2);
1387       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1388                "__start__stack:\n\t.ds\t1\n\n");
1389     }
1390
1391   /* create the idata segment */
1392   fprintf (asmFile, "%s", iComments2);
1393   fprintf (asmFile, "; indirectly addressable internal ram data\n");
1394   fprintf (asmFile, "%s", iComments2);
1395   copyFile (asmFile, idata->oFile);
1396
1397   /* copy the bit segment */
1398   fprintf (asmFile, "%s", iComments2);
1399   fprintf (asmFile, "; bit data\n");
1400   fprintf (asmFile, "%s", iComments2);
1401   copyFile (asmFile, bit->oFile);
1402
1403   /* if external stack then reserve space of it */
1404   if (mainf && mainf->fbody && options.useXstack)
1405     {
1406       fprintf (asmFile, "%s", iComments2);
1407       fprintf (asmFile, "; external stack \n");
1408       fprintf (asmFile, "%s", iComments2);
1409       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1410       fprintf (asmFile, "\t.ds 256\n");
1411     }
1412
1413
1414   /* copy xtern ram data */
1415   fprintf (asmFile, "%s", iComments2);
1416   fprintf (asmFile, "; external ram data\n");
1417   fprintf (asmFile, "%s", iComments2);
1418   copyFile (asmFile, xdata->oFile);
1419
1420   /* copy the interrupt vector table */
1421   if (mainf && mainf->fbody)
1422     {
1423       fprintf (asmFile, "%s", iComments2);
1424       fprintf (asmFile, "; interrupt vector \n");
1425       fprintf (asmFile, "%s", iComments2);
1426       copyFile (asmFile, vFile);
1427     }
1428
1429   /* copy global & static initialisations */
1430   fprintf (asmFile, "%s", iComments2);
1431   fprintf (asmFile, "; global & static initialisations\n");
1432   fprintf (asmFile, "%s", iComments2);
1433
1434   /* Everywhere we generate a reference to the static_name area,
1435    * (which is currently only here), we immediately follow it with a
1436    * definition of the post_static_name area. This guarantees that
1437    * the post_static_name area will immediately follow the static_name
1438    * area.
1439    */
1440   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1441   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1442   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1443
1444   if (mainf && mainf->fbody)
1445     {
1446       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1447       /* if external stack is specified then the
1448          higher order byte of the xdatalocation is
1449          going into P2 and the lower order going into
1450          spx */
1451       if (options.useXstack)
1452         {
1453           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1454                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1455           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1456                    (unsigned int) options.xdata_loc & 0xff);
1457         }
1458
1459       /* initialise the stack pointer */
1460       /* if the user specified a value then use it */
1461       if (options.stack_loc)
1462         fprintf (asmFile, "\tmov\tsp,#%d\n", options.stack_loc);
1463       else
1464         /* no: we have to compute it */
1465       if (!options.stackOnData && maxRegBank <= 3)
1466         fprintf (asmFile, "\tmov\tsp,#%d\n", ((maxRegBank + 1) * 8) - 1);
1467       else
1468         fprintf (asmFile, "\tmov\tsp,#__start__stack\n");       /* MOF */
1469
1470       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1471       fprintf (asmFile, "\tmov\ta,dpl\n");
1472       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1473       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1474       fprintf (asmFile, "__sdcc_init_data:\n");
1475
1476     }
1477   copyFile (asmFile, statsg->oFile);
1478
1479   if (port->general.glue_up_main && mainf && mainf->fbody)
1480     {
1481       /* This code is generated in the post-static area.
1482        * This area is guaranteed to follow the static area
1483        * by the ugly shucking and jiving about 20 lines ago.
1484        */
1485       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1486       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1487     }
1488
1489   fprintf (asmFile,
1490            "%s"
1491            "; Home\n"
1492            "%s", iComments2, iComments2);
1493   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1494   copyFile (asmFile, home->oFile);
1495
1496   /* copy over code */
1497   fprintf (asmFile, "%s", iComments2);
1498   fprintf (asmFile, "; code\n");
1499   fprintf (asmFile, "%s", iComments2);
1500   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1501   if (mainf && mainf->fbody)
1502     {
1503
1504       /* entry point @ start of CSEG */
1505       fprintf (asmFile, "__sdcc_program_startup:\n");
1506
1507       /* put in the call to main */
1508       fprintf (asmFile, "\tlcall\t_main\n");
1509       if (options.mainreturn)
1510         {
1511
1512           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1513           fprintf (asmFile, "\tret\n");
1514
1515         }
1516       else
1517         {
1518
1519           fprintf (asmFile, ";\treturn from main will lock up\n");
1520           fprintf (asmFile, "\tsjmp .\n");
1521         }
1522     }
1523   copyFile (asmFile, code->oFile);
1524
1525   fclose (asmFile);
1526   applyToSet (tmpfileSet, closeTmpFiles);
1527   applyToSet (tmpfileNameSet, rmTmpFiles);
1528 }
1529
1530 /** Creates a temporary file a'la tmpfile which avoids the bugs
1531     in cygwin wrt c:\tmp.
1532     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1533 */
1534 FILE *
1535 tempfile (void)
1536 {
1537 #if !defined(_MSC_VER)
1538   const char *tmpdir = NULL;
1539   if (getenv ("TMP"))
1540     tmpdir = getenv ("TMP");
1541   else if (getenv ("TEMP"))
1542     tmpdir = getenv ("TEMP");
1543   else if (getenv ("TMPDIR"))
1544     tmpdir = getenv ("TMPDIR");
1545   if (tmpdir)
1546     {
1547       char *name = tempnam (tmpdir, "sdcc");
1548       if (name)
1549         {
1550           FILE *fp = fopen (name, "w+b");
1551           if (fp)
1552             {
1553               addSetHead (&tmpfileNameSet, name);
1554             }
1555           return fp;
1556         }
1557       return NULL;
1558     }
1559 #endif
1560   return tmpfile ();
1561 }
1562
1563 char *
1564 gc_strdup (const char *s)
1565 {
1566   char *ret;
1567   ret = Safe_calloc (1, strlen (s) + 1);
1568   strcpy (ret, s);
1569   return ret;
1570 }