* src/SDCCglue.c (printChar): fixed bug #973350, patch provided by Phuah Yee Keat...
[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 #include <fcntl.h>
30 #include <sys/stat.h>
31
32 #ifdef _WIN32
33 #include <io.h>
34 #else
35 #include <unistd.h>
36 #endif
37
38 symbol *interrupts[INTNO_MAX+1];
39
40 void printIval (symbol *, sym_link *, initList *, FILE *);
41 set *publics = NULL;            /* public variables */
42 set *externs = NULL;            /* Varibles that are declared as extern */
43
44 /* TODO: this should be configurable (DS803C90 uses more than 6) */
45 unsigned maxInterrupts = 6;
46 int allocInfo = 1;
47 symbol *mainf;
48 set *pipeSet = NULL;            /* set of pipes */
49 set *tmpfileSet = NULL;         /* set of tmp file created by the compiler */
50 set *tmpfileNameSet = NULL;     /* All are unlinked at close. */
51
52 /*-----------------------------------------------------------------*/
53 /* closePipes - closes all pipes created by the compiler           */
54 /*-----------------------------------------------------------------*/
55 DEFSETFUNC (closePipes)
56 {
57   FILE *pfile = item;
58   int ret;
59
60   if (pfile) {
61     ret = pclose (pfile);
62     assert(ret != -1);
63   }
64
65   return 0;
66 }
67
68 /*-----------------------------------------------------------------*/
69 /* closeTmpFiles - closes all tmp files created by the compiler    */
70 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
71 /*-----------------------------------------------------------------*/
72 DEFSETFUNC (closeTmpFiles)
73 {
74   FILE *tfile = item;
75   int ret;
76
77   if (tfile) {
78     ret = fclose (tfile);
79     assert(ret == 0);
80   }
81
82   return 0;
83 }
84
85 /*-----------------------------------------------------------------*/
86 /* rmTmpFiles - unlinks all tmp files created by the compiler      */
87 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
88 /*-----------------------------------------------------------------*/
89 DEFSETFUNC (rmTmpFiles)
90 {
91   char *name = item;
92   int ret;
93
94   if (name) {
95       ret = unlink (name);
96       assert(ret == 0);
97       Safe_free (name);
98   }
99
100   return 0;
101 }
102
103 /*-----------------------------------------------------------------*/
104 /* rm_tmpfiles - close and remove temporary files and delete sets  */
105 /*-----------------------------------------------------------------*/
106 void
107 rm_tmpfiles (void)
108 {
109   /* close temporary files */
110   applyToSet (pipeSet, closePipes);
111   /* close temporary files */
112   deleteSet (&pipeSet);
113
114   applyToSet (tmpfileSet, closeTmpFiles);
115   /* remove temporary files */
116   applyToSet (tmpfileNameSet, rmTmpFiles);
117   /* delete temorary file sets */
118   deleteSet (&tmpfileSet);
119   deleteSet (&tmpfileNameSet);
120 }
121
122 /*-----------------------------------------------------------------*/
123 /* copyFile - copies source file to destination file               */
124 /*-----------------------------------------------------------------*/
125 void 
126 copyFile (FILE * dest, FILE * src)
127 {
128   int ch;
129
130   rewind (src);
131   while (!feof (src))
132     if ((ch = fgetc (src)) != EOF)
133       fputc (ch, dest);
134 }
135
136 char *
137 aopLiteralLong (value * val, int offset, int size)
138 {
139   union {
140     float f;
141     unsigned char c[4];
142   }
143   fl;
144
145   if (!val) {
146     // assuming we have been warned before
147     val=constVal("0");
148   }
149
150   /* if it is a float then it gets tricky */
151   /* otherwise it is fairly simple */
152   if (!IS_FLOAT (val->type)) {
153     unsigned long v = (unsigned long) floatFromVal (val);
154
155     v >>= (offset * 8);
156     switch (size) {
157     case 1:
158       tsprintf (buffer, sizeof(buffer), 
159           "!immedbyte", (unsigned int) v & 0xff);
160       break;
161     case 2:
162       tsprintf (buffer, sizeof(buffer), 
163           "!immedword", (unsigned int) v & 0xffff);
164       break;
165     default:
166       /* Hmm.  Too big for now. */
167       assert (0);
168     }
169     return Safe_strdup (buffer);
170   }
171
172   /* PENDING: For now size must be 1 */
173   assert (size == 1);
174
175   /* it is type float */
176   fl.f = (float) floatFromVal (val);
177 #ifdef WORDS_BIGENDIAN
178   tsprintf (buffer, sizeof(buffer), 
179       "!immedbyte", fl.c[3 - offset]);
180 #else
181   tsprintf (buffer, sizeof(buffer), 
182       "!immedbyte", fl.c[offset]);
183 #endif
184   return Safe_strdup (buffer);
185 }
186
187 /*-----------------------------------------------------------------*/
188 /* aopLiteral - string from a literal value                        */
189 /*-----------------------------------------------------------------*/
190 char *
191 aopLiteral (value * val, int offset)
192 {
193   return aopLiteralLong (val, offset, 1);
194 }
195
196 /*-----------------------------------------------------------------*/
197 /* emitRegularMap - emit code for maps with no special cases       */
198 /*-----------------------------------------------------------------*/
199 static void 
200 emitRegularMap (memmap * map, bool addPublics, bool arFlag)
201 {
202   symbol *sym;
203   ast *ival = NULL;
204
205   if (!map)
206     return;
207
208   if (addPublics)
209     {
210       /* PENDING: special case here - should remove */
211       if (!strcmp (map->sname, CODE_NAME))
212         tfprintf (map->oFile, "\t!areacode\n", map->sname);
213       else if (!strcmp (map->sname, DATA_NAME))
214         tfprintf (map->oFile, "\t!areadata\n", map->sname);
215       else if (!strcmp (map->sname, HOME_NAME))
216         tfprintf (map->oFile, "\t!areahome\n", map->sname);
217       else
218         tfprintf (map->oFile, "\t!area\n", map->sname);
219     }
220  
221   for (sym = setFirstItem (map->syms); sym;
222        sym = setNextItem (map->syms))
223     {
224       symbol *newSym=NULL;
225
226       /* if extern then add it into the extern list */
227       if (IS_EXTERN (sym->etype))
228         {
229           addSetHead (&externs, sym);
230           continue;
231         }
232
233       /* if allocation required check is needed
234          then check if the symbol really requires
235          allocation only for local variables */
236
237       if (arFlag && !IS_AGGREGATE (sym->type) &&
238           !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
239           !sym->allocreq && sym->level)
240         continue;
241
242       /* for bitvar locals and parameters */
243       if (!arFlag && !sym->allocreq && sym->level 
244           && !SPEC_ABSA (sym->etype)) {
245         continue;
246       }
247
248       /* if global variable & not static or extern
249          and addPublics allowed then add it to the public set */
250       if ((sym->level == 0 ||
251            (sym->_isparm && !IS_REGPARM (sym->etype))) &&
252           addPublics &&
253           !IS_STATIC (sym->etype) &&
254           (IS_FUNC(sym->type) ? (sym->used || IFFUNC_HASBODY(sym->type)) : 1))
255         {
256           addSetHead (&publics, sym);
257         }
258
259       /* if extern then do nothing or is a function
260          then do nothing */
261       if (IS_FUNC (sym->type) && !(sym->isitmp))
262         continue;
263
264       /* print extra debug info if required */
265       if (options.debug)
266         {
267           if (!sym->level) /* global */
268             {
269               if (IS_STATIC (sym->etype))
270                 fprintf (map->oFile, "F%s$", moduleName); /* scope is file */
271               else
272                 fprintf (map->oFile, "G$");     /* scope is global */
273             }
274           else
275             {
276               /* symbol is local */
277               fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-"));
278             }
279           fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block);
280         }
281       
282       /* if it has an initial value then do it only if
283          it is a global variable */
284       if (sym->ival && sym->level == 0) {
285         if (SPEC_OCLS(sym->etype)==xidata) {
286           /* create a new "XINIT (CODE)" symbol, that will be emitted later
287              in the static seg */
288           newSym=copySymbol (sym);
289           SPEC_OCLS(newSym->etype)=xinit;
290           SNPRINTF (newSym->name, sizeof(newSym->name), "__xinit_%s", sym->name);
291           SNPRINTF (newSym->rname, sizeof(newSym->rname), "__xinit_%s", sym->rname);
292           if (IS_SPEC (newSym->type))
293             SPEC_CONST (newSym->type) = 1;
294           else
295             DCL_PTR_CONST (newSym->type) = 1;
296           SPEC_STAT(newSym->etype)=1;
297           resolveIvalSym(newSym->ival, newSym->type);
298
299           // add it to the "XINIT (CODE)" segment
300           addSet(&xinit->syms, newSym);
301
302           if (!SPEC_ABSA (sym->etype))
303             {
304               FILE *tmpFile = tempfile ();
305               addSetHead (&tmpfileSet, tmpFile);
306               // before allocation we must parse the sym->ival tree
307               // but without actually generating initialization code
308               noAlloc++;
309               resolveIvalSym (sym->ival, sym->type);
310               printIval (sym, sym->type, sym->ival, tmpFile);
311               noAlloc--;
312             }
313
314           sym->ival=NULL;
315         } else {
316           if (IS_AGGREGATE (sym->type)) {
317             ival = initAggregates (sym, sym->ival, NULL);
318           } else {
319             if (getNelements(sym->type, sym->ival)>1) {
320               werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "scalar", 
321                       sym->name);
322             }
323             ival = newNode ('=', newAst_VALUE (symbolVal (sym)),
324                             decorateType (resolveSymbols (list2expr (sym->ival)), RESULT_CHECK));
325           }
326           codeOutFile = statsg->oFile;
327
328           if (ival) {
329             // set ival's lineno to where the symbol was defined
330             setAstLineno (ival, lineno=sym->lineDef);
331             // check if this is not a constant expression
332             if (!constExprTree(ival)) {
333               werror (E_CONST_EXPECTED, "found expression");
334               // but try to do it anyway
335             }
336             allocInfo = 0;
337             if (!astErrors(ival))
338               eBBlockFromiCode (iCodeFromAst (ival));
339             allocInfo = 1;
340           }
341         }         
342         sym->ival = NULL;
343       }
344
345       /* if it has an absolute address then generate
346          an equate for this no need to allocate space */
347       if (SPEC_ABSA (sym->etype))
348         {
349           char *equ="=";
350           if (options.debug) {
351             fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
352           }
353           if (TARGET_IS_XA51) {
354             if (map==sfr) {
355               equ="sfr";
356             } else if (map==bit || map==sfrbit) {
357               equ="bit";
358             }
359           }
360           fprintf (map->oFile, "%s\t%s\t0x%04x\n",
361                    sym->rname, equ,
362                    SPEC_ADDR (sym->etype));
363         }
364       else {
365         int size = getAllocSize (sym->type);
366         if (size==0) {
367           werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE, sym->name);
368         }
369         /* allocate space */
370         if (options.debug) {
371           fprintf (map->oFile, "==.\n");
372         }
373         if (IS_STATIC (sym->etype))
374           tfprintf (map->oFile, "!slabeldef\n", sym->rname);
375         else
376           tfprintf (map->oFile, "!labeldef\n", sym->rname);           
377         tfprintf (map->oFile, "\t!ds\n", 
378                   (unsigned int)  size & 0xffff);
379       }
380     }
381 }
382
383 /*-----------------------------------------------------------------*/
384 /* initPointer - pointer initialization code massaging             */
385 /*-----------------------------------------------------------------*/
386 value *
387 initPointer (initList * ilist, sym_link *toType)
388 {
389   value *val;
390   ast *expr;
391
392   if (!ilist) {
393       return valCastLiteral(toType, 0.0);
394   }
395
396   expr = list2expr (ilist);
397   
398   if (!expr)
399     goto wrong;
400   
401   /* try it the old way first */
402   if ((val = constExprValue (expr, FALSE)))
403     return val;
404   
405   /* ( ptr + constant ) */
406   if (IS_AST_OP (expr) &&
407       (expr->opval.op == '+' || expr->opval.op == '-') &&
408       IS_AST_SYM_VALUE (expr->left) &&
409       (IS_ARRAY(expr->left->ftype) || IS_PTR(expr->left->ftype)) &&
410       compareType(toType, expr->left->ftype) &&
411       IS_AST_LIT_VALUE (expr->right)) {
412     return valForCastAggr (expr->left, expr->left->ftype,
413                            expr->right,
414                            expr->opval.op);
415   }
416   
417   /* (char *)&a */
418   if (IS_AST_OP(expr) && expr->opval.op==CAST &&
419       IS_AST_OP(expr->right) && expr->right->opval.op=='&') {
420     if (compareType(toType, expr->left->ftype)!=1) {
421       werror (W_INIT_WRONG);
422       printFromToType(expr->left->ftype, toType);
423     }
424     // skip the cast ???
425     expr=expr->right;
426   }
427
428   /* no then we have to do these cludgy checks */
429   /* pointers can be initialized with address of
430      a variable or address of an array element */
431   if (IS_AST_OP (expr) && expr->opval.op == '&') {
432     /* address of symbol */
433     if (IS_AST_SYM_VALUE (expr->left)) {
434       val = copyValue (AST_VALUE (expr->left));
435       val->type = newLink (DECLARATOR);
436       if (SPEC_SCLS (expr->left->etype) == S_CODE) {
437         DCL_TYPE (val->type) = CPOINTER;
438         DCL_PTR_CONST (val->type) = port->mem.code_ro;
439       }
440       else if (SPEC_SCLS (expr->left->etype) == S_XDATA)
441         DCL_TYPE (val->type) = FPOINTER;
442       else if (SPEC_SCLS (expr->left->etype) == S_XSTACK)
443         DCL_TYPE (val->type) = PPOINTER;
444       else if (SPEC_SCLS (expr->left->etype) == S_IDATA)
445         DCL_TYPE (val->type) = IPOINTER;
446       else if (SPEC_SCLS (expr->left->etype) == S_EEPROM)
447         DCL_TYPE (val->type) = EEPPOINTER;
448       else
449         DCL_TYPE (val->type) = POINTER;
450       val->type->next = expr->left->ftype;
451       val->etype = getSpec (val->type);
452       return val;
453     }
454
455     /* if address of indexed array */
456     if (IS_AST_OP (expr->left) && expr->left->opval.op == '[')
457       return valForArray (expr->left);
458
459     /* if address of structure element then
460        case 1. a.b ; */
461     if (IS_AST_OP (expr->left) &&
462         expr->left->opval.op == '.') {
463       return valForStructElem (expr->left->left,
464                                expr->left->right);
465     }
466
467     /* case 2. (&a)->b ;
468        (&some_struct)->element */
469     if (IS_AST_OP (expr->left) &&
470         expr->left->opval.op == PTR_OP &&
471         IS_ADDRESS_OF_OP (expr->left->left)) {
472       return valForStructElem (expr->left->left->left,
473                                expr->left->right);
474     }
475   }
476   /* case 3. (((char *) &a) +/- constant) */
477   if (IS_AST_OP (expr) &&
478       (expr->opval.op == '+' || expr->opval.op == '-') &&
479       IS_AST_OP (expr->left) && expr->left->opval.op == CAST &&
480       IS_AST_OP (expr->left->right) &&
481       expr->left->right->opval.op == '&' &&
482       IS_AST_LIT_VALUE (expr->right)) {
483
484     return valForCastAggr (expr->left->right->left,
485                            expr->left->left->opval.lnk,
486                            expr->right, expr->opval.op);
487
488   }
489   /* case 4. (char *)(array type) */
490   if (IS_CAST_OP(expr) && IS_AST_SYM_VALUE (expr->right) &&
491       IS_ARRAY(expr->right->ftype)) {
492
493     val = copyValue (AST_VALUE (expr->right));
494     val->type = newLink (DECLARATOR);
495     if (SPEC_SCLS (expr->right->etype) == S_CODE) {
496       DCL_TYPE (val->type) = CPOINTER;
497       DCL_PTR_CONST (val->type) = port->mem.code_ro;
498     }
499     else if (SPEC_SCLS (expr->right->etype) == S_XDATA)
500       DCL_TYPE (val->type) = FPOINTER;
501     else if (SPEC_SCLS (expr->right->etype) == S_XSTACK)
502       DCL_TYPE (val->type) = PPOINTER;
503     else if (SPEC_SCLS (expr->right->etype) == S_IDATA)
504       DCL_TYPE (val->type) = IPOINTER;
505     else if (SPEC_SCLS (expr->right->etype) == S_EEPROM)
506       DCL_TYPE (val->type) = EEPPOINTER;
507     else
508       DCL_TYPE (val->type) = POINTER;
509     val->type->next = expr->right->ftype->next;
510     val->etype = getSpec (val->type);
511     return val;
512   }
513  wrong:
514   if (expr)
515     werrorfl (expr->filename, expr->lineno, E_INCOMPAT_PTYPES);
516   else
517     werror (E_INCOMPAT_PTYPES);
518   return NULL;
519
520 }
521
522 /*-----------------------------------------------------------------*/
523 /* printChar - formats and prints a characater string with DB      */
524 /*-----------------------------------------------------------------*/
525 void 
526 printChar (FILE * ofile, char *s, int plen)
527 {
528   int i;
529   int len = plen;
530   int pplen = 0;
531   char buf[100];
532   char *p = buf;
533
534   while (len && pplen < plen)
535     {
536       i = 60;
537       while (i && pplen < plen)
538         {
539           if (*s < ' ' || *s == '\"' || *s=='\\')
540             {
541               *p = '\0';
542               if (p != buf)
543                 tfprintf (ofile, "\t!ascii\n", buf);
544               tfprintf (ofile, "\t!db !constbyte\n", (unsigned char)*s);
545               p = buf;
546             }
547           else
548             {
549               *p = *s;
550               p++;
551             }
552           s++;
553           pplen++;
554           i--;
555         }
556       if (p != buf)
557         {
558           *p = '\0';
559           tfprintf (ofile, "\t!ascii\n", buf);
560           p = buf;
561         }
562
563       if (len > 60)
564         len -= 60;
565       else
566         len = 0;
567     }
568   while (pplen < plen)
569     {
570       tfprintf (ofile, "\t!db !constbyte\n", 0);
571       pplen++;
572     }
573 }
574
575 /*-----------------------------------------------------------------*/
576 /* return the generic pointer high byte for a given pointer type.  */
577 /*-----------------------------------------------------------------*/
578 int 
579 pointerTypeToGPByte (const int p_type, const char *iname, const char *oname)
580 {
581   switch (p_type)
582     {
583     case IPOINTER:
584     case POINTER:
585       return GPTYPE_NEAR;
586     case GPOINTER:
587       werror (E_CANNOT_USE_GENERIC_POINTER, 
588               iname ? iname : "<null>", 
589               oname ? oname : "<null>");
590       exit (1);
591     case FPOINTER:
592       return GPTYPE_FAR;
593     case CPOINTER:
594       return GPTYPE_CODE;
595     case PPOINTER:
596       return GPTYPE_XSTACK;
597     default:
598       fprintf (stderr, "*** internal error: unknown pointer type %d in GPByte.\n",
599                p_type);
600       break;
601     }
602   return -1;
603 }
604
605
606 /*-----------------------------------------------------------------*/
607 /* printPointerType - generates ival for pointer type              */
608 /*-----------------------------------------------------------------*/
609 void 
610 _printPointerType (FILE * oFile, const char *name)
611 {
612   if (options.model == MODEL_FLAT24)
613     {
614       if (port->little_endian)
615         fprintf (oFile, "\t.byte %s,(%s >> 8),(%s >> 16)", name, name, name);
616       else
617         fprintf (oFile, "\t.byte (%s >> 16),(%s >> 8),%s", name, name, name);
618     }
619   else
620     {
621       if (port->little_endian)
622         fprintf (oFile, "\t.byte %s,(%s >> 8)", name, name);
623       else
624         fprintf (oFile, "\t.byte (%s >> 8),%s", name, name);
625     }
626 }
627
628 /*-----------------------------------------------------------------*/
629 /* printPointerType - generates ival for pointer type              */
630 /*-----------------------------------------------------------------*/
631 void 
632 printPointerType (FILE * oFile, const char *name)
633 {
634   _printPointerType (oFile, name);
635   fprintf (oFile, "\n");
636 }
637
638 /*-----------------------------------------------------------------*/
639 /* printGPointerType - generates ival for generic pointer type     */
640 /*-----------------------------------------------------------------*/
641 void 
642 printGPointerType (FILE * oFile, const char *iname, const char *oname,
643                    const unsigned int type)
644 {
645   _printPointerType (oFile, iname);
646   fprintf (oFile, ",#0x%02x\n", pointerTypeToGPByte (type, iname, oname));
647 }
648
649 /*-----------------------------------------------------------------*/
650 /* printIvalType - generates ival for int/char                     */
651 /*-----------------------------------------------------------------*/
652 void 
653 printIvalType (symbol *sym, sym_link * type, initList * ilist, FILE * oFile)
654 {
655   value *val;
656
657   /* if initList is deep */
658   if (ilist && (ilist->type == INIT_DEEP))
659     ilist = ilist->init.deep;
660
661   if (!(val = list2val (ilist))) {
662     // assuming a warning has been thrown
663     val=constVal("0");
664   }
665
666   if (val->type != type) {
667     val = valCastLiteral(type, floatFromVal(val));
668   }
669   
670   switch (getSize (type)) {
671   case 1:
672     if (!val)
673       tfprintf (oFile, "\t!db !constbyte\n", 0);
674     else
675       tfprintf (oFile, "\t!dbs\n",
676                 aopLiteral (val, 0));
677     break;
678
679   case 2:
680     if (port->use_dw_for_init)
681       tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
682     else if (port->little_endian)
683       fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
684     else
685       fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 1), aopLiteral (val, 0));
686     break;
687   case 4:
688     if (!val) {
689       tfprintf (oFile, "\t!dw !constword\n", 0);
690       tfprintf (oFile, "\t!dw !constword\n", 0);
691     }
692     else if (port->little_endian) {
693       fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
694                aopLiteral (val, 0), aopLiteral (val, 1),
695                aopLiteral (val, 2), aopLiteral (val, 3));
696     }
697     else {
698       fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
699                aopLiteral (val, 3), aopLiteral (val, 2),
700                aopLiteral (val, 1), aopLiteral (val, 0));
701     }
702     break;
703   }
704 }
705
706 /*-----------------------------------------------------------------*/
707 /* printIvalBitFields - generate initializer for bitfields         */
708 /*-----------------------------------------------------------------*/
709 void printIvalBitFields(symbol **sym, initList **ilist, FILE * oFile)
710 {
711   value *val ;
712   symbol *lsym = *sym;
713   initList *lilist = *ilist ;
714   unsigned long ival = 0;
715   int size =0;
716
717   
718   do {
719     unsigned long i;
720     val = list2val(lilist);
721     if (size) {
722       if (SPEC_BLEN(lsym->etype) > 8) {
723         size += ((SPEC_BLEN (lsym->etype) / 8) + 
724                  (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
725       }
726     } else {
727       size = ((SPEC_BLEN (lsym->etype) / 8) + 
728               (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
729     }
730     i = (unsigned long)floatFromVal(val);
731     i <<= SPEC_BSTR (lsym->etype);
732     ival |= i;
733     if (! ( lsym->next &&
734           (IS_BITFIELD(lsym->next->type)) &&
735           (SPEC_BSTR(lsym->next->etype)))) break;
736     lsym = lsym->next;
737     lilist = lilist->next;
738   } while (1);
739   switch (size) {
740   case 1:
741     tfprintf (oFile, "\t!db !constbyte\n",ival);
742     break;
743
744   case 2:
745     tfprintf (oFile, "\t!dw !constword\n",ival);
746     break;
747   case 4: /* EEP: why is this db and not dw? */
748     tfprintf (oFile, "\t!db  !constword,!constword\n",
749              (ival >> 8) & 0xffff, (ival & 0xffff));
750     break;
751   }
752   *sym = lsym;
753   *ilist = lilist;
754 }
755
756 /*-----------------------------------------------------------------*/
757 /* printIvalStruct - generates initial value for structures        */
758 /*-----------------------------------------------------------------*/
759 void 
760 printIvalStruct (symbol * sym, sym_link * type,
761                  initList * ilist, FILE * oFile)
762 {
763   symbol *sflds;
764   initList *iloop = NULL;
765
766   sflds = SPEC_STRUCT (type)->fields;
767
768   if (ilist) {
769     if (ilist->type != INIT_DEEP) {
770       werrorfl (sym->fileDef, sym->lineDef, E_INIT_STRUCT, sym->name);
771       return;
772     }
773
774     iloop = ilist->init.deep;
775   }
776
777   for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) {
778     if (IS_BITFIELD(sflds->type)) {
779       printIvalBitFields(&sflds,&iloop,oFile);
780     } else {
781       printIval (sym, sflds->type, iloop, oFile);
782     }
783   }
784   if (iloop) {
785     werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "struct", sym->name);
786   }
787   return;
788 }
789
790 /*-----------------------------------------------------------------*/
791 /* printIvalChar - generates initital value for character array    */
792 /*-----------------------------------------------------------------*/
793 int 
794 printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s)
795 {
796   value *val;
797
798   if (!s)
799     {
800
801       val = list2val (ilist);
802       /* if the value is a character string  */
803       if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
804         {
805           if (!DCL_ELEM (type))
806             DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1;
807
808           printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type));
809
810           return 1;
811         }
812       else
813         return 0;
814     }
815   else
816     printChar (oFile, s, strlen (s) + 1);
817   return 1;
818 }
819
820 /*-----------------------------------------------------------------*/
821 /* printIvalArray - generates code for array initialization        */
822 /*-----------------------------------------------------------------*/
823 void
824 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
825                 FILE * oFile)
826 {
827   initList *iloop;
828   int size = 0;
829
830   if (ilist) {
831     /* take care of the special   case  */
832     /* array of characters can be init  */
833     /* by a string                      */
834     if (IS_CHAR (type->next)) {
835       if (!IS_LITERAL(list2val(ilist)->etype)) {
836         werrorfl (ilist->filename, ilist->lineno, E_CONST_EXPECTED);
837         return;
838       }
839       if (printIvalChar (type,
840                          (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
841                          oFile, SPEC_CVAL (sym->etype).v_char))
842         return;
843     }
844     /* not the special case             */
845     if (ilist->type != INIT_DEEP) {
846       werrorfl (ilist->filename, ilist->lineno, E_INIT_STRUCT, sym->name);
847       return;
848     }
849
850     for (iloop=ilist->init.deep; iloop; iloop=iloop->next) {
851       printIval (sym, type->next, iloop, oFile);
852       
853       if ((++size > DCL_ELEM(type)) && DCL_ELEM(type)) {
854         werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "array", sym->name);
855         break;
856       }
857     }
858   }
859   
860   if (DCL_ELEM(type)) {
861     // pad with zeros if needed
862     if (size<DCL_ELEM(type)) {
863       size = (DCL_ELEM(type) - size) * getSize(type->next);
864       while (size--) {
865         tfprintf (oFile, "\t!db !constbyte\n", 0);
866       }
867     }
868   } else {
869     // we have not been given a size, but we now know it
870     DCL_ELEM (type) = size;
871   }
872
873   return;
874 }
875
876 /*-----------------------------------------------------------------*/
877 /* printIvalFuncPtr - generate initial value for function pointers */
878 /*-----------------------------------------------------------------*/
879 void 
880 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
881 {
882   value *val;
883   int dLvl = 0;
884
885   if (ilist)
886     val = list2val (ilist);
887   else
888     val = valCastLiteral(type, 0.0);
889
890   if (!val) {
891     // an error has been thrown already
892     val=constVal("0");
893   }
894
895   if (IS_LITERAL(val->etype)) {
896     if (compareType(type, val->etype) == 0) {
897       werrorfl (ilist->filename, ilist->lineno, E_INCOMPAT_TYPES);
898       printFromToType (val->type, type);
899     }
900     printIvalCharPtr (NULL, type, val, oFile);
901     return;
902   }
903
904   /* check the types   */
905   if ((dLvl = compareType (val->type, type->next)) <= 0)
906     {
907       tfprintf (oFile, "\t!dw !constword\n", 0);
908       return;
909     }
910
911   /* now generate the name */
912   if (!val->sym)
913     {
914       if (port->use_dw_for_init)
915         {
916           tfprintf (oFile, "\t!dws\n", val->name);
917         }
918       else
919         {
920           printPointerType (oFile, val->name);
921         }
922     }
923   else if (port->use_dw_for_init)
924     {
925       tfprintf (oFile, "\t!dws\n", val->sym->rname);
926     }
927   else
928     {
929       printPointerType (oFile, val->sym->rname);
930     }
931
932   return;
933 }
934
935 /*-----------------------------------------------------------------*/
936 /* printIvalCharPtr - generates initial values for character pointers */
937 /*-----------------------------------------------------------------*/
938 int 
939 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
940 {
941   int size = 0;
942
943   /* PENDING: this is _very_ mcs51 specific, including a magic
944      number...
945      It's also endin specific.
946    */
947   size = getSize (type);
948
949   if (val->name && strlen (val->name))
950     {
951       if (size == 1)            /* This appears to be Z80 specific?? */
952         {
953           tfprintf (oFile,
954                     "\t!dbs\n", val->name);
955         }
956       else if (size == FPTRSIZE)
957         {
958           if (port->use_dw_for_init)
959             {
960               tfprintf (oFile, "\t!dws\n", val->name);
961             }
962           else
963             {
964               printPointerType (oFile, val->name);
965             }
966         }
967       else if (size == GPTRSIZE)
968         {
969           int type;
970           if (IS_PTR (val->type)) {
971             type = DCL_TYPE (val->type);
972           } else {
973             type = PTR_TYPE (SPEC_OCLS (val->etype));
974           }
975           if (val->sym && val->sym->isstrlit) {
976             // this is a literal string
977             type=CPOINTER;
978           }
979           printGPointerType (oFile, val->name, sym->name, type);
980         }
981       else
982         {
983           fprintf (stderr, "*** internal error: unknown size in "
984                    "printIvalCharPtr.\n");
985         }
986     }
987   else
988     {
989       // these are literals assigned to pointers
990       switch (size)
991         {
992         case 1:
993           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
994           break;
995         case 2:
996           if (port->use_dw_for_init)
997             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
998           else if (port->little_endian)
999             tfprintf (oFile, "\t.byte %s,%s\n",
1000                       aopLiteral (val, 0), aopLiteral (val, 1));
1001           else
1002             tfprintf (oFile, "\t.byte %s,%s\n",
1003                       aopLiteral (val, 1), aopLiteral (val, 0));
1004           break;
1005         case 3:
1006           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
1007             // non-zero mcs51 generic pointer
1008             werrorfl (sym->fileDef, sym->lineDef, E_LITERAL_GENERIC);
1009           }
1010           if (port->little_endian) {
1011             fprintf (oFile, "\t.byte %s,%s,%s\n",
1012                      aopLiteral (val, 0), 
1013                      aopLiteral (val, 1),
1014                      aopLiteral (val, 2));
1015           } else {
1016             fprintf (oFile, "\t.byte %s,%s,%s\n",
1017                      aopLiteral (val, 2), 
1018                      aopLiteral (val, 1),
1019                      aopLiteral (val, 0));
1020           }
1021           break;
1022         case 4:
1023           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
1024             // non-zero ds390 generic pointer
1025             werrorfl (sym->fileDef, sym->lineDef, E_LITERAL_GENERIC);
1026           }
1027           if (port->little_endian) {
1028             fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
1029                      aopLiteral (val, 0), 
1030                      aopLiteral (val, 1), 
1031                      aopLiteral (val, 2),
1032                      aopLiteral (val, 3));
1033           } else {
1034             fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
1035                      aopLiteral (val, 3), 
1036                      aopLiteral (val, 2), 
1037                      aopLiteral (val, 1),
1038                      aopLiteral (val, 0));
1039           }
1040           break;
1041         default:
1042           assert (0);
1043         }
1044     }
1045
1046   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
1047     addSet (&statsg->syms, val->sym);
1048   }
1049
1050   return 1;
1051 }
1052
1053 /*-----------------------------------------------------------------*/
1054 /* printIvalPtr - generates initial value for pointers             */
1055 /*-----------------------------------------------------------------*/
1056 void 
1057 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1058 {
1059   value *val;
1060   int size;
1061
1062   /* if deep then   */
1063   if (ilist && (ilist->type == INIT_DEEP))
1064     ilist = ilist->init.deep;
1065
1066   /* function pointer     */
1067   if (IS_FUNC (type->next))
1068     {
1069       printIvalFuncPtr (type, ilist, oFile);
1070       return;
1071     }
1072
1073   if (!(val = initPointer (ilist, type)))
1074     return;
1075
1076   /* if character pointer */
1077   if (IS_CHAR (type->next))
1078     if (printIvalCharPtr (sym, type, val, oFile))
1079       return;
1080
1081   /* check the type      */
1082   if (compareType (type, val->type) == 0) {
1083     werrorfl (ilist->filename, ilist->lineno, W_INIT_WRONG);
1084     printFromToType (val->type, type);
1085   }
1086
1087   /* if val is literal */
1088   if (IS_LITERAL (val->etype))
1089     {
1090       switch (getSize (type))
1091         {
1092         case 1:
1093           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
1094           break;
1095         case 2:
1096           if (port->use_dw_for_init)
1097             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
1098           else if (port->little_endian)
1099             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1100           else
1101             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 1), aopLiteral (val, 0));
1102           break;
1103         case 3: // how about '390??
1104           fprintf (oFile, "; generic printIvalPtr\n");
1105           if (port->little_endian)
1106             {
1107               fprintf (oFile, "\t.byte %s,%s",
1108                        aopLiteral (val, 0), aopLiteral (val, 1));
1109             }
1110           else
1111             {
1112               fprintf (oFile, "\t.byte %s,%s",
1113                        aopLiteral (val, 1), aopLiteral (val, 0));
1114             }
1115           if (IS_GENPTR (val->type))
1116             fprintf (oFile, ",%s\n", aopLiteral (val, 2));
1117           else if (IS_PTR (val->type))
1118             fprintf (oFile, ",#%x\n", pointerTypeToGPByte (DCL_TYPE (val->type), NULL, NULL));
1119           else
1120             fprintf (oFile, ",%s\n", aopLiteral (val, 2));
1121         }
1122       return;
1123     }
1124
1125
1126   size = getSize (type);
1127
1128   if (size == 1)                /* Z80 specific?? */
1129     {
1130       tfprintf (oFile, "\t!dbs\n", val->name);
1131     }
1132   else if (size == FPTRSIZE)
1133     {
1134       if (port->use_dw_for_init) {
1135         tfprintf (oFile, "\t!dws\n", val->name);
1136       } else {
1137         printPointerType (oFile, val->name);
1138       }
1139     }
1140   else if (size == GPTRSIZE)
1141     {
1142       printGPointerType (oFile, val->name, sym->name,
1143                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1144                           PTR_TYPE (SPEC_OCLS (val->etype))));
1145     }
1146   return;
1147 }
1148
1149 /*-----------------------------------------------------------------*/
1150 /* printIval - generates code for initial value                    */
1151 /*-----------------------------------------------------------------*/
1152 void 
1153 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1154 {
1155   sym_link *itype;
1156   
1157   /* if structure then    */
1158   if (IS_STRUCT (type))
1159     {
1160       printIvalStruct (sym, type, ilist, oFile);
1161       return;
1162     }
1163
1164   /* if this is an array   */
1165   if (IS_ARRAY (type))
1166     {
1167       printIvalArray (sym, type, ilist, oFile);
1168       return;
1169     }
1170
1171   if (ilist)
1172     {
1173       // not an aggregate, ilist must be a node
1174       if (ilist->type!=INIT_NODE) {
1175           // or a 1-element list
1176         if (ilist->init.deep->next) {
1177           werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "scalar", 
1178                   sym->name);
1179         } else {
1180           ilist=ilist->init.deep;
1181         }
1182       }
1183
1184       // and the type must match
1185       itype=ilist->init.node->ftype;
1186
1187       if (compareType(type, itype)==0) {
1188         // special case for literal strings
1189         if (IS_ARRAY (itype) && IS_CHAR (getSpec(itype)) &&
1190             // which are really code pointers
1191             IS_PTR(type) && DCL_TYPE(type)==CPOINTER) {
1192           // no sweat
1193         } else {
1194           werrorfl (ilist->filename, ilist->lineno, E_TYPE_MISMATCH, "assignment", " ");
1195           printFromToType(itype, type);
1196         }
1197       }
1198     }
1199
1200   /* if this is a pointer */
1201   if (IS_PTR (type))
1202     {
1203       printIvalPtr (sym, type, ilist, oFile);
1204       return;
1205     }
1206
1207   /* if type is SPECIFIER */
1208   if (IS_SPEC (type))
1209     {
1210       printIvalType (sym, type, ilist, oFile);
1211       return;
1212     }
1213 }
1214
1215 /*-----------------------------------------------------------------*/
1216 /* emitStaticSeg - emitcode for the static segment                 */
1217 /*-----------------------------------------------------------------*/
1218 void 
1219 emitStaticSeg (memmap * map, FILE * out)
1220 {
1221   symbol *sym;
1222
1223   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1224
1225   /* for all variables in this segment do */
1226   for (sym = setFirstItem (map->syms); sym;
1227        sym = setNextItem (map->syms))
1228     {
1229
1230       /* if it is "extern" then do nothing */
1231       if (IS_EXTERN (sym->etype))
1232         continue;
1233
1234       /* if it is not static add it to the public
1235          table */
1236       if (!IS_STATIC (sym->etype))
1237         {
1238           addSetHead (&publics, sym);
1239         }
1240
1241       /* print extra debug info if required */
1242       if (options.debug) {
1243
1244         if (!sym->level)
1245           {                     /* global */
1246             if (IS_STATIC (sym->etype))
1247               fprintf (out, "F%s$", moduleName);        /* scope is file */
1248             else
1249               fprintf (out, "G$");      /* scope is global */
1250           }
1251         else
1252           /* symbol is local */
1253           fprintf (out, "L%s$",
1254                    (sym->localof ? sym->localof->name : "-null-"));
1255         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1256       }
1257       
1258       /* if it has an absolute address */
1259       if (SPEC_ABSA (sym->etype))
1260         {
1261           if (options.debug)
1262             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1263           
1264           fprintf (out, "%s\t=\t0x%04x\n",
1265                    sym->rname,
1266                    SPEC_ADDR (sym->etype));
1267         }
1268       else
1269         {
1270           if (options.debug)
1271             fprintf (out, " == .\n");
1272           
1273           /* if it has an initial value */
1274           if (sym->ival)
1275             {
1276               fprintf (out, "%s:\n", sym->rname);
1277               noAlloc++;
1278               resolveIvalSym (sym->ival, sym->type);
1279               printIval (sym, sym->type, sym->ival, out);
1280               noAlloc--;
1281               /* if sym is a simple string and sym->ival is a string, 
1282                  WE don't need it anymore */
1283               if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) &&
1284                   IS_AST_SYM_VALUE(list2expr(sym->ival)) &&
1285                   list2val(sym->ival)->sym->isstrlit) {
1286                 freeStringSymbol(list2val(sym->ival)->sym);
1287               }
1288             }
1289           else {
1290               /* allocate space */
1291               int size = getSize (sym->type);
1292               
1293               if (size==0) {
1294                   werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE,sym->name);
1295               }
1296               fprintf (out, "%s:\n", sym->rname);
1297               /* special case for character strings */
1298               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1299                   SPEC_CVAL (sym->etype).v_char)
1300                   printChar (out,
1301                              SPEC_CVAL (sym->etype).v_char,
1302                              size);
1303               else
1304                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1305             }
1306         }
1307     }
1308 }
1309
1310 /*-----------------------------------------------------------------*/
1311 /* emitMaps - emits the code for the data portion the code         */
1312 /*-----------------------------------------------------------------*/
1313 void 
1314 emitMaps (void)
1315 {
1316   int publicsfr = TARGET_IS_MCS51; /* Ideally, this should be true for all  */
1317                                    /* ports but let's be conservative - EEP */
1318   
1319   inInitMode++;
1320   /* no special considerations for the following
1321      data, idata & bit & xdata */
1322   emitRegularMap (data, TRUE, TRUE);
1323   emitRegularMap (idata, TRUE, TRUE);
1324   emitRegularMap (bit, TRUE, FALSE);
1325   emitRegularMap (xdata, TRUE, TRUE);
1326   if (port->genXINIT) {
1327     emitRegularMap (xidata, TRUE, TRUE);
1328   }
1329   emitRegularMap (sfr, publicsfr, FALSE);
1330   emitRegularMap (sfrbit, publicsfr, FALSE);
1331   emitRegularMap (home, TRUE, FALSE);
1332   emitRegularMap (code, TRUE, FALSE);
1333
1334   emitStaticSeg (statsg, code->oFile);
1335   if (port->genXINIT) {
1336     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1337     emitStaticSeg (xinit, code->oFile);
1338   }
1339   inInitMode--;
1340 }
1341
1342 /*-----------------------------------------------------------------*/
1343 /* flushStatics - flush all currently defined statics out to file  */
1344 /*  and delete.  Temporary function                                */
1345 /*-----------------------------------------------------------------*/
1346 void 
1347 flushStatics (void)
1348 {
1349   emitStaticSeg (statsg, codeOutFile);
1350   statsg->syms = NULL;
1351 }
1352
1353 /*-----------------------------------------------------------------*/
1354 /* createInterruptVect - creates the interrupt vector              */
1355 /*-----------------------------------------------------------------*/
1356 void 
1357 createInterruptVect (FILE * vFile)
1358 {
1359   unsigned i = 0;
1360   mainf = newSymbol ("main", 0);
1361   mainf->block = 0;
1362
1363   /* only if the main function exists */
1364   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1365     {
1366       if (!options.cc_only && !noAssemble && !options.c1mode)
1367         werror (E_NO_MAIN);
1368       return;
1369     }
1370
1371   /* if the main is only a prototype ie. no body then do nothing */
1372   if (!IFFUNC_HASBODY(mainf->type))
1373     {
1374       /* if ! compile only then main function should be present */
1375       if (!options.cc_only && !noAssemble)
1376         werror (E_NO_MAIN);
1377       return;
1378     }
1379
1380   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1381   fprintf (vFile, "__interrupt_vect:\n");
1382
1383
1384   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1385     {
1386       /* "generic" interrupt table header (if port doesn't specify one).
1387        * Look suspiciously like 8051 code to me...
1388        */
1389
1390       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1391
1392       /* now for the other interrupts */
1393       for (; i < maxInterrupts; i++)
1394         {
1395           if (interrupts[i])
1396             {
1397               fprintf (vFile, "\tljmp\t%s\n", interrupts[i]->rname);
1398               if ( i != maxInterrupts - 1 )
1399                 fprintf (vFile, "\t.ds\t5\n");
1400             }
1401           else
1402             {
1403               fprintf (vFile, "\treti\n");
1404               if ( i != maxInterrupts - 1 )
1405                 fprintf (vFile, "\t.ds\t7\n");
1406             }
1407         }
1408     }
1409 }
1410
1411 char *iComments1 =
1412 {
1413   ";--------------------------------------------------------\n"
1414   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1415
1416 char *iComments2 =
1417 {
1418   ";--------------------------------------------------------\n"};
1419
1420
1421 /*-----------------------------------------------------------------*/
1422 /* initialComments - puts in some initial comments                 */
1423 /*-----------------------------------------------------------------*/
1424 void 
1425 initialComments (FILE * afile)
1426 {
1427   time_t t;
1428   time (&t);
1429   fprintf (afile, "%s", iComments1);
1430   fprintf (afile, "; Version " SDCC_VERSION_STR " (%s)\n", __DATE__);
1431   fprintf (afile, "; This file generated %s", asctime (localtime (&t)));
1432   fprintf (afile, "%s", iComments2);
1433 }
1434
1435 /*-----------------------------------------------------------------*/
1436 /* printPublics - generates .global for publics                    */
1437 /*-----------------------------------------------------------------*/
1438 void 
1439 printPublics (FILE * afile)
1440 {
1441   symbol *sym;
1442
1443   fprintf (afile, "%s", iComments2);
1444   fprintf (afile, "; Public variables in this module\n");
1445   fprintf (afile, "%s", iComments2);
1446
1447   for (sym = setFirstItem (publics); sym;
1448        sym = setNextItem (publics))
1449     tfprintf (afile, "\t!global\n", sym->rname);
1450 }
1451
1452 /*-----------------------------------------------------------------*/
1453 /* printExterns - generates .global for externs                    */
1454 /*-----------------------------------------------------------------*/
1455 void 
1456 printExterns (FILE * afile)
1457 {
1458   symbol *sym;
1459
1460   fprintf (afile, "%s", iComments2);
1461   fprintf (afile, "; Externals used\n");
1462   fprintf (afile, "%s", iComments2);
1463
1464   for (sym = setFirstItem (externs); sym;
1465        sym = setNextItem (externs))
1466     tfprintf (afile, "\t!extern\n", sym->rname);
1467 }
1468
1469 /*-----------------------------------------------------------------*/
1470 /* emitOverlay - will emit code for the overlay stuff              */
1471 /*-----------------------------------------------------------------*/
1472 static void 
1473 emitOverlay (FILE * afile)
1474 {
1475   set *ovrset;
1476
1477   if (!elementsInSet (ovrSetSets))
1478     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1479
1480   /* for each of the sets in the overlay segment do */
1481   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1482        ovrset = setNextItem (ovrSetSets))
1483     {
1484
1485       symbol *sym;
1486
1487       if (elementsInSet (ovrset))
1488         {
1489           /* output the area informtion */
1490           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1491         }
1492
1493       for (sym = setFirstItem (ovrset); sym;
1494            sym = setNextItem (ovrset))
1495         {
1496           /* if extern then it is in the publics table: do nothing */
1497           if (IS_EXTERN (sym->etype))
1498             continue;
1499
1500           /* if allocation required check is needed
1501              then check if the symbol really requires
1502              allocation only for local variables */
1503           if (!IS_AGGREGATE (sym->type) &&
1504               !(sym->_isparm && !IS_REGPARM (sym->etype))
1505               && !sym->allocreq && sym->level)
1506             continue;
1507
1508           /* if global variable & not static or extern
1509              and addPublics allowed then add it to the public set */
1510           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1511               && !IS_STATIC (sym->etype))
1512             {
1513               addSetHead (&publics, sym);
1514             }
1515
1516           /* if extern then do nothing or is a function
1517              then do nothing */
1518           if (IS_FUNC (sym->type))
1519             continue;
1520
1521           /* print extra debug info if required */
1522           if (options.debug)
1523             {
1524               if (!sym->level)
1525                 {               /* global */
1526                   if (IS_STATIC (sym->etype))
1527                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1528                   else
1529                     fprintf (afile, "G$");      /* scope is global */
1530                 }
1531               else
1532                 /* symbol is local */
1533                 fprintf (afile, "L%s$",
1534                          (sym->localof ? sym->localof->name : "-null-"));
1535               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1536             }
1537
1538           /* if is has an absolute address then generate
1539              an equate for this no need to allocate space */
1540           if (SPEC_ABSA (sym->etype))
1541             {
1542
1543               if (options.debug)
1544                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1545
1546               fprintf (afile, "%s\t=\t0x%04x\n",
1547                        sym->rname,
1548                        SPEC_ADDR (sym->etype));
1549             }
1550           else {
1551               int size = getSize(sym->type);
1552
1553               if (size==0) {
1554                   werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE);
1555               }       
1556               if (options.debug)
1557                   fprintf (afile, "==.\n");
1558               
1559               /* allocate space */
1560               tfprintf (afile, "!labeldef\n", sym->rname);
1561               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1562           }
1563           
1564         }
1565     }
1566 }
1567
1568
1569 /*-----------------------------------------------------------------*/
1570 /* spacesToUnderscores - replace spaces with underscores        */
1571 /*-----------------------------------------------------------------*/
1572 static char *
1573 spacesToUnderscores (char *dest, const char *src, size_t len)
1574 {
1575   int i;
1576   char *p;
1577
1578   assert(dest != NULL);
1579   assert(src != NULL);
1580   assert(len > 0);
1581
1582   --len;
1583   for (p = dest, i = 0; *src != '\0' && i < len; ++src, ++i) {
1584     *p++ = isspace(*src) ? '_' : *src;
1585   }
1586   *p = '\0';
1587
1588   return dest;
1589 }
1590
1591
1592 /*-----------------------------------------------------------------*/
1593 /* glue - the final glue that hold the whole thing together        */
1594 /*-----------------------------------------------------------------*/
1595 void 
1596 glue (void)
1597 {
1598   FILE *vFile;
1599   FILE *asmFile;
1600   FILE *ovrFile = tempfile ();
1601   char moduleBuf[PATH_MAX];
1602   int mcs51_like;
1603
1604   if(port->general.glue_up_main &&
1605     (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51 || TARGET_IS_DS400))
1606   {
1607       mcs51_like=1; /*So it has bits, sfr, sbits, data, idata, etc...*/
1608   }
1609   else
1610   {
1611       mcs51_like=0;
1612   }
1613
1614   addSetHead (&tmpfileSet, ovrFile);
1615   /* print the global struct definitions */
1616   if (options.debug)
1617     cdbStructBlock (0);
1618
1619   vFile = tempfile ();
1620   /* PENDING: this isnt the best place but it will do */
1621   if (port->general.glue_up_main)
1622     {
1623       /* create the interrupt vector table */
1624       createInterruptVect (vFile);
1625     }
1626
1627   addSetHead (&tmpfileSet, vFile);
1628
1629   /* emit code for the all the variables declared */
1630   emitMaps ();
1631   /* do the overlay segments */
1632   emitOverlay (ovrFile);
1633
1634   outputDebugSymbols();
1635
1636   /* now put it all together into the assembler file */
1637   /* create the assembler file name */
1638
1639   /* -o option overrides default name? */
1640   if ((noAssemble || options.c1mode) && fullDstFileName)
1641     {
1642       strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1643     }
1644   else
1645     {
1646       strncpyz (scratchFileName, dstFileName, PATH_MAX);
1647       strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1648     }
1649
1650   if (!(asmFile = fopen (scratchFileName, "w")))
1651     {
1652       werror (E_FILE_OPEN_ERR, scratchFileName);
1653       exit (1);
1654     }
1655
1656   /* initial comments */
1657   initialComments (asmFile);
1658
1659   /* print module name */
1660   tfprintf (asmFile, "\t!module\n",
1661     spacesToUnderscores (moduleBuf, moduleName, sizeof moduleBuf));
1662   if(mcs51_like)
1663   {
1664     fprintf (asmFile, "\t.optsdcc -m%s", port->target);
1665
1666     switch(options.model)
1667     {
1668         case MODEL_SMALL:   fprintf (asmFile, " --model-small");   break;
1669         case MODEL_COMPACT: fprintf (asmFile, " --model-compact"); break;
1670         case MODEL_MEDIUM:  fprintf (asmFile, " --model-medium");  break;
1671         case MODEL_LARGE:   fprintf (asmFile, " --model-large");   break;
1672         case MODEL_FLAT24:  fprintf (asmFile, " --model-flat24");  break;
1673         case MODEL_PAGE0:   fprintf (asmFile, " --model-page0");   break;
1674         default: break;
1675     }
1676     /*if(options.stackAuto)      fprintf (asmFile, " --stack-auto");*/
1677     if(options.useXstack)      fprintf (asmFile, " --xstack");
1678     /*if(options.intlong_rent)   fprintf (asmFile, " --int-long-rent");*/
1679     /*if(options.float_rent)     fprintf (asmFile, " --float-rent");*/
1680     if(options.noRegParams)    fprintf (asmFile, " --no-reg-params");
1681     if(options.parms_in_bank1) fprintf (asmFile, " --parms-in-bank1");
1682     fprintf (asmFile, "\n");
1683   }
1684   else if(TARGET_IS_Z80 || TARGET_IS_GBZ80 || TARGET_IS_HC08)
1685   {
1686     fprintf (asmFile, "\t.optsdcc -m%s\n", port->target);
1687   }
1688
1689   tfprintf (asmFile, "\t!fileprelude\n");
1690
1691   /* Let the port generate any global directives, etc. */
1692   if (port->genAssemblerPreamble)
1693     {
1694       port->genAssemblerPreamble (asmFile);
1695     }
1696
1697   /* print the global variables in this module */
1698   printPublics (asmFile);
1699   if (port->assembler.externGlobal)
1700     printExterns (asmFile);
1701
1702   if(( mcs51_like )
1703    ||( TARGET_IS_Z80 )) /*.p.t.20030924 need to output SFR table for Z80 as well */
1704   {
1705       /* copy the sfr segment */
1706       fprintf (asmFile, "%s", iComments2);
1707       fprintf (asmFile, "; special function registers\n");
1708       fprintf (asmFile, "%s", iComments2);
1709       copyFile (asmFile, sfr->oFile);
1710   }
1711   
1712   if(mcs51_like)
1713     {
1714       /* copy the sbit segment */
1715       fprintf (asmFile, "%s", iComments2);
1716       fprintf (asmFile, "; special function bits \n");
1717       fprintf (asmFile, "%s", iComments2);
1718       copyFile (asmFile, sfrbit->oFile);
1719   
1720       /*JCF: Create the areas for the register banks*/
1721       if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1722       {
1723          fprintf (asmFile, "%s", iComments2);
1724          fprintf (asmFile, "; overlayable register banks \n");
1725          fprintf (asmFile, "%s", iComments2);
1726          if(RegBankUsed[0])
1727             fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1728          if(RegBankUsed[1]||options.parms_in_bank1)
1729             fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1730          if(RegBankUsed[2])
1731             fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1732          if(RegBankUsed[3])
1733             fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1734       }
1735     }
1736
1737   /* copy the data segment */
1738   fprintf (asmFile, "%s", iComments2);
1739   fprintf (asmFile, "; %s ram data\n", mcs51_like?"internal":"");
1740   fprintf (asmFile, "%s", iComments2);
1741   copyFile (asmFile, data->oFile);
1742
1743
1744   /* create the overlay segments */
1745   if (overlay) {
1746     fprintf (asmFile, "%s", iComments2);
1747     fprintf (asmFile, "; overlayable items in %s ram \n", mcs51_like?"internal":"");
1748     fprintf (asmFile, "%s", iComments2);
1749     copyFile (asmFile, ovrFile);
1750   }
1751
1752   /* create the stack segment MOF */
1753   if (mainf && IFFUNC_HASBODY(mainf->type))
1754     {
1755       fprintf (asmFile, "%s", iComments2);
1756       fprintf (asmFile, "; Stack segment in internal ram \n");
1757       fprintf (asmFile, "%s", iComments2);
1758       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1759                "__start__stack:\n\t.ds\t1\n\n");
1760     }
1761
1762   /* create the idata segment */
1763   if ( (idata) && (mcs51_like) ) {
1764     fprintf (asmFile, "%s", iComments2);
1765     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1766     fprintf (asmFile, "%s", iComments2);
1767     copyFile (asmFile, idata->oFile);
1768   }
1769
1770   /* copy the bit segment */
1771   if (mcs51_like) {
1772     fprintf (asmFile, "%s", iComments2);
1773     fprintf (asmFile, "; bit data\n");
1774     fprintf (asmFile, "%s", iComments2);
1775     copyFile (asmFile, bit->oFile);
1776   }
1777
1778   /* if external stack then reserve space of it */
1779   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1780     {
1781       fprintf (asmFile, "%s", iComments2);
1782       fprintf (asmFile, "; external stack \n");
1783       fprintf (asmFile, "%s", iComments2);
1784       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1785       fprintf (asmFile, "\t.ds 256\n");
1786     }
1787
1788
1789   /* copy xtern ram data */
1790   if (mcs51_like) {
1791     fprintf (asmFile, "%s", iComments2);
1792     fprintf (asmFile, "; external ram data\n");
1793     fprintf (asmFile, "%s", iComments2);
1794     copyFile (asmFile, xdata->oFile);
1795   }
1796
1797   /* copy xternal initialized ram data */
1798   fprintf (asmFile, "%s", iComments2);
1799   fprintf (asmFile, "; external initialized ram data\n");
1800   fprintf (asmFile, "%s", iComments2);
1801   copyFile (asmFile, xidata->oFile);
1802
1803   /* If the port wants to generate any extra areas, let it do so. */
1804   if (port->extraAreas.genExtraAreaDeclaration)
1805   {
1806       port->extraAreas.genExtraAreaDeclaration(asmFile, 
1807                                                mainf && IFFUNC_HASBODY(mainf->type));
1808   }
1809     
1810   /* copy the interrupt vector table */
1811   if (mainf && IFFUNC_HASBODY(mainf->type))
1812     {
1813       fprintf (asmFile, "%s", iComments2);
1814       fprintf (asmFile, "; interrupt vector \n");
1815       fprintf (asmFile, "%s", iComments2);
1816       copyFile (asmFile, vFile);
1817     }
1818
1819   /* copy global & static initialisations */
1820   fprintf (asmFile, "%s", iComments2);
1821   fprintf (asmFile, "; global & static initialisations\n");
1822   fprintf (asmFile, "%s", iComments2);
1823
1824   /* Everywhere we generate a reference to the static_name area,
1825    * (which is currently only here), we immediately follow it with a
1826    * definition of the post_static_name area. This guarantees that
1827    * the post_static_name area will immediately follow the static_name
1828    * area.
1829    */
1830   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1831   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1832   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1833
1834   if (mainf && IFFUNC_HASBODY(mainf->type))
1835     {
1836       if (port->genInitStartup)
1837         {
1838            port->genInitStartup(asmFile);
1839         }
1840       else
1841         {
1842           fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1843           /* if external stack is specified then the
1844              higher order byte of the xdatalocation is
1845              going into P2 and the lower order going into
1846              spx */
1847           if (options.useXstack)
1848             {
1849               fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1850                        (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1851               fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1852                        (unsigned int) options.xdata_loc & 0xff);
1853             }
1854
1855           // This should probably be a port option, but I'm being lazy.
1856           // on the 400, the firmware boot loader gives us a valid stack
1857           // (see '400 data sheet pg. 85 (TINI400 ROM Initialization code)
1858           if (!TARGET_IS_DS400)
1859             {
1860               /* initialise the stack pointer.  JCF: aslink takes care of the location */
1861               fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");     /* MOF */
1862             }
1863
1864           fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1865           fprintf (asmFile, "\tmov\ta,dpl\n");
1866           fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1867           fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1868           fprintf (asmFile, "__sdcc_init_data:\n");
1869
1870           // if the port can copy the XINIT segment to XISEG
1871           if (port->genXINIT)
1872             {
1873               port->genXINIT(asmFile);
1874             }
1875         }
1876
1877     }
1878   copyFile (asmFile, statsg->oFile);
1879
1880   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1881     {
1882       /* This code is generated in the post-static area.
1883        * This area is guaranteed to follow the static area
1884        * by the ugly shucking and jiving about 20 lines ago.
1885        */
1886       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1887       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1888     }
1889
1890   fprintf (asmFile,
1891            "%s"
1892            "; Home\n"
1893            "%s", iComments2, iComments2);
1894   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1895   copyFile (asmFile, home->oFile);
1896
1897   /* copy over code */
1898   fprintf (asmFile, "%s", iComments2);
1899   fprintf (asmFile, "; code\n");
1900   fprintf (asmFile, "%s", iComments2);
1901   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1902   if (mainf && IFFUNC_HASBODY(mainf->type))
1903     {
1904
1905       /* entry point @ start of CSEG */
1906       fprintf (asmFile, "__sdcc_program_startup:\n");
1907
1908       /* put in jump or call to main */
1909       if (options.mainreturn)
1910         {
1911           fprintf (asmFile, "\tljmp\t_main\n");   /* needed? */
1912           fprintf (asmFile, ";\treturn from main will return to caller\n");
1913         }
1914       else
1915         {
1916           fprintf (asmFile, "\tlcall\t_main\n");
1917           fprintf (asmFile, ";\treturn from main will lock up\n");
1918           fprintf (asmFile, "\tsjmp .\n");
1919         }
1920     }
1921   copyFile (asmFile, code->oFile);
1922
1923   if (port->genAssemblerEnd) {
1924       port->genAssemblerEnd(asmFile);
1925   }
1926   fclose (asmFile);
1927
1928   rm_tmpfiles ();
1929 }
1930
1931
1932 /** Creates a temporary file with unique file name
1933     Scans, in order:
1934     - TMP, TEMP, TMPDIR env. varibles
1935     - if Un*x system: /usr/tmp and /tmp
1936     - root directory using mkstemp() if avaliable
1937     - default location using tempnam()
1938 */
1939 static int
1940 tempfileandname(char *fname, size_t len)
1941 {
1942 #define TEMPLATE      "sdccXXXXXX"
1943 #define TEMPLATE_LEN  ((sizeof TEMPLATE) - 1)
1944
1945   const char *tmpdir = NULL;
1946   int fd;
1947
1948   if ((tmpdir = getenv ("TMP")) == NULL)
1949     if ((tmpdir = getenv ("TEMP")) == NULL)
1950       tmpdir = getenv ("TMPDIR");
1951
1952 #if defined(_WIN32)
1953   {
1954     static int warning_emitted;
1955
1956     if (tmpdir == NULL)
1957       {
1958         tmpdir = "c:\\";
1959         if (!warning_emitted)
1960           {
1961             fprintf (stderr, "TMP not defined in environment, using %s for temporary files\n.", tmpdir);
1962             warning_emitted = 1;
1963           }
1964       }
1965   }
1966 #else
1967   {
1968     /* try with /usr/tmp and /tmp on Un*x systems */
1969     struct stat statbuf;
1970
1971     if (tmpdir == NULL) {
1972       if (stat("/usr/tmp", &statbuf) != -1)
1973         tmpdir = "/usr/tmp";
1974       else if (stat("/tmp", &statbuf) != -1)
1975         tmpdir = "/tmp";
1976     }
1977   }
1978 #endif
1979
1980 #ifdef HAVE_MKSTEMP
1981   {
1982     char fnamebuf[PATH_MAX];
1983     size_t name_len;
1984
1985     if (fname == NULL || len == 0) {
1986       fname = fnamebuf;
1987       len = sizeof fnamebuf;
1988     }
1989
1990     if (tmpdir) {
1991       name_len = strlen(tmpdir) + 1 + TEMPLATE_LEN;
1992
1993       assert(name_len < len);
1994       if (!(name_len < len))  /* in NDEBUG is defined */
1995         return -1;            /* buffer too small, temporary file can not be created */
1996
1997       sprintf(fname, "%s" DIR_SEPARATOR_STRING TEMPLATE, tmpdir);
1998     }
1999     else {
2000       name_len = TEMPLATE_LEN;
2001
2002       assert(name_len < len);
2003       if (!(name_len < len))  /* in NDEBUG is defined */
2004         return -1;            /* buffer too small, temporary file can not be created */
2005
2006       strcpy(fname, TEMPLATE);
2007     }
2008
2009     fd = mkstemp(fname);
2010   }
2011 #else
2012   {
2013     char *name = tempnam(tmpdir, "sdcc");
2014
2015     if (name == NULL) {
2016       perror("Can't create temporary file name");
2017       exit(1);
2018     }
2019
2020     assert(strlen(name) < len);
2021     if (!(strlen(name) < len))  /* in NDEBUG is defined */
2022       return -1;                /* buffer too small, temporary file can not be created */
2023
2024     strcpy(fname, name);
2025 #ifdef _WIN32
2026     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IREAD | S_IWRITE);
2027 #else
2028     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IRUSR | S_IWUSR);
2029 #endif
2030   }
2031 #endif
2032
2033   if (fd == -1) {
2034     perror("Can't create temporary file");
2035     exit(1);
2036   }
2037
2038   return fd;
2039 }
2040
2041
2042 /** Create a temporary file name
2043 */
2044 char *
2045 tempfilename(void)
2046 {
2047   int fd;
2048   static char fnamebuf[PATH_MAX];
2049
2050   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
2051     fprintf(stderr, "Can't create temporary file name!");
2052     exit(1);
2053   }
2054
2055   fd = close(fd);
2056   assert(fd != -1);
2057
2058   return fnamebuf;
2059 }
2060
2061
2062 /** Create a temporary file and add it to tmpfileNameSet,
2063     so that it is removed explicitly by rm_tmpfiles()
2064     or implicitly at program extit.
2065 */
2066 FILE *
2067 tempfile(void)
2068 {
2069   int fd;
2070   char *tmp;
2071   FILE *fp;
2072   char fnamebuf[PATH_MAX];
2073
2074   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
2075     fprintf(stderr, "Can't create temporary file!");
2076     exit(1);
2077   }
2078
2079   tmp = Safe_strdup(fnamebuf);
2080   if (tmp)
2081     addSetHead(&tmpfileNameSet, tmp);
2082
2083   if ((fp = fdopen(fd, "w+b")) == NULL) {
2084       perror("Can't create temporary file!");
2085       exit(1);
2086   }
2087
2088   return fp;
2089 }