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