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