fixed bug #517082
[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 (IS_LITERAL(val->etype)) {
800     if (compareType(type,val->etype)==0) {
801       werror (E_INCOMPAT_TYPES);
802       printFromToType (val->type, type);
803     }
804     printIvalCharPtr (NULL, type, val, oFile);
805     return;
806   }
807
808   /* check the types   */
809   if ((dLvl = compareType (val->type, type->next)) <= 0)
810     {
811       tfprintf (oFile, "\t!dw !constword\n", 0);
812       return;
813     }
814
815   /* now generate the name */
816   if (!val->sym)
817     {
818       if (port->use_dw_for_init)
819         {
820           tfprintf (oFile, "\t!dws\n", val->name);
821         }
822       else
823         {
824           printPointerType (oFile, val->name);
825         }
826     }
827   else if (port->use_dw_for_init)
828     {
829       tfprintf (oFile, "\t!dws\n", val->sym->rname);
830     }
831   else
832     {
833       printPointerType (oFile, val->sym->rname);
834     }
835
836   return;
837 }
838
839 /*-----------------------------------------------------------------*/
840 /* printIvalCharPtr - generates initial values for character pointers */
841 /*-----------------------------------------------------------------*/
842 int 
843 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
844 {
845   int size = 0;
846
847   /* PENDING: this is _very_ mcs51 specific, including a magic
848      number...
849      It's also endin specific.
850    */
851   size = getSize (type);
852
853   if (val->name && strlen (val->name))
854     {
855       if (size == 1)            /* This appears to be Z80 specific?? */
856         {
857           tfprintf (oFile,
858                     "\t!dbs\n", val->name);
859         }
860       else if (size == FPTRSIZE)
861         {
862           if (port->use_dw_for_init)
863             {
864               tfprintf (oFile, "\t!dws\n", val->name);
865             }
866           else
867             {
868               printPointerType (oFile, val->name);
869             }
870         }
871       else if (size == GPTRSIZE)
872         {
873           int type;
874           if (IS_PTR (val->type)) {
875             type = DCL_TYPE (val->type);
876           } else {
877             type = PTR_TYPE (SPEC_OCLS (val->etype));
878           }
879           if (val->sym && val->sym->isstrlit) {
880             // this is a literal string
881             type=CPOINTER;
882           }
883           printGPointerType (oFile, val->name, sym->name, type);
884         }
885       else
886         {
887           fprintf (stderr, "*** internal error: unknown size in "
888                    "printIvalCharPtr.\n");
889         }
890     }
891   else
892     {
893       // these are literals assigned to pointers
894       switch (size)
895         {
896         case 1:
897           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
898           break;
899         case 2:
900           if (port->use_dw_for_init)
901             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
902           else
903             tfprintf (oFile, "\t.byte %s,%s\n",
904                       aopLiteral (val, 0), aopLiteral (val, 1));
905           break;
906         case 3:
907           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
908             // non-zero mcs51 generic pointer
909             werror (E_LITERAL_GENERIC);
910           }
911           fprintf (oFile, "\t.byte %s,%s,%s\n",
912                    aopLiteral (val, 0), 
913                    aopLiteral (val, 1),
914                    aopLiteral (val, 2));
915           break;
916         case 4:
917           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
918             // non-zero ds390 generic pointer
919             werror (E_LITERAL_GENERIC);
920           }
921           fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
922                    aopLiteral (val, 0), 
923                    aopLiteral (val, 1), 
924                    aopLiteral (val, 2),
925                    aopLiteral (val, 3));
926           break;
927         default:
928           assert (0);
929         }
930     }
931
932   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
933     addSet (&statsg->syms, val->sym);
934   }
935
936   return 1;
937 }
938
939 /*-----------------------------------------------------------------*/
940 /* printIvalPtr - generates initial value for pointers             */
941 /*-----------------------------------------------------------------*/
942 void 
943 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
944 {
945   value *val;
946   int size;
947
948   /* if deep then   */
949   if (ilist->type == INIT_DEEP)
950     ilist = ilist->init.deep;
951
952   /* function pointer     */
953   if (IS_FUNC (type->next))
954     {
955       printIvalFuncPtr (type, ilist, oFile);
956       return;
957     }
958
959   if (!(val = initPointer (ilist, type)))
960     return;
961
962   /* if character pointer */
963   if (IS_CHAR (type->next))
964     if (printIvalCharPtr (sym, type, val, oFile))
965       return;
966
967   /* check the type      */
968   if (compareType (type, val->type) == 0)
969     werror (W_INIT_WRONG);
970
971   /* if val is literal */
972   if (IS_LITERAL (val->etype))
973     {
974       switch (getSize (type))
975         {
976         case 1:
977           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
978           break;
979         case 2:
980           if (port->use_dw_for_init)
981             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
982           else
983             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
984           break;
985         case 3:
986           fprintf (oFile, "\t.byte %s,%s,#0x02\n",
987                    aopLiteral (val, 0), aopLiteral (val, 1));
988         }
989       return;
990     }
991
992
993   size = getSize (type);
994
995   if (size == 1)                /* Z80 specific?? */
996     {
997       tfprintf (oFile, "\t!dbs\n", val->name);
998     }
999   else if (size == FPTRSIZE)
1000     {
1001       if (port->use_dw_for_init) {
1002         tfprintf (oFile, "\t!dws\n", val->name);
1003       } else {
1004         printPointerType (oFile, val->name);
1005       }
1006     }
1007   else if (size == GPTRSIZE)
1008     {
1009       printGPointerType (oFile, val->name, sym->name,
1010                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1011                           PTR_TYPE (SPEC_OCLS (val->etype))));
1012     }
1013   return;
1014 }
1015
1016 /*-----------------------------------------------------------------*/
1017 /* printIval - generates code for initial value                    */
1018 /*-----------------------------------------------------------------*/
1019 void 
1020 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1021 {
1022   if (!ilist)
1023     return;
1024
1025   /* if structure then    */
1026   if (IS_STRUCT (type))
1027     {
1028       printIvalStruct (sym, type, ilist, oFile);
1029       return;
1030     }
1031
1032   /* if this is a pointer */
1033   if (IS_PTR (type))
1034     {
1035       printIvalPtr (sym, type, ilist, oFile);
1036       return;
1037     }
1038
1039   /* if this is an array   */
1040   if (IS_ARRAY (type))
1041     {
1042       printIvalArray (sym, type, ilist, oFile);
1043       return;
1044     }
1045
1046   /* if type is SPECIFIER */
1047   if (IS_SPEC (type))
1048     {
1049       printIvalType (sym, type, ilist, oFile);
1050       return;
1051     }
1052 }
1053
1054 /*-----------------------------------------------------------------*/
1055 /* emitStaticSeg - emitcode for the static segment                 */
1056 /*-----------------------------------------------------------------*/
1057 void 
1058 emitStaticSeg (memmap * map, FILE * out)
1059 {
1060   symbol *sym;
1061
1062   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1063
1064   /* for all variables in this segment do */
1065   for (sym = setFirstItem (map->syms); sym;
1066        sym = setNextItem (map->syms))
1067     {
1068
1069       /* if it is "extern" then do nothing */
1070       if (IS_EXTERN (sym->etype))
1071         continue;
1072
1073       /* if it is not static add it to the public
1074          table */
1075       if (!IS_STATIC (sym->etype))
1076         {
1077           addSetHead (&publics, sym);
1078         }
1079
1080       /* print extra debug info if required */
1081       if (options.debug) {
1082         cdbSymbol (sym, cdbFile, FALSE, FALSE);
1083         if (!sym->level)
1084           {                     /* global */
1085             if (IS_STATIC (sym->etype))
1086               fprintf (out, "F%s$", moduleName);        /* scope is file */
1087             else
1088               fprintf (out, "G$");      /* scope is global */
1089           }
1090         else
1091           /* symbol is local */
1092           fprintf (out, "L%s$",
1093                    (sym->localof ? sym->localof->name : "-null-"));
1094         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1095       }
1096       
1097       /* if it has an absolute address */
1098       if (SPEC_ABSA (sym->etype))
1099         {
1100           if (options.debug)
1101             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1102           
1103           fprintf (out, "%s\t=\t0x%04x\n",
1104                    sym->rname,
1105                    SPEC_ADDR (sym->etype));
1106         }
1107       else
1108         {
1109           if (options.debug)
1110             fprintf (out, " == .\n");
1111           
1112           /* if it has an initial value */
1113           if (sym->ival)
1114             {
1115               fprintf (out, "%s:\n", sym->rname);
1116               noAlloc++;
1117               resolveIvalSym (sym->ival);
1118               printIval (sym, sym->type, sym->ival, out);
1119               noAlloc--;
1120             }
1121           else {
1122               /* allocate space */
1123               int size = getSize (sym->type);
1124               
1125               if (size==0) {
1126                   werror(E_UNKNOWN_SIZE,sym->name);
1127               }
1128               fprintf (out, "%s:\n", sym->rname);
1129               /* special case for character strings */
1130               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1131                   SPEC_CVAL (sym->etype).v_char)
1132                   printChar (out,
1133                              SPEC_CVAL (sym->etype).v_char,
1134                              strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1135               else
1136                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1137             }
1138         }
1139     }
1140 }
1141
1142 /*-----------------------------------------------------------------*/
1143 /* emitMaps - emits the code for the data portion the code         */
1144 /*-----------------------------------------------------------------*/
1145 void 
1146 emitMaps ()
1147 {
1148   inInitMode++;
1149   /* no special considerations for the following
1150      data, idata & bit & xdata */
1151   emitRegularMap (data, TRUE, TRUE);
1152   emitRegularMap (idata, TRUE, TRUE);
1153   emitRegularMap (bit, TRUE, FALSE);
1154   emitRegularMap (xdata, TRUE, TRUE);
1155   if (port->genXINIT) {
1156     emitRegularMap (xidata, TRUE, TRUE);
1157   }
1158   emitRegularMap (sfr, FALSE, FALSE);
1159   emitRegularMap (sfrbit, FALSE, FALSE);
1160   emitRegularMap (home, TRUE, FALSE);
1161   emitRegularMap (code, TRUE, FALSE);
1162
1163   emitStaticSeg (statsg, code->oFile);
1164   if (port->genXINIT) {
1165     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1166     emitStaticSeg (xinit, code->oFile);
1167   }
1168   inInitMode--;
1169 }
1170
1171 /*-----------------------------------------------------------------*/
1172 /* flushStatics - flush all currently defined statics out to file  */
1173 /*  and delete.  Temporary function                                */
1174 /*-----------------------------------------------------------------*/
1175 void 
1176 flushStatics (void)
1177 {
1178   emitStaticSeg (statsg, codeOutFile);
1179   statsg->syms = NULL;
1180 }
1181
1182 /*-----------------------------------------------------------------*/
1183 /* createInterruptVect - creates the interrupt vector              */
1184 /*-----------------------------------------------------------------*/
1185 void 
1186 createInterruptVect (FILE * vFile)
1187 {
1188   unsigned i = 0;
1189   mainf = newSymbol ("main", 0);
1190   mainf->block = 0;
1191
1192   /* only if the main function exists */
1193   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1194     {
1195       if (!options.cc_only && !noAssemble)
1196         werror (E_NO_MAIN);
1197       return;
1198     }
1199
1200   /* if the main is only a prototype ie. no body then do nothing */
1201   if (!IFFUNC_HASBODY(mainf->type))
1202     {
1203       /* if ! compile only then main function should be present */
1204       if (!options.cc_only && !noAssemble)
1205         werror (E_NO_MAIN);
1206       return;
1207     }
1208
1209   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1210   fprintf (vFile, "__interrupt_vect:\n");
1211
1212
1213   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1214     {
1215       /* "generic" interrupt table header (if port doesn't specify one).
1216        * Look suspiciously like 8051 code to me...
1217        */
1218
1219       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1220
1221
1222       /* now for the other interrupts */
1223       for (; i < maxInterrupts; i++)
1224         {
1225           if (interrupts[i])
1226             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1227           else
1228             fprintf (vFile, "\treti\n\t.ds\t7\n");
1229         }
1230     }
1231 }
1232
1233 char *iComments1 =
1234 {
1235   ";--------------------------------------------------------\n"
1236   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1237
1238 char *iComments2 =
1239 {
1240   ";--------------------------------------------------------\n"};
1241
1242
1243 /*-----------------------------------------------------------------*/
1244 /* initialComments - puts in some initial comments                 */
1245 /*-----------------------------------------------------------------*/
1246 void 
1247 initialComments (FILE * afile)
1248 {
1249   time_t t;
1250   time (&t);
1251   fprintf (afile, "%s", iComments1);
1252   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1253   fprintf (afile, "%s", iComments2);
1254 }
1255
1256 /*-----------------------------------------------------------------*/
1257 /* printPublics - generates .global for publics                    */
1258 /*-----------------------------------------------------------------*/
1259 void 
1260 printPublics (FILE * afile)
1261 {
1262   symbol *sym;
1263
1264   fprintf (afile, "%s", iComments2);
1265   fprintf (afile, "; Public variables in this module\n");
1266   fprintf (afile, "%s", iComments2);
1267
1268   for (sym = setFirstItem (publics); sym;
1269        sym = setNextItem (publics))
1270     tfprintf (afile, "\t!global\n", sym->rname);
1271 }
1272
1273 /*-----------------------------------------------------------------*/
1274 /* printExterns - generates .global for externs                    */
1275 /*-----------------------------------------------------------------*/
1276 void 
1277 printExterns (FILE * afile)
1278 {
1279   symbol *sym;
1280
1281   fprintf (afile, "%s", iComments2);
1282   fprintf (afile, "; Externals used\n");
1283   fprintf (afile, "%s", iComments2);
1284
1285   for (sym = setFirstItem (externs); sym;
1286        sym = setNextItem (externs))
1287     tfprintf (afile, "\t!extern\n", sym->rname);
1288 }
1289
1290 /*-----------------------------------------------------------------*/
1291 /* emitOverlay - will emit code for the overlay stuff              */
1292 /*-----------------------------------------------------------------*/
1293 static void 
1294 emitOverlay (FILE * afile)
1295 {
1296   set *ovrset;
1297
1298   if (!elementsInSet (ovrSetSets))
1299     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1300
1301   /* for each of the sets in the overlay segment do */
1302   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1303        ovrset = setNextItem (ovrSetSets))
1304     {
1305
1306       symbol *sym;
1307
1308       if (elementsInSet (ovrset))
1309         {
1310           /* output the area informtion */
1311           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1312         }
1313
1314       for (sym = setFirstItem (ovrset); sym;
1315            sym = setNextItem (ovrset))
1316         {
1317           /* if extern then it is in the publics table: do nothing */
1318           if (IS_EXTERN (sym->etype))
1319             continue;
1320
1321           /* if allocation required check is needed
1322              then check if the symbol really requires
1323              allocation only for local variables */
1324           if (!IS_AGGREGATE (sym->type) &&
1325               !(sym->_isparm && !IS_REGPARM (sym->etype))
1326               && !sym->allocreq && sym->level)
1327             continue;
1328
1329           /* if global variable & not static or extern
1330              and addPublics allowed then add it to the public set */
1331           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1332               && !IS_STATIC (sym->etype))
1333             {
1334               addSetHead (&publics, sym);
1335             }
1336
1337           /* if extern then do nothing or is a function
1338              then do nothing */
1339           if (IS_FUNC (sym->type))
1340             continue;
1341
1342           /* print extra debug info if required */
1343           if (options.debug)
1344             {
1345               cdbSymbol (sym, cdbFile, FALSE, FALSE);
1346
1347               if (!sym->level)
1348                 {               /* global */
1349                   if (IS_STATIC (sym->etype))
1350                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1351                   else
1352                     fprintf (afile, "G$");      /* scope is global */
1353                 }
1354               else
1355                 /* symbol is local */
1356                 fprintf (afile, "L%s$",
1357                          (sym->localof ? sym->localof->name : "-null-"));
1358               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1359             }
1360
1361           /* if is has an absolute address then generate
1362              an equate for this no need to allocate space */
1363           if (SPEC_ABSA (sym->etype))
1364             {
1365
1366               if (options.debug)
1367                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1368
1369               fprintf (afile, "%s\t=\t0x%04x\n",
1370                        sym->rname,
1371                        SPEC_ADDR (sym->etype));
1372             }
1373           else {
1374               int size = getSize(sym->type);
1375
1376               if (size==0) {
1377                   werror(E_UNKNOWN_SIZE,sym->name);
1378               }       
1379               if (options.debug)
1380                   fprintf (afile, "==.\n");
1381               
1382               /* allocate space */
1383               tfprintf (afile, "!labeldef\n", sym->rname);
1384               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1385           }
1386           
1387         }
1388     }
1389 }
1390
1391 /*-----------------------------------------------------------------*/
1392 /* glue - the final glue that hold the whole thing together        */
1393 /*-----------------------------------------------------------------*/
1394 void 
1395 glue ()
1396 {
1397   FILE *vFile;
1398   FILE *asmFile;
1399   FILE *ovrFile = tempfile ();
1400
1401   addSetHead (&tmpfileSet, ovrFile);
1402   /* print the global struct definitions */
1403   if (options.debug)
1404     cdbStructBlock (0, cdbFile);
1405
1406   vFile = tempfile ();
1407   /* PENDING: this isnt the best place but it will do */
1408   if (port->general.glue_up_main)
1409     {
1410       /* create the interrupt vector table */
1411       createInterruptVect (vFile);
1412     }
1413
1414   addSetHead (&tmpfileSet, vFile);
1415
1416   /* emit code for the all the variables declared */
1417   emitMaps ();
1418   /* do the overlay segments */
1419   emitOverlay (ovrFile);
1420
1421   /* now put it all together into the assembler file */
1422   /* create the assembler file name */
1423
1424   if (!options.c1mode)
1425     {
1426       sprintf (scratchFileName, srcFileName);
1427       strcat (scratchFileName, port->assembler.file_ext);
1428     }
1429   else
1430     {
1431       strcpy (scratchFileName, options.out_name);
1432     }
1433
1434   if (!(asmFile = fopen (scratchFileName, "w")))
1435     {
1436       werror (E_FILE_OPEN_ERR, scratchFileName);
1437       exit (1);
1438     }
1439
1440   /* initial comments */
1441   initialComments (asmFile);
1442
1443   /* print module name */
1444   tfprintf (asmFile, "\t!module\n", moduleName);
1445   tfprintf (asmFile, "\t!fileprelude\n");
1446
1447   /* Let the port generate any global directives, etc. */
1448   if (port->genAssemblerPreamble)
1449     {
1450       port->genAssemblerPreamble (asmFile);
1451     }
1452
1453   /* print the global variables in this module */
1454   printPublics (asmFile);
1455   if (port->assembler.externGlobal)
1456     printExterns (asmFile);
1457
1458   /* copy the sfr segment */
1459   fprintf (asmFile, "%s", iComments2);
1460   fprintf (asmFile, "; special function registers\n");
1461   fprintf (asmFile, "%s", iComments2);
1462   copyFile (asmFile, sfr->oFile);
1463
1464   /* copy the sbit segment */
1465   fprintf (asmFile, "%s", iComments2);
1466   fprintf (asmFile, "; special function bits \n");
1467   fprintf (asmFile, "%s", iComments2);
1468   copyFile (asmFile, sfrbit->oFile);
1469
1470   /* copy the data segment */
1471   fprintf (asmFile, "%s", iComments2);
1472   fprintf (asmFile, "; internal ram data\n");
1473   fprintf (asmFile, "%s", iComments2);
1474   copyFile (asmFile, data->oFile);
1475
1476
1477   /* create the overlay segments */
1478   if (overlay) {
1479     fprintf (asmFile, "%s", iComments2);
1480     fprintf (asmFile, "; overlayable items in internal ram \n");
1481     fprintf (asmFile, "%s", iComments2);
1482     copyFile (asmFile, ovrFile);
1483   }
1484
1485   /* create the stack segment MOF */
1486   if (mainf && IFFUNC_HASBODY(mainf->type))
1487     {
1488       fprintf (asmFile, "%s", iComments2);
1489       fprintf (asmFile, "; Stack segment in internal ram \n");
1490       fprintf (asmFile, "%s", iComments2);
1491       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1492                "__start__stack:\n\t.ds\t1\n\n");
1493     }
1494
1495   /* create the idata segment */
1496   if (idata) {
1497     fprintf (asmFile, "%s", iComments2);
1498     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1499     fprintf (asmFile, "%s", iComments2);
1500     copyFile (asmFile, idata->oFile);
1501   }
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