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