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