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