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