fixed an array of structures initialisation bug
[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 (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         val = list2val (ilist);
531         switch (getSize (type)) {
532         case 1:
533                 if (!val)
534                         tfprintf (oFile, "\t!db !constbyte\n", 0);
535                 else
536                         tfprintf (oFile, "\t!dbs\n",
537                                   aopLiteral (val, 0));
538                 break;
539
540         case 2:
541                 if (port->use_dw_for_init)
542                         tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
543                 else
544                         fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
545                 break;
546         case 4:
547                 if (!val) {
548                         tfprintf (oFile, "\t!dw !constword\n", 0);
549                         tfprintf (oFile, "\t!dw !constword\n", 0);
550                 }
551                 else {
552                         fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
553                                  aopLiteral (val, 0), aopLiteral (val, 1),
554                                  aopLiteral (val, 2), aopLiteral (val, 3));
555                 }
556                 break;
557         }
558 }
559
560 /*-----------------------------------------------------------------*/
561 /* printIvalBitFields - generate initializer for bitfields         */
562 /*-----------------------------------------------------------------*/
563 void printIvalBitFields(symbol **sym, initList **ilist, FILE * oFile)
564 {
565         value *val ;
566         symbol *lsym = *sym;
567         initList *lilist = *ilist ;
568         unsigned long ival = 0;
569         int size =0;
570
571         
572         do {
573                 unsigned long i;
574                 val = list2val(lilist);
575                 if (size) {
576                         if (SPEC_BLEN(lsym->etype) > 8) {
577                                 size += ((SPEC_BLEN (lsym->etype) / 8) + 
578                                          (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
579                         }
580                 } else {
581                         size = ((SPEC_BLEN (lsym->etype) / 8) + 
582                                  (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
583                 }
584                 i = (unsigned long)floatFromVal(val);
585                 i <<= SPEC_BSTR (lsym->etype);
586                 ival |= i;
587                 if (! ( lsym->next &&
588                         (IS_BITFIELD(lsym->next->type)) &&
589                         (SPEC_BSTR(lsym->next->etype)))) break;
590                 lsym = lsym->next;
591                 lilist = lilist->next;
592         } while (1);
593         switch (size) {
594         case 1:
595                 tfprintf (oFile, "\t!db !constbyte\n",ival);
596                 break;
597
598         case 2:
599                 tfprintf (oFile, "\t!dw !constword\n",ival);
600                 break;
601         case 4:
602                 tfprintf (oFile, "\t!db  !constword,!constword\n",
603                          (ival >> 8) & 0xffff, (ival & 0xffff));
604                 break;
605         }
606         *sym = lsym;
607         *ilist = lilist;
608 }
609
610 /*-----------------------------------------------------------------*/
611 /* printIvalStruct - generates initial value for structures        */
612 /*-----------------------------------------------------------------*/
613 void 
614 printIvalStruct (symbol * sym, sym_link * type,
615                  initList * ilist, FILE * oFile)
616 {
617         symbol *sflds;
618         initList *iloop;
619
620         sflds = SPEC_STRUCT (type)->fields;
621         if (ilist->type != INIT_DEEP) {
622                 werror (E_INIT_STRUCT, sym->name);
623                 return;
624         }
625
626         iloop = ilist->init.deep;
627
628         for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) {
629                 if (IS_BITFIELD(sflds->type)) {
630                         printIvalBitFields(&sflds,&iloop,oFile);
631                 } else {
632                         printIval (sflds, sflds->type, iloop, oFile);
633                 }
634         }
635         return;
636 }
637
638 /*-----------------------------------------------------------------*/
639 /* printIvalChar - generates initital value for character array    */
640 /*-----------------------------------------------------------------*/
641 int 
642 printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s)
643 {
644   value *val;
645   int remain;
646
647   if (!s)
648     {
649
650       val = list2val (ilist);
651       /* if the value is a character string  */
652       if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
653         {
654           if (!DCL_ELEM (type))
655             DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1;
656
657           printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type));
658
659           if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) - 1)) > 0)
660             while (remain--)
661               tfprintf (oFile, "\t!db !constbyte\n", 0);
662
663           return 1;
664         }
665       else
666         return 0;
667     }
668   else
669     printChar (oFile, s, strlen (s) + 1);
670   return 1;
671 }
672
673 /*-----------------------------------------------------------------*/
674 /* printIvalArray - generates code for array initialization        */
675 /*-----------------------------------------------------------------*/
676 void 
677 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
678                 FILE * oFile)
679 {
680   initList *iloop;
681   int lcnt = 0, size = 0;
682
683   /* take care of the special   case  */
684   /* array of characters can be init  */
685   /* by a string                      */
686   if (IS_CHAR (type->next))
687     if (printIvalChar (type,
688                        (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
689                        oFile, SPEC_CVAL (sym->etype).v_char))
690       return;
691
692   /* not the special case             */
693   if (ilist->type != INIT_DEEP)
694     {
695       werror (E_INIT_STRUCT, sym->name);
696       return;
697     }
698
699   iloop = ilist->init.deep;
700   lcnt = DCL_ELEM (type);
701
702   for (;;)
703     {
704       size++;
705       printIval (sym, type->next, iloop, oFile);
706       iloop = (iloop ? iloop->next : NULL);
707
708
709       /* if not array limits given & we */
710       /* are out of initialisers then   */
711       if (!DCL_ELEM (type) && !iloop)
712         break;
713
714       /* no of elements given and we    */
715       /* have generated for all of them */
716       if (!--lcnt) {
717         /* if initializers left */
718         if (iloop) {
719           werror (W_EXESS_ARRAY_INITIALIZERS, sym->name, sym->lineDef);
720         }
721         break;
722       }
723     }
724
725   /* if we have not been given a size  */
726   if (!DCL_ELEM (type))
727     DCL_ELEM (type) = size;
728
729   return;
730 }
731
732 /*-----------------------------------------------------------------*/
733 /* printIvalFuncPtr - generate initial value for function pointers */
734 /*-----------------------------------------------------------------*/
735 void 
736 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
737 {
738   value *val;
739   int dLvl = 0;
740
741   val = list2val (ilist);
742   /* check the types   */
743   if ((dLvl = compareType (val->type, type->next)) <= 0)
744     {
745       tfprintf (oFile, "\t!dw !constword\n", 0);
746       return;
747     }
748
749   /* now generate the name */
750   if (!val->sym)
751     {
752       if (port->use_dw_for_init)
753         {
754           tfprintf (oFile, "\t!dws\n", val->name);
755         }
756       else
757         {
758           printPointerType (oFile, val->name);
759         }
760     }
761   else if (port->use_dw_for_init)
762     {
763       tfprintf (oFile, "\t!dws\n", val->sym->rname);
764     }
765   else
766     {
767       printPointerType (oFile, val->sym->rname);
768     }
769
770   return;
771 }
772
773 /*-----------------------------------------------------------------*/
774 /* printIvalCharPtr - generates initial values for character pointers */
775 /*-----------------------------------------------------------------*/
776 int 
777 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
778 {
779   int size = 0;
780
781   /* PENDING: this is _very_ mcs51 specific, including a magic
782      number...
783      It's also endin specific.
784    */
785   size = getSize (type);
786
787   if (val->name && strlen (val->name))
788     {
789       if (size == 1)            /* This appears to be Z80 specific?? */
790         {
791           tfprintf (oFile,
792                     "\t!dbs\n", val->name);
793         }
794       else if (size == FPTRSIZE)
795         {
796           if (port->use_dw_for_init)
797             {
798               tfprintf (oFile, "\t!dws\n", val->name);
799             }
800           else
801             {
802               printPointerType (oFile, val->name);
803             }
804         }
805       else if (size == GPTRSIZE)
806         {
807           int type;
808           if (IS_PTR (val->type)) {
809             type = DCL_TYPE (val->type);
810           } else {
811             type = PTR_TYPE (SPEC_OCLS (val->etype));
812           }
813           if (val->sym && val->sym->isstrlit) {
814             // this is a literal string
815             type=CPOINTER;
816           }
817           printGPointerType (oFile, val->name, sym->name, type);
818         }
819       else
820         {
821           fprintf (stderr, "*** internal error: unknown size in "
822                    "printIvalCharPtr.\n");
823         }
824     }
825   else
826     {
827       /* What is this case? Are these pointers? */
828       switch (size)
829         {
830         case 1:
831           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
832           break;
833         case 2:
834           if (port->use_dw_for_init)
835             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
836           else
837             tfprintf (oFile, "\t.byte %s,%s\n",
838                       aopLiteral (val, 0), aopLiteral (val, 1));
839           break;
840         case 3:
841           /* PENDING: 0x02 or 0x%02x, CDATA? */
842           fprintf (oFile, "\t.byte %s,%s,#0x02\n",
843                    aopLiteral (val, 0), aopLiteral (val, 1));
844           break;
845         default:
846           assert (0);
847         }
848     }
849
850   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
851     addSet (&statsg->syms, val->sym);
852   }
853
854   return 1;
855 }
856
857 /*-----------------------------------------------------------------*/
858 /* printIvalPtr - generates initial value for pointers             */
859 /*-----------------------------------------------------------------*/
860 void 
861 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
862 {
863   value *val;
864   int size;
865
866   /* if deep then   */
867   if (ilist->type == INIT_DEEP)
868     ilist = ilist->init.deep;
869
870   /* function pointer     */
871   if (IS_FUNC (type->next))
872     {
873       printIvalFuncPtr (type, ilist, oFile);
874       return;
875     }
876
877   if (!(val = initPointer (ilist)))
878     return;
879
880   /* if character pointer */
881   if (IS_CHAR (type->next))
882     if (printIvalCharPtr (sym, type, val, oFile))
883       return;
884
885   /* check the type      */
886   if (compareType (type, val->type) == 0)
887     werror (W_INIT_WRONG);
888
889   /* if val is literal */
890   if (IS_LITERAL (val->etype))
891     {
892       switch (getSize (type))
893         {
894         case 1:
895           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
896           break;
897         case 2:
898           if (port->use_dw_for_init)
899             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
900           else
901             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
902           break;
903         case 3:
904           fprintf (oFile, "\t.byte %s,%s,#0x02\n",
905                    aopLiteral (val, 0), aopLiteral (val, 1));
906         }
907       return;
908     }
909
910
911   size = getSize (type);
912
913   if (size == 1)                /* Z80 specific?? */
914     {
915       tfprintf (oFile, "\t!dbs\n", val->name);
916     }
917   else if (size == FPTRSIZE)
918     {
919       if (port->use_dw_for_init) {
920         tfprintf (oFile, "\t!dws\n", val->name);
921       } else {
922         printPointerType (oFile, val->name);
923       }
924     }
925   else if (size == GPTRSIZE)
926     {
927       printGPointerType (oFile, val->name, sym->name,
928                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
929                           PTR_TYPE (SPEC_OCLS (val->etype))));
930     }
931   return;
932 }
933
934 /*-----------------------------------------------------------------*/
935 /* printIval - generates code for initial value                    */
936 /*-----------------------------------------------------------------*/
937 void 
938 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
939 {
940   if (!ilist)
941     return;
942
943   /* if structure then    */
944   if (IS_STRUCT (type))
945     {
946       printIvalStruct (sym, type, ilist, oFile);
947       return;
948     }
949
950   /* if this is a pointer */
951   if (IS_PTR (type))
952     {
953       printIvalPtr (sym, type, ilist, oFile);
954       return;
955     }
956
957   /* if this is an array   */
958   if (IS_ARRAY (type))
959     {
960       printIvalArray (sym, type, ilist, oFile);
961       return;
962     }
963
964   /* if type is SPECIFIER */
965   if (IS_SPEC (type))
966     {
967       printIvalType (type, ilist, oFile);
968       return;
969     }
970 }
971
972 /*-----------------------------------------------------------------*/
973 /* emitStaticSeg - emitcode for the static segment                 */
974 /*-----------------------------------------------------------------*/
975 void 
976 emitStaticSeg (memmap * map, FILE * out)
977 {
978   symbol *sym;
979
980   /*     fprintf(map->oFile,"\t.area\t%s\n",map->sname); */
981   if (!out)
982     out = code->oFile;
983
984   /* for all variables in this segment do */
985   for (sym = setFirstItem (map->syms); sym;
986        sym = setNextItem (map->syms))
987     {
988
989       /* if it is "extern" then do nothing */
990       if (IS_EXTERN (sym->etype))
991         continue;
992
993       /* if it is not static add it to the public
994          table */
995       if (!IS_STATIC (sym->etype))
996         addSetHead (&publics, sym);
997
998       /* print extra debug info if required */
999       if (options.debug) {
1000         cdbSymbol (sym, cdbFile, FALSE, FALSE);
1001         if (!sym->level)
1002           {                     /* global */
1003             if (IS_STATIC (sym->etype))
1004               fprintf (out, "F%s$", moduleName);        /* scope is file */
1005             else
1006               fprintf (out, "G$");      /* scope is global */
1007           }
1008         else
1009           /* symbol is local */
1010           fprintf (out, "L%s$",
1011                    (sym->localof ? sym->localof->name : "-null-"));
1012         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1013       }
1014       
1015       /* if it has an absolute address */
1016       if (SPEC_ABSA (sym->etype))
1017         {
1018           if (options.debug)
1019             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1020           
1021           fprintf (out, "%s\t=\t0x%04x\n",
1022                    sym->rname,
1023                    SPEC_ADDR (sym->etype));
1024         }
1025       else
1026         {
1027           if (options.debug)
1028             fprintf (out, " == .\n");
1029           
1030           /* if it has an initial value */
1031           if (sym->ival)
1032             {
1033               fprintf (out, "%s:\n", sym->rname);
1034               noAlloc++;
1035               resolveIvalSym (sym->ival);
1036               printIval (sym, sym->type, sym->ival, out);
1037               noAlloc--;
1038             }
1039           else
1040             {
1041               /* allocate space */
1042               fprintf (out, "%s:\n", sym->rname);
1043               /* special case for character strings */
1044               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1045                   SPEC_CVAL (sym->etype).v_char)
1046                 printChar (out,
1047                            SPEC_CVAL (sym->etype).v_char,
1048                            strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1049               else
1050                 tfprintf (out, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1051             }
1052         }
1053     }
1054 }
1055
1056 /*-----------------------------------------------------------------*/
1057 /* emitMaps - emits the code for the data portion the code         */
1058 /*-----------------------------------------------------------------*/
1059 void 
1060 emitMaps ()
1061 {
1062   inInitMode++;
1063   /* no special considerations for the following
1064      data, idata & bit & xdata */
1065   emitRegularMap (data, TRUE, TRUE);
1066   emitRegularMap (idata, TRUE, TRUE);
1067   emitRegularMap (bit, TRUE, FALSE);
1068   emitRegularMap (xdata, TRUE, TRUE);
1069   emitRegularMap (sfr, FALSE, FALSE);
1070   emitRegularMap (sfrbit, FALSE, FALSE);
1071   emitRegularMap (home, TRUE, FALSE);
1072   emitRegularMap (code, TRUE, FALSE);
1073
1074   emitStaticSeg (statsg, code->oFile);
1075   inInitMode--;
1076 }
1077
1078 /*-----------------------------------------------------------------*/
1079 /* flushStatics - flush all currently defined statics out to file  */
1080 /*  and delete.  Temporary function                                */
1081 /*-----------------------------------------------------------------*/
1082 void 
1083 flushStatics (void)
1084 {
1085   emitStaticSeg (statsg, codeOutFile);
1086   statsg->syms = NULL;
1087 }
1088
1089 /*-----------------------------------------------------------------*/
1090 /* createInterruptVect - creates the interrupt vector              */
1091 /*-----------------------------------------------------------------*/
1092 void 
1093 createInterruptVect (FILE * vFile)
1094 {
1095   unsigned i = 0;
1096   mainf = newSymbol ("main", 0);
1097   mainf->block = 0;
1098
1099   /* only if the main function exists */
1100   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1101     {
1102       if (!options.cc_only && !noAssemble)
1103         werror (E_NO_MAIN);
1104       return;
1105     }
1106
1107   /* if the main is only a prototype ie. no body then do nothing */
1108   if (!IFFUNC_HASBODY(mainf->type))
1109     {
1110       /* if ! compile only then main function should be present */
1111       if (!options.cc_only && !noAssemble)
1112         werror (E_NO_MAIN);
1113       return;
1114     }
1115
1116   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1117   fprintf (vFile, "__interrupt_vect:\n");
1118
1119
1120   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1121     {
1122       /* "generic" interrupt table header (if port doesn't specify one).
1123
1124        * Look suspiciously like 8051 code to me...
1125        */
1126
1127       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1128
1129
1130       /* now for the other interrupts */
1131       for (; i < maxInterrupts; i++)
1132         {
1133           if (interrupts[i])
1134             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1135           else
1136             fprintf (vFile, "\treti\n\t.ds\t7\n");
1137         }
1138     }
1139 }
1140
1141 char *iComments1 =
1142 {
1143   ";--------------------------------------------------------\n"
1144   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1145
1146 char *iComments2 =
1147 {
1148   ";--------------------------------------------------------\n"};
1149
1150
1151 /*-----------------------------------------------------------------*/
1152 /* initialComments - puts in some initial comments                 */
1153 /*-----------------------------------------------------------------*/
1154 void 
1155 initialComments (FILE * afile)
1156 {
1157   time_t t;
1158   time (&t);
1159   fprintf (afile, "%s", iComments1);
1160   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1161   fprintf (afile, "%s", iComments2);
1162 }
1163
1164 /*-----------------------------------------------------------------*/
1165 /* printPublics - generates .global for publics                    */
1166 /*-----------------------------------------------------------------*/
1167 void 
1168 printPublics (FILE * afile)
1169 {
1170   symbol *sym;
1171
1172   fprintf (afile, "%s", iComments2);
1173   fprintf (afile, "; Public variables in this module\n");
1174   fprintf (afile, "%s", iComments2);
1175
1176   for (sym = setFirstItem (publics); sym;
1177        sym = setNextItem (publics))
1178     tfprintf (afile, "\t!global\n", sym->rname);
1179 }
1180
1181 /*-----------------------------------------------------------------*/
1182 /* printExterns - generates .global for externs                    */
1183 /*-----------------------------------------------------------------*/
1184 void 
1185 printExterns (FILE * afile)
1186 {
1187   symbol *sym;
1188
1189   fprintf (afile, "%s", iComments2);
1190   fprintf (afile, "; Externals used\n");
1191   fprintf (afile, "%s", iComments2);
1192
1193   for (sym = setFirstItem (externs); sym;
1194        sym = setNextItem (externs))
1195     tfprintf (afile, "\t!global\n", sym->rname);
1196 }
1197
1198 /*-----------------------------------------------------------------*/
1199 /* emitOverlay - will emit code for the overlay stuff              */
1200 /*-----------------------------------------------------------------*/
1201 static void 
1202 emitOverlay (FILE * afile)
1203 {
1204   set *ovrset;
1205
1206   if (!elementsInSet (ovrSetSets))
1207     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1208
1209   /* for each of the sets in the overlay segment do */
1210   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1211        ovrset = setNextItem (ovrSetSets))
1212     {
1213
1214       symbol *sym;
1215
1216       if (elementsInSet (ovrset))
1217         {
1218           /* this dummy area is used to fool the assembler
1219              otherwise the assembler will append each of these
1220              declarations into one chunk and will not overlay
1221              sad but true */
1222           fprintf (afile, "\t.area _DUMMY\n");
1223           /* output the area informtion */
1224           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1225         }
1226
1227       for (sym = setFirstItem (ovrset); sym;
1228            sym = setNextItem (ovrset))
1229         {
1230
1231           /* if extern then add it to the publics tabledo nothing */
1232           if (IS_EXTERN (sym->etype))
1233             continue;
1234
1235           /* if allocation required check is needed
1236              then check if the symbol really requires
1237              allocation only for local variables */
1238           if (!IS_AGGREGATE (sym->type) &&
1239               !(sym->_isparm && !IS_REGPARM (sym->etype))
1240               && !sym->allocreq && sym->level)
1241             continue;
1242
1243           /* if global variable & not static or extern
1244              and addPublics allowed then add it to the public set */
1245           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1246               && !IS_STATIC (sym->etype))
1247             addSetHead (&publics, sym);
1248
1249           /* if extern then do nothing or is a function
1250              then do nothing */
1251           if (IS_FUNC (sym->type))
1252             continue;
1253
1254           /* print extra debug info if required */
1255           if (options.debug)
1256             {
1257               cdbSymbol (sym, cdbFile, FALSE, FALSE);
1258
1259               if (!sym->level)
1260                 {               /* global */
1261                   if (IS_STATIC (sym->etype))
1262                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1263                   else
1264                     fprintf (afile, "G$");      /* scope is global */
1265                 }
1266               else
1267                 /* symbol is local */
1268                 fprintf (afile, "L%s$",
1269                          (sym->localof ? sym->localof->name : "-null-"));
1270               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1271             }
1272
1273           /* if is has an absolute address then generate
1274              an equate for this no need to allocate space */
1275           if (SPEC_ABSA (sym->etype))
1276             {
1277
1278               if (options.debug)
1279                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1280
1281               fprintf (afile, "%s\t=\t0x%04x\n",
1282                        sym->rname,
1283                        SPEC_ADDR (sym->etype));
1284             }
1285           else
1286             {
1287               if (options.debug)
1288                 fprintf (afile, "==.\n");
1289               
1290               /* allocate space */
1291               tfprintf (afile, "!labeldef\n", sym->rname);
1292               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1293             }
1294
1295         }
1296     }
1297 }
1298
1299 /*-----------------------------------------------------------------*/
1300 /* glue - the final glue that hold the whole thing together        */
1301 /*-----------------------------------------------------------------*/
1302 void 
1303 glue ()
1304 {
1305   FILE *vFile;
1306   FILE *asmFile;
1307   FILE *ovrFile = tempfile ();
1308
1309   addSetHead (&tmpfileSet, ovrFile);
1310   /* print the global struct definitions */
1311   if (options.debug)
1312     cdbStructBlock (0, cdbFile);
1313
1314   vFile = tempfile ();
1315   /* PENDING: this isnt the best place but it will do */
1316   if (port->general.glue_up_main)
1317     {
1318       /* create the interrupt vector table */
1319       createInterruptVect (vFile);
1320     }
1321
1322   addSetHead (&tmpfileSet, vFile);
1323
1324   /* emit code for the all the variables declared */
1325   emitMaps ();
1326   /* do the overlay segments */
1327   emitOverlay (ovrFile);
1328
1329   /* now put it all together into the assembler file */
1330   /* create the assembler file name */
1331
1332   if (!options.c1mode)
1333     {
1334       sprintf (scratchFileName, srcFileName);
1335       strcat (scratchFileName, port->assembler.file_ext);
1336     }
1337   else
1338     {
1339       strcpy (scratchFileName, options.out_name);
1340     }
1341
1342   if (!(asmFile = fopen (scratchFileName, "w")))
1343     {
1344       werror (E_FILE_OPEN_ERR, scratchFileName);
1345       exit (1);
1346     }
1347
1348   /* initial comments */
1349   initialComments (asmFile);
1350
1351   /* print module name */
1352   tfprintf (asmFile, "\t!module\n", moduleName);
1353   tfprintf (asmFile, "\t!fileprelude\n");
1354
1355   /* Let the port generate any global directives, etc. */
1356   if (port->genAssemblerPreamble)
1357     {
1358       port->genAssemblerPreamble (asmFile);
1359     }
1360
1361   /* print the global variables in this module */
1362   printPublics (asmFile);
1363   if (port->assembler.externGlobal)
1364     printExterns (asmFile);
1365
1366   /* copy the sfr segment */
1367   fprintf (asmFile, "%s", iComments2);
1368   fprintf (asmFile, "; special function registers\n");
1369   fprintf (asmFile, "%s", iComments2);
1370   copyFile (asmFile, sfr->oFile);
1371
1372   /* copy the sbit segment */
1373   fprintf (asmFile, "%s", iComments2);
1374   fprintf (asmFile, "; special function bits \n");
1375   fprintf (asmFile, "%s", iComments2);
1376   copyFile (asmFile, sfrbit->oFile);
1377
1378   /* copy the data segment */
1379   fprintf (asmFile, "%s", iComments2);
1380   fprintf (asmFile, "; internal ram data\n");
1381   fprintf (asmFile, "%s", iComments2);
1382   copyFile (asmFile, data->oFile);
1383
1384
1385   /* create the overlay segments */
1386   fprintf (asmFile, "%s", iComments2);
1387   fprintf (asmFile, "; overlayable items in internal ram \n");
1388   fprintf (asmFile, "%s", iComments2);
1389   copyFile (asmFile, ovrFile);
1390
1391   /* create the stack segment MOF */
1392   if (mainf && IFFUNC_HASBODY(mainf->type))
1393     {
1394       fprintf (asmFile, "%s", iComments2);
1395       fprintf (asmFile, "; Stack segment in internal ram \n");
1396       fprintf (asmFile, "%s", iComments2);
1397       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1398                "__start__stack:\n\t.ds\t1\n\n");
1399     }
1400
1401   /* create the idata segment */
1402   fprintf (asmFile, "%s", iComments2);
1403   fprintf (asmFile, "; indirectly addressable internal ram data\n");
1404   fprintf (asmFile, "%s", iComments2);
1405   copyFile (asmFile, idata->oFile);
1406
1407   /* copy the bit segment */
1408   fprintf (asmFile, "%s", iComments2);
1409   fprintf (asmFile, "; bit data\n");
1410   fprintf (asmFile, "%s", iComments2);
1411   copyFile (asmFile, bit->oFile);
1412
1413   /* if external stack then reserve space of it */
1414   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1415     {
1416       fprintf (asmFile, "%s", iComments2);
1417       fprintf (asmFile, "; external stack \n");
1418       fprintf (asmFile, "%s", iComments2);
1419       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1420       fprintf (asmFile, "\t.ds 256\n");
1421     }
1422
1423
1424   /* copy xtern ram data */
1425   fprintf (asmFile, "%s", iComments2);
1426   fprintf (asmFile, "; external ram data\n");
1427   fprintf (asmFile, "%s", iComments2);
1428   copyFile (asmFile, xdata->oFile);
1429
1430   /* copy the interrupt vector table */
1431   if (mainf && IFFUNC_HASBODY(mainf->type))
1432     {
1433       fprintf (asmFile, "%s", iComments2);
1434       fprintf (asmFile, "; interrupt vector \n");
1435       fprintf (asmFile, "%s", iComments2);
1436       copyFile (asmFile, vFile);
1437     }
1438
1439   /* copy global & static initialisations */
1440   fprintf (asmFile, "%s", iComments2);
1441   fprintf (asmFile, "; global & static initialisations\n");
1442   fprintf (asmFile, "%s", iComments2);
1443
1444   /* Everywhere we generate a reference to the static_name area,
1445    * (which is currently only here), we immediately follow it with a
1446    * definition of the post_static_name area. This guarantees that
1447    * the post_static_name area will immediately follow the static_name
1448    * area.
1449    */
1450   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1451   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1452   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1453
1454   if (mainf && IFFUNC_HASBODY(mainf->type))
1455     {
1456       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1457       /* if external stack is specified then the
1458          higher order byte of the xdatalocation is
1459          going into P2 and the lower order going into
1460          spx */
1461       if (options.useXstack)
1462         {
1463           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1464                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1465           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1466                    (unsigned int) options.xdata_loc & 0xff);
1467         }
1468
1469       /* initialise the stack pointer */
1470       /* if the user specified a value then use it */
1471       if (options.stack_loc)
1472         fprintf (asmFile, "\tmov\tsp,#%d\n", options.stack_loc);
1473       else
1474         /* no: we have to compute it */
1475       if (!options.stackOnData && maxRegBank <= 3)
1476         fprintf (asmFile, "\tmov\tsp,#%d\n", ((maxRegBank + 1) * 8) - 1);
1477       else
1478         fprintf (asmFile, "\tmov\tsp,#__start__stack\n");       /* MOF */
1479
1480       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1481       fprintf (asmFile, "\tmov\ta,dpl\n");
1482       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1483       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1484       fprintf (asmFile, "__sdcc_init_data:\n");
1485
1486     }
1487   copyFile (asmFile, statsg->oFile);
1488
1489   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1490     {
1491       /* This code is generated in the post-static area.
1492        * This area is guaranteed to follow the static area
1493        * by the ugly shucking and jiving about 20 lines ago.
1494        */
1495       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1496       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1497     }
1498
1499   fprintf (asmFile,
1500            "%s"
1501            "; Home\n"
1502            "%s", iComments2, iComments2);
1503   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1504   copyFile (asmFile, home->oFile);
1505
1506   /* copy over code */
1507   fprintf (asmFile, "%s", iComments2);
1508   fprintf (asmFile, "; code\n");
1509   fprintf (asmFile, "%s", iComments2);
1510   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1511   if (mainf && IFFUNC_HASBODY(mainf->type))
1512     {
1513
1514       /* entry point @ start of CSEG */
1515       fprintf (asmFile, "__sdcc_program_startup:\n");
1516
1517       /* put in the call to main */
1518       fprintf (asmFile, "\tlcall\t_main\n");
1519       if (options.mainreturn)
1520         {
1521
1522           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1523           fprintf (asmFile, "\tret\n");
1524
1525         }
1526       else
1527         {
1528
1529           fprintf (asmFile, ";\treturn from main will lock up\n");
1530           fprintf (asmFile, "\tsjmp .\n");
1531         }
1532     }
1533   copyFile (asmFile, code->oFile);
1534
1535   fclose (asmFile);
1536   applyToSet (tmpfileSet, closeTmpFiles);
1537   applyToSet (tmpfileNameSet, rmTmpFiles);
1538 }
1539
1540 #if defined (__MINGW32__) || defined (__CYGWIN__) || defined (_MSC_VER)
1541 void
1542 rm_tmpfiles (void)
1543 {
1544   applyToSet (tmpfileSet, closeTmpFiles);
1545   applyToSet (tmpfileNameSet, rmTmpFiles);
1546 }
1547 #endif
1548
1549 /** Creates a temporary file name a'la tmpnam which avoids the bugs
1550     in cygwin wrt c:\tmp.
1551     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1552 */
1553 char *
1554 tempfilename (void)
1555 {
1556 #if !defined(_MSC_VER)
1557   const char *tmpdir = NULL;
1558   if (getenv ("TMP"))
1559     tmpdir = getenv ("TMP");
1560   else if (getenv ("TEMP"))
1561     tmpdir = getenv ("TEMP");
1562   else if (getenv ("TMPDIR"))
1563     tmpdir = getenv ("TMPDIR");
1564   if (tmpdir)
1565     {
1566       char *name = tempnam (tmpdir, "sdcc");
1567       if (name)
1568         {
1569           return name;
1570         }
1571     }
1572 #endif
1573   return tmpnam (NULL);
1574 }
1575
1576 /** Creates a temporary file a'la tmpfile which avoids the bugs
1577     in cygwin wrt c:\tmp.
1578     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1579 */
1580 FILE *
1581 tempfile (void)
1582 {
1583 #if !defined(_MSC_VER)
1584   const char *tmpdir = NULL;
1585   if (getenv ("TMP"))
1586     tmpdir = getenv ("TMP");
1587   else if (getenv ("TEMP"))
1588     tmpdir = getenv ("TEMP");
1589   else if (getenv ("TMPDIR"))
1590     tmpdir = getenv ("TMPDIR");
1591   if (tmpdir)
1592     {
1593       char *name = Safe_strdup( tempnam (tmpdir, "sdcc"));
1594       if (name)
1595         {
1596           FILE *fp = fopen (name, "w+b");
1597           if (fp)
1598             {
1599               addSetHead (&tmpfileNameSet, name);
1600             }
1601           return fp;
1602         }
1603       return NULL;
1604     }
1605 #endif
1606   return tmpfile ();
1607 }
1608