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