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