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