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