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