e0d0619a6eea9029e4ba5bc6e0fc9eae79ebf34d
[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         addSetHead (&publics, sym);
1062
1063       /* print extra debug info if required */
1064       if (options.debug) {
1065         cdbSymbol (sym, cdbFile, FALSE, FALSE);
1066         if (!sym->level)
1067           {                     /* global */
1068             if (IS_STATIC (sym->etype))
1069               fprintf (out, "F%s$", moduleName);        /* scope is file */
1070             else
1071               fprintf (out, "G$");      /* scope is global */
1072           }
1073         else
1074           /* symbol is local */
1075           fprintf (out, "L%s$",
1076                    (sym->localof ? sym->localof->name : "-null-"));
1077         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1078       }
1079       
1080       /* if it has an absolute address */
1081       if (SPEC_ABSA (sym->etype))
1082         {
1083           if (options.debug)
1084             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1085           
1086           fprintf (out, "%s\t=\t0x%04x\n",
1087                    sym->rname,
1088                    SPEC_ADDR (sym->etype));
1089         }
1090       else
1091         {
1092           if (options.debug)
1093             fprintf (out, " == .\n");
1094           
1095           /* if it has an initial value */
1096           if (sym->ival)
1097             {
1098               fprintf (out, "%s:\n", sym->rname);
1099               noAlloc++;
1100               resolveIvalSym (sym->ival);
1101               printIval (sym, sym->type, sym->ival, out);
1102               noAlloc--;
1103             }
1104           else {
1105               /* allocate space */
1106               int size = getSize (sym->type);
1107               
1108               if (size==0) {
1109                   werror(E_UNKNOWN_SIZE,sym->name);
1110               }
1111               fprintf (out, "%s:\n", sym->rname);
1112               /* special case for character strings */
1113               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1114                   SPEC_CVAL (sym->etype).v_char)
1115                   printChar (out,
1116                              SPEC_CVAL (sym->etype).v_char,
1117                              strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1118               else
1119                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1120             }
1121         }
1122     }
1123 }
1124
1125 /*-----------------------------------------------------------------*/
1126 /* emitMaps - emits the code for the data portion the code         */
1127 /*-----------------------------------------------------------------*/
1128 void 
1129 emitMaps ()
1130 {
1131   inInitMode++;
1132   /* no special considerations for the following
1133      data, idata & bit & xdata */
1134   emitRegularMap (data, TRUE, TRUE);
1135   emitRegularMap (idata, TRUE, TRUE);
1136   emitRegularMap (bit, TRUE, FALSE);
1137   emitRegularMap (xdata, TRUE, TRUE);
1138   if (port->genXINIT) {
1139     emitRegularMap (xidata, TRUE, TRUE);
1140   }
1141   emitRegularMap (sfr, FALSE, FALSE);
1142   emitRegularMap (sfrbit, FALSE, FALSE);
1143   emitRegularMap (home, TRUE, FALSE);
1144   emitRegularMap (code, TRUE, FALSE);
1145
1146   emitStaticSeg (statsg, code->oFile);
1147   if (port->genXINIT) {
1148     fprintf (code->oFile, "\t.area\t%s\n", xinit->sname);
1149     emitStaticSeg (xinit, code->oFile);
1150   }
1151   inInitMode--;
1152 }
1153
1154 /*-----------------------------------------------------------------*/
1155 /* flushStatics - flush all currently defined statics out to file  */
1156 /*  and delete.  Temporary function                                */
1157 /*-----------------------------------------------------------------*/
1158 void 
1159 flushStatics (void)
1160 {
1161   emitStaticSeg (statsg, codeOutFile);
1162   statsg->syms = NULL;
1163 }
1164
1165 /*-----------------------------------------------------------------*/
1166 /* createInterruptVect - creates the interrupt vector              */
1167 /*-----------------------------------------------------------------*/
1168 void 
1169 createInterruptVect (FILE * vFile)
1170 {
1171   unsigned i = 0;
1172   mainf = newSymbol ("main", 0);
1173   mainf->block = 0;
1174
1175   /* only if the main function exists */
1176   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1177     {
1178       if (!options.cc_only && !noAssemble)
1179         werror (E_NO_MAIN);
1180       return;
1181     }
1182
1183   /* if the main is only a prototype ie. no body then do nothing */
1184   if (!IFFUNC_HASBODY(mainf->type))
1185     {
1186       /* if ! compile only then main function should be present */
1187       if (!options.cc_only && !noAssemble)
1188         werror (E_NO_MAIN);
1189       return;
1190     }
1191
1192   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1193   fprintf (vFile, "__interrupt_vect:\n");
1194
1195
1196   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1197     {
1198       /* "generic" interrupt table header (if port doesn't specify one).
1199        * Look suspiciously like 8051 code to me...
1200        */
1201
1202       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1203
1204
1205       /* now for the other interrupts */
1206       for (; i < maxInterrupts; i++)
1207         {
1208           if (interrupts[i])
1209             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1210           else
1211             fprintf (vFile, "\treti\n\t.ds\t7\n");
1212         }
1213     }
1214 }
1215
1216 char *iComments1 =
1217 {
1218   ";--------------------------------------------------------\n"
1219   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1220
1221 char *iComments2 =
1222 {
1223   ";--------------------------------------------------------\n"};
1224
1225
1226 /*-----------------------------------------------------------------*/
1227 /* initialComments - puts in some initial comments                 */
1228 /*-----------------------------------------------------------------*/
1229 void 
1230 initialComments (FILE * afile)
1231 {
1232   time_t t;
1233   time (&t);
1234   fprintf (afile, "%s", iComments1);
1235   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1236   fprintf (afile, "%s", iComments2);
1237 }
1238
1239 /*-----------------------------------------------------------------*/
1240 /* printPublics - generates .global for publics                    */
1241 /*-----------------------------------------------------------------*/
1242 void 
1243 printPublics (FILE * afile)
1244 {
1245   symbol *sym;
1246
1247   fprintf (afile, "%s", iComments2);
1248   fprintf (afile, "; Public variables in this module\n");
1249   fprintf (afile, "%s", iComments2);
1250
1251   for (sym = setFirstItem (publics); sym;
1252        sym = setNextItem (publics))
1253     tfprintf (afile, "\t!global\n", sym->rname);
1254 }
1255
1256 /*-----------------------------------------------------------------*/
1257 /* printExterns - generates .global for externs                    */
1258 /*-----------------------------------------------------------------*/
1259 void 
1260 printExterns (FILE * afile)
1261 {
1262   symbol *sym;
1263
1264   fprintf (afile, "%s", iComments2);
1265   fprintf (afile, "; Externals used\n");
1266   fprintf (afile, "%s", iComments2);
1267
1268   for (sym = setFirstItem (externs); sym;
1269        sym = setNextItem (externs))
1270     tfprintf (afile, "\t!global\n", sym->rname);
1271 }
1272
1273 /*-----------------------------------------------------------------*/
1274 /* emitOverlay - will emit code for the overlay stuff              */
1275 /*-----------------------------------------------------------------*/
1276 static void 
1277 emitOverlay (FILE * afile)
1278 {
1279   set *ovrset;
1280
1281   if (!elementsInSet (ovrSetSets))
1282     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1283
1284   /* for each of the sets in the overlay segment do */
1285   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1286        ovrset = setNextItem (ovrSetSets))
1287     {
1288
1289       symbol *sym;
1290
1291       if (elementsInSet (ovrset))
1292         {
1293 #if 0
1294           /* this dummy area is used to fool the assembler
1295              otherwise the assembler will append each of these
1296              declarations into one chunk and will not overlay
1297              sad but true */
1298           fprintf (afile, "\t.area _DUMMY\n");
1299 #else
1300           /* not anymore since asmain.c:1.13 */
1301 #endif
1302           /* output the area informtion */
1303           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1304         }
1305
1306       for (sym = setFirstItem (ovrset); sym;
1307            sym = setNextItem (ovrset))
1308         {
1309
1310           /* if extern then add it to the publics tabledo nothing */
1311           if (IS_EXTERN (sym->etype))
1312             continue;
1313
1314           /* if allocation required check is needed
1315              then check if the symbol really requires
1316              allocation only for local variables */
1317           if (!IS_AGGREGATE (sym->type) &&
1318               !(sym->_isparm && !IS_REGPARM (sym->etype))
1319               && !sym->allocreq && sym->level)
1320             continue;
1321
1322           /* if global variable & not static or extern
1323              and addPublics allowed then add it to the public set */
1324           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1325               && !IS_STATIC (sym->etype))
1326             addSetHead (&publics, sym);
1327
1328           /* if extern then do nothing or is a function
1329              then do nothing */
1330           if (IS_FUNC (sym->type))
1331             continue;
1332
1333           /* print extra debug info if required */
1334           if (options.debug)
1335             {
1336               cdbSymbol (sym, cdbFile, FALSE, FALSE);
1337
1338               if (!sym->level)
1339                 {               /* global */
1340                   if (IS_STATIC (sym->etype))
1341                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1342                   else
1343                     fprintf (afile, "G$");      /* scope is global */
1344                 }
1345               else
1346                 /* symbol is local */
1347                 fprintf (afile, "L%s$",
1348                          (sym->localof ? sym->localof->name : "-null-"));
1349               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1350             }
1351
1352           /* if is has an absolute address then generate
1353              an equate for this no need to allocate space */
1354           if (SPEC_ABSA (sym->etype))
1355             {
1356
1357               if (options.debug)
1358                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1359
1360               fprintf (afile, "%s\t=\t0x%04x\n",
1361                        sym->rname,
1362                        SPEC_ADDR (sym->etype));
1363             }
1364           else {
1365               int size = getSize(sym->type);
1366
1367               if (size==0) {
1368                   werror(E_UNKNOWN_SIZE,sym->name);
1369               }       
1370               if (options.debug)
1371                   fprintf (afile, "==.\n");
1372               
1373               /* allocate space */
1374               tfprintf (afile, "!labeldef\n", sym->rname);
1375               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1376           }
1377           
1378         }
1379     }
1380 }
1381
1382 /*-----------------------------------------------------------------*/
1383 /* glue - the final glue that hold the whole thing together        */
1384 /*-----------------------------------------------------------------*/
1385 void 
1386 glue ()
1387 {
1388   FILE *vFile;
1389   FILE *asmFile;
1390   FILE *ovrFile = tempfile ();
1391
1392   addSetHead (&tmpfileSet, ovrFile);
1393   /* print the global struct definitions */
1394   if (options.debug)
1395     cdbStructBlock (0, cdbFile);
1396
1397   vFile = tempfile ();
1398   /* PENDING: this isnt the best place but it will do */
1399   if (port->general.glue_up_main)
1400     {
1401       /* create the interrupt vector table */
1402       createInterruptVect (vFile);
1403     }
1404
1405   addSetHead (&tmpfileSet, vFile);
1406
1407   /* emit code for the all the variables declared */
1408   emitMaps ();
1409   /* do the overlay segments */
1410   emitOverlay (ovrFile);
1411
1412   /* now put it all together into the assembler file */
1413   /* create the assembler file name */
1414
1415   if (!options.c1mode)
1416     {
1417       sprintf (scratchFileName, srcFileName);
1418       strcat (scratchFileName, port->assembler.file_ext);
1419     }
1420   else
1421     {
1422       strcpy (scratchFileName, options.out_name);
1423     }
1424
1425   if (!(asmFile = fopen (scratchFileName, "w")))
1426     {
1427       werror (E_FILE_OPEN_ERR, scratchFileName);
1428       exit (1);
1429     }
1430
1431   /* initial comments */
1432   initialComments (asmFile);
1433
1434   /* print module name */
1435   tfprintf (asmFile, "\t!module\n", moduleName);
1436   tfprintf (asmFile, "\t!fileprelude\n");
1437
1438   /* Let the port generate any global directives, etc. */
1439   if (port->genAssemblerPreamble)
1440     {
1441       port->genAssemblerPreamble (asmFile);
1442     }
1443
1444   /* print the global variables in this module */
1445   printPublics (asmFile);
1446   if (port->assembler.externGlobal)
1447     printExterns (asmFile);
1448
1449   /* copy the sfr segment */
1450   fprintf (asmFile, "%s", iComments2);
1451   fprintf (asmFile, "; special function registers\n");
1452   fprintf (asmFile, "%s", iComments2);
1453   copyFile (asmFile, sfr->oFile);
1454
1455   /* copy the sbit segment */
1456   fprintf (asmFile, "%s", iComments2);
1457   fprintf (asmFile, "; special function bits \n");
1458   fprintf (asmFile, "%s", iComments2);
1459   copyFile (asmFile, sfrbit->oFile);
1460
1461   /* copy the data segment */
1462   fprintf (asmFile, "%s", iComments2);
1463   fprintf (asmFile, "; internal ram data\n");
1464   fprintf (asmFile, "%s", iComments2);
1465   copyFile (asmFile, data->oFile);
1466
1467
1468   /* create the overlay segments */
1469   fprintf (asmFile, "%s", iComments2);
1470   fprintf (asmFile, "; overlayable items in internal ram \n");
1471   fprintf (asmFile, "%s", iComments2);
1472   copyFile (asmFile, ovrFile);
1473
1474   /* create the stack segment MOF */
1475   if (mainf && IFFUNC_HASBODY(mainf->type))
1476     {
1477       fprintf (asmFile, "%s", iComments2);
1478       fprintf (asmFile, "; Stack segment in internal ram \n");
1479       fprintf (asmFile, "%s", iComments2);
1480       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1481                "__start__stack:\n\t.ds\t1\n\n");
1482     }
1483
1484   /* create the idata segment */
1485   fprintf (asmFile, "%s", iComments2);
1486   fprintf (asmFile, "; indirectly addressable internal ram data\n");
1487   fprintf (asmFile, "%s", iComments2);
1488   copyFile (asmFile, idata->oFile);
1489
1490   /* copy the bit segment */
1491   fprintf (asmFile, "%s", iComments2);
1492   fprintf (asmFile, "; bit data\n");
1493   fprintf (asmFile, "%s", iComments2);
1494   copyFile (asmFile, bit->oFile);
1495
1496   /* if external stack then reserve space of it */
1497   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1498     {
1499       fprintf (asmFile, "%s", iComments2);
1500       fprintf (asmFile, "; external stack \n");
1501       fprintf (asmFile, "%s", iComments2);
1502       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1503       fprintf (asmFile, "\t.ds 256\n");
1504     }
1505
1506
1507   /* copy xtern ram data */
1508   fprintf (asmFile, "%s", iComments2);
1509   fprintf (asmFile, "; external ram data\n");
1510   fprintf (asmFile, "%s", iComments2);
1511   copyFile (asmFile, xdata->oFile);
1512
1513   /* copy xternal initialized ram data */
1514   fprintf (asmFile, "%s", iComments2);
1515   fprintf (asmFile, "; external initialized ram data\n");
1516   fprintf (asmFile, "%s", iComments2);
1517   copyFile (asmFile, xidata->oFile);
1518
1519   /* copy the interrupt vector table */
1520   if (mainf && IFFUNC_HASBODY(mainf->type))
1521     {
1522       fprintf (asmFile, "%s", iComments2);
1523       fprintf (asmFile, "; interrupt vector \n");
1524       fprintf (asmFile, "%s", iComments2);
1525       copyFile (asmFile, vFile);
1526     }
1527
1528   /* copy global & static initialisations */
1529   fprintf (asmFile, "%s", iComments2);
1530   fprintf (asmFile, "; global & static initialisations\n");
1531   fprintf (asmFile, "%s", iComments2);
1532
1533   /* Everywhere we generate a reference to the static_name area,
1534    * (which is currently only here), we immediately follow it with a
1535    * definition of the post_static_name area. This guarantees that
1536    * the post_static_name area will immediately follow the static_name
1537    * area.
1538    */
1539   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1540   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1541   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1542
1543   if (mainf && IFFUNC_HASBODY(mainf->type))
1544     {
1545       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1546       /* if external stack is specified then the
1547          higher order byte of the xdatalocation is
1548          going into P2 and the lower order going into
1549          spx */
1550       if (options.useXstack)
1551         {
1552           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1553                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1554           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1555                    (unsigned int) options.xdata_loc & 0xff);
1556         }
1557
1558       /* initialise the stack pointer */
1559       /* if the user specified a value then use it */
1560       if (options.stack_loc)
1561         fprintf (asmFile, "\tmov\tsp,#%d\n", options.stack_loc & 0xff);
1562       else
1563         /* no: we have to compute it */
1564       if (!options.stackOnData && maxRegBank <= 3)
1565         fprintf (asmFile, "\tmov\tsp,#%d\n", ((maxRegBank + 1) * 8) - 1);
1566       else
1567         fprintf (asmFile, "\tmov\tsp,#__start__stack\n");       /* MOF */
1568
1569       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1570       fprintf (asmFile, "\tmov\ta,dpl\n");
1571       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1572       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1573       fprintf (asmFile, "__sdcc_init_data:\n");
1574
1575       // if the port can copy the XINIT segment to XISEG
1576       if (port->genXINIT) {
1577         port->genXINIT(asmFile);
1578       }
1579
1580     }
1581   copyFile (asmFile, statsg->oFile);
1582
1583   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1584     {
1585       /* This code is generated in the post-static area.
1586        * This area is guaranteed to follow the static area
1587        * by the ugly shucking and jiving about 20 lines ago.
1588        */
1589       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1590       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1591     }
1592
1593   fprintf (asmFile,
1594            "%s"
1595            "; Home\n"
1596            "%s", iComments2, iComments2);
1597   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1598   copyFile (asmFile, home->oFile);
1599
1600   /* copy over code */
1601   fprintf (asmFile, "%s", iComments2);
1602   fprintf (asmFile, "; code\n");
1603   fprintf (asmFile, "%s", iComments2);
1604   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1605   if (mainf && IFFUNC_HASBODY(mainf->type))
1606     {
1607
1608       /* entry point @ start of CSEG */
1609       fprintf (asmFile, "__sdcc_program_startup:\n");
1610
1611       /* put in the call to main */
1612       fprintf (asmFile, "\tlcall\t_main\n");
1613       if (options.mainreturn)
1614         {
1615
1616           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1617           fprintf (asmFile, "\tret\n");
1618
1619         }
1620       else
1621         {
1622
1623           fprintf (asmFile, ";\treturn from main will lock up\n");
1624           fprintf (asmFile, "\tsjmp .\n");
1625         }
1626     }
1627   copyFile (asmFile, code->oFile);
1628
1629   fclose (asmFile);
1630   applyToSet (tmpfileSet, closeTmpFiles);
1631   applyToSet (tmpfileNameSet, rmTmpFiles);
1632 }
1633
1634 #if defined (__MINGW32__) || defined (__CYGWIN__) || defined (_MSC_VER)
1635 void
1636 rm_tmpfiles (void)
1637 {
1638   applyToSet (tmpfileSet, closeTmpFiles);
1639   applyToSet (tmpfileNameSet, rmTmpFiles);
1640 }
1641 #endif
1642
1643 /** Creates a temporary file name a'la tmpnam which avoids the bugs
1644     in cygwin wrt c:\tmp.
1645     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1646 */
1647 char *
1648 tempfilename (void)
1649 {
1650 #if !defined(_MSC_VER)
1651   const char *tmpdir = NULL;
1652   if (getenv ("TMP"))
1653     tmpdir = getenv ("TMP");
1654   else if (getenv ("TEMP"))
1655     tmpdir = getenv ("TEMP");
1656   else if (getenv ("TMPDIR"))
1657     tmpdir = getenv ("TMPDIR");
1658   if (tmpdir)
1659     {
1660       char *name = tempnam (tmpdir, "sdcc");
1661       if (name)
1662         {
1663           return name;
1664         }
1665     }
1666 #endif
1667   return tmpnam (NULL);
1668 }
1669
1670 /** Creates a temporary file a'la tmpfile which avoids the bugs
1671     in cygwin wrt c:\tmp.
1672     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1673 */
1674 FILE *
1675 tempfile (void)
1676 {
1677 #if !defined(_MSC_VER)
1678   const char *tmpdir = NULL;
1679   if (getenv ("TMP"))
1680     tmpdir = getenv ("TMP");
1681   else if (getenv ("TEMP"))
1682     tmpdir = getenv ("TEMP");
1683   else if (getenv ("TMPDIR"))
1684     tmpdir = getenv ("TMPDIR");
1685   if (tmpdir)
1686     {
1687       char *name = Safe_strdup( tempnam (tmpdir, "sdcc"));
1688       if (name)
1689         {
1690           FILE *fp = fopen (name, "w+b");
1691           if (fp)
1692             {
1693               addSetHead (&tmpfileNameSet, name);
1694             }
1695           return fp;
1696         }
1697       return NULL;
1698     }
1699 #endif
1700   return tmpfile ();
1701 }
1702