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