* src/SDCCglue.c, src/SDCCast.c:
[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 *, bool check);
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, TRUE);
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     {
710       unsigned long i;
711       val = list2val (lilist);
712       if (size)
713         {
714           if (SPEC_BLEN (lsym->etype) > 8)
715             {
716               size += ((SPEC_BLEN (lsym->etype) / 8) +
717                        (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
718             }
719         }
720       else
721         {
722           size = ((SPEC_BLEN (lsym->etype) / 8) +
723                   (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
724         }
725
726       /* check if the literal value is within bounds */
727       if (val &&
728         checkConstantRange (lsym->etype, val->etype, '=', FALSE) == CCR_OVL &&
729         !options.lessPedantic)
730         {
731           werror (W_LIT_OVERFLOW);
732         }
733
734       i = ulFromVal (val);
735       i &= (1 << SPEC_BLEN (lsym->etype)) - 1;
736       i <<= SPEC_BSTR (lsym->etype);
737       ival |= i;
738       if (!(lsym->next &&
739         (IS_BITFIELD (lsym->next->type)) &&
740         (SPEC_BSTR (lsym->next->etype))))
741         break;
742       lsym = lsym->next;
743       lilist = lilist ? lilist->next : NULL;
744     }
745   while (1);
746
747   switch (size)
748   {
749   case 1:
750     dbuf_tprintf (oBuf, "\t!db !constbyte\n", ival);
751     break;
752
753   case 2:
754     dbuf_tprintf (oBuf, "\t!dw !constword\n", ival);
755     break;
756
757   case 4:
758     dbuf_tprintf (oBuf, "\t!dw  !constword,!constword\n",
759       (ival >> 16) & 0xffff, (ival & 0xffff));
760     break;
761   }
762   *sym = lsym;
763   *ilist = lilist;
764 }
765
766 /*-----------------------------------------------------------------*/
767 /* printIvalStruct - generates initial value for structures        */
768 /*-----------------------------------------------------------------*/
769 void
770 printIvalStruct (symbol * sym, sym_link * type,
771                  initList * ilist, struct dbuf_s * oBuf)
772 {
773   symbol *sflds;
774   initList *iloop = NULL;
775
776   sflds = SPEC_STRUCT (type)->fields;
777
778   if (ilist) {
779     if (ilist->type != INIT_DEEP) {
780       werrorfl (sym->fileDef, sym->lineDef, E_INIT_STRUCT, sym->name);
781       return;
782     }
783
784     iloop = ilist->init.deep;
785   }
786
787   if (SPEC_STRUCT (type)->type == UNION) {
788     printIval (sym, sflds->type, iloop, oBuf, TRUE);
789     iloop = iloop ? iloop->next : NULL;
790   } else {
791     for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) {
792       if (IS_BITFIELD(sflds->type)) {
793         printIvalBitFields(&sflds, &iloop, oBuf);
794       } else {
795         printIval (sym, sflds->type, iloop, oBuf, TRUE);
796       }
797     }
798   }
799   if (iloop) {
800     werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "struct", sym->name);
801   }
802   return;
803 }
804
805 /*-----------------------------------------------------------------*/
806 /* printIvalChar - generates initital value for character array    */
807 /*-----------------------------------------------------------------*/
808 int
809 printIvalChar (symbol * sym, sym_link * type, initList * ilist, struct dbuf_s * oBuf, char *s, bool check)
810 {
811   value *val;
812   unsigned int size = DCL_ELEM (type);
813
814   if (!s)
815     {
816       val = list2val (ilist);
817       /* if the value is a character string  */
818       if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
819         {
820           if (!size)
821             {
822               /* we have not been given a size, but now we know it */
823               size = strlen (SPEC_CVAL (val->etype).v_char) + 1;
824               /* but first check, if it's a flexible array */
825               if (sym && IS_STRUCT (sym->type))
826                 sym->flexArrayLength = size;
827               else
828                 DCL_ELEM (type) = size;
829             }
830
831           if (check && DCL_ELEM (val->type) > size)
832             werror (W_EXCESS_INITIALIZERS, "array of chars", sym->name, sym->lineDef);
833
834           printChar (oBuf, SPEC_CVAL (val->etype).v_char, size);
835
836           return 1;
837         }
838       else
839         return 0;
840     }
841   else
842     printChar (oBuf, s, strlen (s) + 1);
843   return 1;
844 }
845
846 /*-----------------------------------------------------------------*/
847 /* printIvalArray - generates code for array initialization        */
848 /*-----------------------------------------------------------------*/
849 void
850 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
851                 struct dbuf_s * oBuf, bool check)
852 {
853   value *val;
854   initList *iloop;
855   unsigned int size = 0;
856
857   if (ilist) {
858     /* take care of the special   case  */
859     /* array of characters can be init  */
860     /* by a string                      */
861     if (IS_CHAR (type->next)) {
862       val = list2val(ilist);
863       if (!val) {
864         werrorfl (ilist->filename, ilist->lineno, E_INIT_STRUCT, sym->name);
865         return;
866       }
867       if (!IS_LITERAL(val->etype)) {
868         werrorfl (ilist->filename, ilist->lineno, E_CONST_EXPECTED);
869         return;
870       }
871       if (printIvalChar (sym, type,
872                          (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
873                          oBuf, SPEC_CVAL (sym->etype).v_char, check))
874         return;
875     }
876     /* not the special case             */
877     if (ilist->type != INIT_DEEP) {
878       werrorfl (ilist->filename, ilist->lineno, E_INIT_STRUCT, sym->name);
879       return;
880     }
881
882     for (iloop=ilist->init.deep; iloop; iloop=iloop->next) {
883       if ((++size > DCL_ELEM(type)) && DCL_ELEM(type)) {
884         werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "array", sym->name);
885         break;
886       }
887       printIval (sym, type->next, iloop, oBuf, TRUE);
888     }
889   }
890
891   if (DCL_ELEM(type)) {
892     // pad with zeros if needed
893     if (size<DCL_ELEM(type)) {
894       size = (DCL_ELEM(type) - size) * getSize(type->next);
895       while (size--) {
896         dbuf_tprintf (oBuf, "\t!db !constbyte\n", 0);
897       }
898     }
899   } else {
900     /* we have not been given a size, but now we know it */
901     /* but first check, if it's a flexible array */
902     if (IS_STRUCT (sym->type))
903       sym->flexArrayLength = size * getSize (type->next);
904     else
905       DCL_ELEM (type) = size;
906   }
907
908   return;
909 }
910
911 /*-----------------------------------------------------------------*/
912 /* printIvalFuncPtr - generate initial value for function pointers */
913 /*-----------------------------------------------------------------*/
914 void
915 printIvalFuncPtr (sym_link * type, initList * ilist, struct dbuf_s * oBuf)
916 {
917   value *val;
918   int dLvl = 0;
919
920   if (ilist)
921     val = list2val (ilist);
922   else
923     val = valCastLiteral(type, 0.0);
924
925   if (!val) {
926     // an error has been thrown already
927     val = constCharVal (0);
928   }
929
930   if (IS_LITERAL(val->etype)) {
931     if (compareType(type, val->etype) == 0) {
932       werrorfl (ilist->filename, ilist->lineno, E_INCOMPAT_TYPES);
933       printFromToType (val->type, type);
934     }
935     printIvalCharPtr (NULL, type, val, oBuf);
936     return;
937   }
938
939   /* check the types   */
940   if ((dLvl = compareType (val->type, type->next)) <= 0)
941     {
942       dbuf_tprintf (oBuf, "\t!dw !constword\n", 0);
943       return;
944     }
945
946   /* now generate the name */
947   if (!val->sym)
948     {
949       if (port->use_dw_for_init)
950         {
951           dbuf_tprintf (oBuf, "\t!dws\n", val->name);
952         }
953       else
954         {
955           printPointerType (oBuf, val->name);
956         }
957     }
958   else if (port->use_dw_for_init)
959     {
960       dbuf_tprintf (oBuf, "\t!dws\n", val->sym->rname);
961     }
962   else
963     {
964       printPointerType (oBuf, val->sym->rname);
965     }
966
967   return;
968 }
969
970 /*-----------------------------------------------------------------*/
971 /* printIvalCharPtr - generates initial values for character pointers */
972 /*-----------------------------------------------------------------*/
973 int
974 printIvalCharPtr (symbol * sym, sym_link * type, value * val, struct dbuf_s * oBuf)
975 {
976   int size = 0;
977
978   /* PENDING: this is _very_ mcs51 specific, including a magic
979      number...
980      It's also endian specific.
981    */
982   size = getSize (type);
983
984   if (val->name && strlen (val->name))
985     {
986       if (size == 1)            /* This appears to be Z80 specific?? */
987         {
988           dbuf_tprintf (oBuf,
989                     "\t!dbs\n", val->name);
990         }
991       else if (size == FPTRSIZE)
992         {
993           if (port->use_dw_for_init)
994             {
995               dbuf_tprintf (oBuf, "\t!dws\n", val->name);
996             }
997           else
998             {
999               printPointerType (oBuf, val->name);
1000             }
1001         }
1002       else if (size == GPTRSIZE)
1003         {
1004           int type;
1005           if (IS_PTR (val->type)) {
1006             type = DCL_TYPE (val->type);
1007           } else {
1008             type = PTR_TYPE (SPEC_OCLS (val->etype));
1009           }
1010           if (val->sym && val->sym->isstrlit) {
1011             // this is a literal string
1012             type=CPOINTER;
1013           }
1014           printGPointerType (oBuf, val->name, sym->name, type);
1015         }
1016       else
1017         {
1018           fprintf (stderr, "*** internal error: unknown size in "
1019                    "printIvalCharPtr.\n");
1020         }
1021     }
1022   else
1023     {
1024       // these are literals assigned to pointers
1025       switch (size)
1026         {
1027         case 1:
1028           dbuf_tprintf (oBuf, "\t!dbs\n", aopLiteral (val, 0));
1029           break;
1030         case 2:
1031           if (port->use_dw_for_init)
1032             dbuf_tprintf (oBuf, "\t!dws\n", aopLiteralLong (val, 0, size));
1033           else if (port->little_endian)
1034             dbuf_tprintf (oBuf, "\t.byte %s,%s\n",
1035                       aopLiteral (val, 0), aopLiteral (val, 1));
1036           else
1037             dbuf_tprintf (oBuf, "\t.byte %s,%s\n",
1038                       aopLiteral (val, 1), aopLiteral (val, 0));
1039           break;
1040         case 3:
1041           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
1042             // non-zero mcs51 generic pointer
1043             werrorfl (sym->fileDef, sym->lineDef, E_LITERAL_GENERIC);
1044           }
1045           if (port->little_endian) {
1046             dbuf_printf (oBuf, "\t.byte %s,%s,%s\n",
1047                      aopLiteral (val, 0),
1048                      aopLiteral (val, 1),
1049                      aopLiteral (val, 2));
1050           } else {
1051             dbuf_printf (oBuf, "\t.byte %s,%s,%s\n",
1052                      aopLiteral (val, 2),
1053                      aopLiteral (val, 1),
1054                      aopLiteral (val, 0));
1055           }
1056           break;
1057         case 4:
1058           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
1059             // non-zero ds390 generic pointer
1060             werrorfl (sym->fileDef, sym->lineDef, E_LITERAL_GENERIC);
1061           }
1062           if (port->little_endian) {
1063             dbuf_printf (oBuf, "\t.byte %s,%s,%s,%s\n",
1064                      aopLiteral (val, 0),
1065                      aopLiteral (val, 1),
1066                      aopLiteral (val, 2),
1067                      aopLiteral (val, 3));
1068           } else {
1069             dbuf_printf (oBuf, "\t.byte %s,%s,%s,%s\n",
1070                      aopLiteral (val, 3),
1071                      aopLiteral (val, 2),
1072                      aopLiteral (val, 1),
1073                      aopLiteral (val, 0));
1074           }
1075           break;
1076         default:
1077           assert (0);
1078         }
1079     }
1080
1081   if (!noInit && val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
1082     addSet (&statsg->syms, val->sym);
1083   }
1084
1085   return 1;
1086 }
1087
1088 /*-----------------------------------------------------------------*/
1089 /* printIvalPtr - generates initial value for pointers             */
1090 /*-----------------------------------------------------------------*/
1091 void
1092 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, struct dbuf_s * oBuf)
1093 {
1094   value *val;
1095   int size;
1096
1097   /* if deep then   */
1098   if (ilist && (ilist->type == INIT_DEEP))
1099     ilist = ilist->init.deep;
1100
1101   /* function pointer     */
1102   if (IS_FUNC (type->next))
1103     {
1104       printIvalFuncPtr (type, ilist, oBuf);
1105       return;
1106     }
1107
1108   if (!(val = initPointer (ilist, type)))
1109     return;
1110
1111   /* if character pointer */
1112   if (IS_CHAR (type->next))
1113     if (printIvalCharPtr (sym, type, val, oBuf))
1114       return;
1115
1116   /* check the type      */
1117   if (compareType (type, val->type) == 0) {
1118     werrorfl (ilist->filename, ilist->lineno, W_INIT_WRONG);
1119     printFromToType (val->type, type);
1120   }
1121
1122   /* if val is literal */
1123   if (IS_LITERAL (val->etype))
1124     {
1125       switch (getSize (type))
1126         {
1127         case 1:
1128           dbuf_tprintf (oBuf, "\t!db !constbyte\n", (unsigned int) ulFromVal (val) & 0xff);
1129           break;
1130         case 2:
1131           if (port->use_dw_for_init)
1132             dbuf_tprintf (oBuf, "\t!dws\n", aopLiteralLong (val, 0, 2));
1133           else if (port->little_endian)
1134             dbuf_tprintf (oBuf, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1135           else
1136             dbuf_tprintf (oBuf, "\t.byte %s,%s\n", aopLiteral (val, 1), aopLiteral (val, 0));
1137           break;
1138         case 3: // how about '390??
1139           dbuf_printf (oBuf, "; generic printIvalPtr\n");
1140           if (port->little_endian)
1141             {
1142               dbuf_printf (oBuf, "\t.byte %s,%s",
1143                        aopLiteral (val, 0), aopLiteral (val, 1));
1144             }
1145           else
1146             {
1147               dbuf_printf (oBuf, "\t.byte %s,%s",
1148                        aopLiteral (val, 1), aopLiteral (val, 0));
1149             }
1150           if (IS_GENPTR (val->type))
1151             dbuf_printf (oBuf, ",%s\n", aopLiteral (val, 2));
1152           else if (IS_PTR (val->type))
1153             dbuf_printf (oBuf, ",#%x\n", pointerTypeToGPByte (DCL_TYPE (val->type), NULL, NULL));
1154           else
1155             dbuf_printf (oBuf, ",%s\n", aopLiteral (val, 2));
1156         }
1157       return;
1158     }
1159
1160
1161   size = getSize (type);
1162
1163   if (size == 1)                /* Z80 specific?? */
1164     {
1165       dbuf_tprintf (oBuf, "\t!dbs\n", val->name);
1166     }
1167   else if (size == FPTRSIZE)
1168     {
1169       if (port->use_dw_for_init) {
1170         dbuf_tprintf (oBuf, "\t!dws\n", val->name);
1171       } else {
1172         printPointerType (oBuf, val->name);
1173       }
1174     }
1175   else if (size == GPTRSIZE)
1176     {
1177       printGPointerType (oBuf, val->name, sym->name,
1178                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1179                           PTR_TYPE (SPEC_OCLS (val->etype))));
1180     }
1181   return;
1182 }
1183
1184 /*-----------------------------------------------------------------*/
1185 /* printIval - generates code for initial value                    */
1186 /*-----------------------------------------------------------------*/
1187 void
1188 printIval (symbol * sym, sym_link * type, initList * ilist, struct dbuf_s * oBuf, bool check)
1189 {
1190   sym_link *itype;
1191
1192   /* if structure then    */
1193   if (IS_STRUCT (type))
1194     {
1195       printIvalStruct (sym, type, ilist, oBuf);
1196       return;
1197     }
1198
1199   /* if this is an array   */
1200   if (IS_ARRAY (type))
1201     {
1202       printIvalArray (sym, type, ilist, oBuf, check);
1203       return;
1204     }
1205
1206   if (ilist)
1207     {
1208       // not an aggregate, ilist must be a node
1209       if (ilist->type!=INIT_NODE) {
1210           // or a 1-element list
1211         if (ilist->init.deep->next) {
1212           werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "scalar",
1213                   sym->name);
1214         } else {
1215           ilist=ilist->init.deep;
1216         }
1217       }
1218
1219       // and the type must match
1220       itype=ilist->init.node->ftype;
1221
1222       if (compareType(type, itype)==0) {
1223         // special case for literal strings
1224         if (IS_ARRAY (itype) && IS_CHAR (getSpec(itype)) &&
1225             // which are really code pointers
1226             IS_PTR(type) && DCL_TYPE(type)==CPOINTER) {
1227           // no sweat
1228         } else {
1229           werrorfl (ilist->filename, ilist->lineno, E_TYPE_MISMATCH, "assignment", " ");
1230           printFromToType(itype, type);
1231         }
1232       }
1233     }
1234
1235   /* if this is a pointer */
1236   if (IS_PTR (type))
1237     {
1238       printIvalPtr (sym, type, ilist, oBuf);
1239       return;
1240     }
1241
1242   /* if type is SPECIFIER */
1243   if (IS_SPEC (type))
1244     {
1245       printIvalType (sym, type, ilist, oBuf);
1246       return;
1247     }
1248 }
1249
1250 /*-----------------------------------------------------------------*/
1251 /* emitStaticSeg - emitcode for the static segment                 */
1252 /*-----------------------------------------------------------------*/
1253 void
1254 emitStaticSeg (memmap * map, struct dbuf_s * oBuf)
1255 {
1256   symbol *sym;
1257
1258   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1259
1260   /* for all variables in this segment do */
1261   for (sym = setFirstItem (map->syms); sym;
1262        sym = setNextItem (map->syms))
1263     {
1264
1265       /* if it is "extern" then do nothing */
1266       if (IS_EXTERN (sym->etype))
1267         continue;
1268
1269       /* if it is not static add it to the public table */
1270       if (!IS_STATIC (sym->etype))
1271         {
1272           addSetHead (&publics, sym);
1273         }
1274
1275       /* print extra debug info if required */
1276       if (options.debug)
1277         {
1278           if (!sym->level)
1279             {                     /* global */
1280               if (IS_STATIC (sym->etype))
1281                 dbuf_printf (oBuf, "F%s$", moduleName);        /* scope is file */
1282               else
1283                 dbuf_printf (oBuf, "G$");      /* scope is global */
1284             }
1285           else
1286             {
1287               /* symbol is local */
1288               dbuf_printf (oBuf, "L%s$",
1289                            (sym->localof ? sym->localof->name : "-null-"));
1290             }
1291           dbuf_printf (oBuf, "%s$%d$%d", sym->name, sym->level, sym->block);
1292         }
1293
1294       /* if it has an absolute address and no initializer */
1295       if (SPEC_ABSA (sym->etype) && !sym->ival)
1296         {
1297           if (options.debug)
1298             dbuf_printf (oBuf, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1299
1300           dbuf_printf (oBuf, "%s\t=\t0x%04x\n",
1301                    sym->rname,
1302                    SPEC_ADDR (sym->etype));
1303         }
1304       else
1305         {
1306           if (options.debug)
1307             dbuf_printf (oBuf, " == .\n");
1308
1309           /* if it has an initial value */
1310           if (sym->ival)
1311             {
1312               if (SPEC_ABSA (sym->etype))
1313                 {
1314                   dbuf_tprintf (oBuf, "\t!org\n", SPEC_ADDR (sym->etype));
1315                 }
1316               dbuf_printf (oBuf, "%s:\n", sym->rname);
1317               ++noAlloc;
1318               resolveIvalSym (sym->ival, sym->type);
1319               printIval (sym, sym->type, sym->ival, oBuf, map != xinit);
1320               --noAlloc;
1321               /* if sym is a simple string and sym->ival is a string,
1322                  WE don't need it anymore */
1323               if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) &&
1324                   IS_AST_SYM_VALUE(list2expr(sym->ival)) &&
1325                   list2val(sym->ival)->sym->isstrlit) {
1326                 freeStringSymbol(list2val(sym->ival)->sym);
1327               }
1328             }
1329           else {
1330               /* allocate space */
1331               int size = getSize (sym->type);
1332
1333               if (size==0) {
1334                   werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE,sym->name);
1335               }
1336               dbuf_printf (oBuf, "%s:\n", sym->rname);
1337               /* special case for character strings */
1338               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1339                   SPEC_CVAL (sym->etype).v_char)
1340                   printChar (oBuf,
1341                              SPEC_CVAL (sym->etype).v_char,
1342                              size);
1343               else
1344                   dbuf_tprintf (oBuf, "\t!ds\n", (unsigned int) size & 0xffff);
1345             }
1346         }
1347     }
1348 }
1349
1350 /*-----------------------------------------------------------------*/
1351 /* emitMaps - emits the code for the data portion the code         */
1352 /*-----------------------------------------------------------------*/
1353 void
1354 emitMaps (void)
1355 {
1356   int publicsfr = TARGET_IS_MCS51; /* Ideally, this should be true for all  */
1357                                    /* ports but let's be conservative - EEP */
1358
1359   inInitMode++;
1360   /* no special considerations for the following
1361      data, idata & bit & xdata */
1362   emitRegularMap (data, TRUE, TRUE);
1363   emitRegularMap (idata, TRUE, TRUE);
1364   emitRegularMap (d_abs, TRUE, TRUE);
1365   emitRegularMap (i_abs, TRUE, TRUE);
1366   emitRegularMap (bit, TRUE, TRUE);
1367   emitRegularMap (pdata, TRUE, TRUE);
1368   emitRegularMap (xdata, TRUE, TRUE);
1369   emitRegularMap (x_abs, TRUE, TRUE);
1370   if (port->genXINIT) {
1371     emitRegularMap (xidata, TRUE, TRUE);
1372   }
1373   emitRegularMap (sfr, publicsfr, FALSE);
1374   emitRegularMap (sfrbit, publicsfr, FALSE);
1375   emitRegularMap (home, TRUE, FALSE);
1376   emitRegularMap (code, TRUE, FALSE);
1377
1378   if (options.const_seg) {
1379     dbuf_tprintf (&code->oBuf, "\t!area\n", options.const_seg);
1380   }
1381   emitStaticSeg (statsg, &code->oBuf);
1382   if (port->genXINIT) {
1383     dbuf_tprintf (&code->oBuf, "\t!area\n", xinit->sname);
1384     emitStaticSeg (xinit, &code->oBuf);
1385   }
1386   dbuf_tprintf (&code->oBuf, "\t!area\n", c_abs->sname);
1387   emitStaticSeg (c_abs, &code->oBuf);
1388   inInitMode--;
1389 }
1390
1391 /*-----------------------------------------------------------------*/
1392 /* flushStatics - flush all currently defined statics out to file  */
1393 /*  and delete.  Temporary function                                */
1394 /*-----------------------------------------------------------------*/
1395 void
1396 flushStatics (void)
1397 {
1398   emitStaticSeg (statsg, codeOutBuf);
1399   statsg->syms = NULL;
1400 }
1401
1402 /*-----------------------------------------------------------------*/
1403 /* createInterruptVect - creates the interrupt vector              */
1404 /*-----------------------------------------------------------------*/
1405 void
1406 createInterruptVect (struct dbuf_s *vBuf)
1407 {
1408   mainf = newSymbol ("main", 0);
1409   mainf->block = 0;
1410
1411   /* only if the main function exists */
1412   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1413     {
1414       if (!options.cc_only && !noAssemble && !options.c1mode)
1415         werror (E_NO_MAIN);
1416       return;
1417     }
1418
1419   /* if the main is only a prototype ie. no body then do nothing */
1420   if (!IFFUNC_HASBODY(mainf->type))
1421     {
1422       /* if ! compile only then main function should be present */
1423       if (!options.cc_only && !noAssemble)
1424         werror (E_NO_MAIN);
1425       return;
1426     }
1427
1428   dbuf_tprintf (vBuf, "\t!areacode\n", HOME_NAME);
1429   dbuf_printf (vBuf, "__interrupt_vect:\n");
1430
1431
1432   if (!port->genIVT || !(port->genIVT (vBuf, interrupts, maxInterrupts)))
1433     {
1434       /* There's no such thing as a "generic" interrupt table header. */
1435       wassert(0);
1436     }
1437 }
1438
1439 char *iComments1 =
1440 {
1441   ";--------------------------------------------------------\n"
1442   "; File Created by SDCC : free open source ANSI-C Compiler\n"};
1443
1444 char *iComments2 =
1445 {
1446   ";--------------------------------------------------------\n"};
1447
1448
1449 /*-----------------------------------------------------------------*/
1450 /* initialComments - puts in some initial comments                 */
1451 /*-----------------------------------------------------------------*/
1452 void
1453 initialComments (FILE * afile)
1454 {
1455   time_t t;
1456   time (&t);
1457   fprintf (afile, "%s", iComments1);
1458   fprintf (afile, "; Version " SDCC_VERSION_STR " #%s (%s) (%s)\n",
1459            getBuildNumber(), getBuildDate(), getBuildEnvironment());
1460   fprintf (afile, "; This file was generated %s", asctime (localtime (&t)));
1461   fprintf (afile, "%s", iComments2);
1462 }
1463
1464 /*-----------------------------------------------------------------*/
1465 /* printPublics - generates .global for publics                    */
1466 /*-----------------------------------------------------------------*/
1467 void
1468 printPublics (FILE * afile)
1469 {
1470   symbol *sym;
1471
1472   fprintf (afile, "%s", iComments2);
1473   fprintf (afile, "; Public variables in this module\n");
1474   fprintf (afile, "%s", iComments2);
1475
1476   for (sym = setFirstItem (publics); sym;
1477        sym = setNextItem (publics))
1478     tfprintf (afile, "\t!global\n", sym->rname);
1479 }
1480
1481 /*-----------------------------------------------------------------*/
1482 /* printExterns - generates .global for externs                    */
1483 /*-----------------------------------------------------------------*/
1484 void
1485 printExterns (FILE * afile)
1486 {
1487   symbol *sym;
1488
1489   fprintf (afile, "%s", iComments2);
1490   fprintf (afile, "; Externals used\n");
1491   fprintf (afile, "%s", iComments2);
1492
1493   for (sym = setFirstItem (externs); sym;
1494        sym = setNextItem (externs))
1495     tfprintf (afile, "\t!extern\n", sym->rname);
1496 }
1497
1498 /*-----------------------------------------------------------------*/
1499 /* emitOverlay - will emit code for the overlay stuff              */
1500 /*-----------------------------------------------------------------*/
1501 static void
1502 emitOverlay (struct dbuf_s * aBuf)
1503 {
1504   set *ovrset;
1505
1506   if (!elementsInSet (ovrSetSets))
1507     dbuf_tprintf (aBuf, "\t!area\n", port->mem.overlay_name);
1508
1509   /* for each of the sets in the overlay segment do */
1510   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1511        ovrset = setNextItem (ovrSetSets))
1512     {
1513
1514       symbol *sym;
1515
1516       if (elementsInSet (ovrset))
1517         {
1518           /* output the area informtion */
1519           dbuf_printf (aBuf, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1520         }
1521
1522       for (sym = setFirstItem (ovrset); sym;
1523            sym = setNextItem (ovrset))
1524         {
1525           /* if extern then it is in the publics table: do nothing */
1526           if (IS_EXTERN (sym->etype))
1527             continue;
1528
1529           /* if allocation required check is needed
1530              then check if the symbol really requires
1531              allocation only for local variables */
1532           if (!IS_AGGREGATE (sym->type) &&
1533               !(sym->_isparm && !IS_REGPARM (sym->etype))
1534               && !sym->allocreq && sym->level)
1535             continue;
1536
1537           /* if global variable & not static or extern
1538              and addPublics allowed then add it to the public set */
1539           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1540               && !IS_STATIC (sym->etype))
1541             {
1542               addSetHead (&publics, sym);
1543             }
1544
1545           /* if extern then do nothing or is a function
1546              then do nothing */
1547           if (IS_FUNC (sym->type))
1548             continue;
1549
1550           /* print extra debug info if required */
1551           if (options.debug)
1552             {
1553               if (!sym->level)
1554                 {               /* global */
1555                   if (IS_STATIC (sym->etype))
1556                     dbuf_printf (aBuf, "F%s$", moduleName);        /* scope is file */
1557                   else
1558                     dbuf_printf (aBuf, "G$");      /* scope is global */
1559                 }
1560               else
1561                 /* symbol is local */
1562                 dbuf_printf (aBuf, "L%s$",
1563                          (sym->localof ? sym->localof->name : "-null-"));
1564               dbuf_printf (aBuf, "%s$%d$%d", sym->name, sym->level, sym->block);
1565             }
1566
1567           /* if is has an absolute address then generate
1568              an equate for this no need to allocate space */
1569           if (SPEC_ABSA (sym->etype))
1570             {
1571
1572               if (options.debug)
1573                 dbuf_printf (aBuf, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1574
1575               dbuf_printf (aBuf, "%s\t=\t0x%04x\n",
1576                        sym->rname,
1577                        SPEC_ADDR (sym->etype));
1578             }
1579           else
1580             {
1581               int size = getSize(sym->type);
1582
1583               if (size==0) {
1584                   werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE);
1585               }
1586               if (options.debug)
1587                   dbuf_printf (aBuf, "==.\n");
1588
1589               /* allocate space */
1590               dbuf_tprintf (aBuf, "!labeldef\n", sym->rname);
1591               dbuf_tprintf (aBuf, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1592           }
1593
1594         }
1595     }
1596 }
1597
1598 /*-----------------------------------------------------------------*/
1599 /* glue - the final glue that hold the whole thing together        */
1600 /*-----------------------------------------------------------------*/
1601 void
1602 glue (void)
1603 {
1604   struct dbuf_s vBuf;
1605   struct dbuf_s ovrBuf;
1606   FILE *asmFile;
1607   int mcs51_like;
1608
1609   dbuf_init (&vBuf, 4096);
1610   dbuf_init (&ovrBuf, 4096);
1611
1612   mcs51_like = (port->general.glue_up_main &&
1613     (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51 || TARGET_IS_DS400));
1614
1615   /* print the global struct definitions */
1616   if (options.debug)
1617     cdbStructBlock (0);
1618
1619   /* PENDING: this isn't the best place but it will do */
1620   if (port->general.glue_up_main)
1621     {
1622       /* create the interrupt vector table */
1623       createInterruptVect (&vBuf);
1624     }
1625
1626   /* emit code for the all the variables declared */
1627   emitMaps ();
1628   /* do the overlay segments */
1629   emitOverlay (&ovrBuf);
1630
1631   outputDebugSymbols ();
1632
1633   /* now put it all together into the assembler file */
1634   /* create the assembler file name */
1635
1636   /* -o option overrides default name? */
1637   if ((noAssemble || options.c1mode) && fullDstFileName)
1638     {
1639       strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1640     }
1641   else
1642     {
1643       strncpyz (scratchFileName, dstFileName, PATH_MAX);
1644       strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1645     }
1646
1647   if (!(asmFile = fopen (scratchFileName, "w")))
1648     {
1649       werror (E_FILE_OPEN_ERR, scratchFileName);
1650       exit (EXIT_FAILURE);
1651     }
1652
1653   /* initial comments */
1654   initialComments (asmFile);
1655
1656   /* print module name */
1657   tfprintf (asmFile, "\t!module\n", moduleName);
1658   if (mcs51_like)
1659     {
1660       fprintf (asmFile, "\t.optsdcc -m%s", port->target);
1661
1662       switch(options.model)
1663         {
1664         case MODEL_SMALL:   fprintf (asmFile, " --model-small");   break;
1665         case MODEL_COMPACT: fprintf (asmFile, " --model-compact"); break;
1666         case MODEL_MEDIUM:  fprintf (asmFile, " --model-medium");  break;
1667         case MODEL_LARGE:   fprintf (asmFile, " --model-large");   break;
1668         case MODEL_FLAT24:  fprintf (asmFile, " --model-flat24");  break;
1669         case MODEL_PAGE0:   fprintf (asmFile, " --model-page0");   break;
1670         default: break;
1671         }
1672       /*if(options.stackAuto)      fprintf (asmFile, " --stack-auto");*/
1673       if(options.useXstack)      fprintf (asmFile, " --xstack");
1674       /*if(options.intlong_rent)   fprintf (asmFile, " --int-long-rent");*/
1675       /*if(options.float_rent)     fprintf (asmFile, " --float-rent");*/
1676       if(options.noRegParams)    fprintf (asmFile, " --no-reg-params");
1677       if(options.parms_in_bank1) fprintf (asmFile, " --parms-in-bank1");
1678       fprintf (asmFile, "\n");
1679     }
1680   else if (TARGET_Z80_LIKE || TARGET_IS_HC08)
1681     {
1682       fprintf (asmFile, "\t.optsdcc -m%s\n", port->target);
1683     }
1684
1685   tfprintf (asmFile, "\t!fileprelude\n");
1686
1687   /* Let the port generate any global directives, etc. */
1688   if (port->genAssemblerPreamble)
1689     {
1690       port->genAssemblerPreamble (asmFile);
1691     }
1692
1693   /* print the global variables in this module */
1694   printPublics (asmFile);
1695   if (port->assembler.externGlobal)
1696     printExterns (asmFile);
1697
1698   if (( mcs51_like )
1699      ||( TARGET_IS_Z80 )) /*.p.t.20030924 need to output SFR table for Z80 as well */
1700     {
1701       /* copy the sfr segment */
1702       fprintf (asmFile, "%s", iComments2);
1703       fprintf (asmFile, "; special function registers\n");
1704       fprintf (asmFile, "%s", iComments2);
1705       dbuf_write_and_destroy (&sfr->oBuf, asmFile);
1706     }
1707
1708   if (mcs51_like)
1709     {
1710       /* copy the sbit segment */
1711       fprintf (asmFile, "%s", iComments2);
1712       fprintf (asmFile, "; special function bits\n");
1713       fprintf (asmFile, "%s", iComments2);
1714       dbuf_write_and_destroy (&sfrbit->oBuf, asmFile);
1715
1716       /*JCF: Create the areas for the register banks*/
1717       if (RegBankUsed[0] || RegBankUsed[1] || RegBankUsed[2] || RegBankUsed[3])
1718         {
1719           fprintf (asmFile, "%s", iComments2);
1720           fprintf (asmFile, "; overlayable register banks\n");
1721           fprintf (asmFile, "%s", iComments2);
1722           if (RegBankUsed[0])
1723             fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1724           if (RegBankUsed[1] || options.parms_in_bank1)
1725             fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1726           if (RegBankUsed[2])
1727             fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1728           if (RegBankUsed[3])
1729             fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1730         }
1731       if (BitBankUsed)
1732         {
1733           fprintf (asmFile, "%s", iComments2);
1734           fprintf (asmFile, "; overlayable bit register bank\n");
1735           fprintf (asmFile, "%s", iComments2);
1736           fprintf (asmFile, "\t.area BIT_BANK\t(REL,OVR,DATA)\n");
1737           fprintf (asmFile, "bits:\n\t.ds 1\n");
1738           fprintf (asmFile, "\tb0 = bits[0]\n");
1739           fprintf (asmFile, "\tb1 = bits[1]\n");
1740           fprintf (asmFile, "\tb2 = bits[2]\n");
1741           fprintf (asmFile, "\tb3 = bits[3]\n");
1742           fprintf (asmFile, "\tb4 = bits[4]\n");
1743           fprintf (asmFile, "\tb5 = bits[5]\n");
1744           fprintf (asmFile, "\tb6 = bits[6]\n");
1745           fprintf (asmFile, "\tb7 = bits[7]\n");
1746         }
1747     }
1748
1749   /* copy the data segment */
1750   fprintf (asmFile, "%s", iComments2);
1751   fprintf (asmFile, "; %s ram data\n", mcs51_like?"internal":"");
1752   fprintf (asmFile, "%s", iComments2);
1753   dbuf_write_and_destroy (&data->oBuf, asmFile);
1754
1755
1756   /* create the overlay segments */
1757   if (overlay)
1758     {
1759       fprintf (asmFile, "%s", iComments2);
1760       fprintf (asmFile, "; overlayable items in %s ram \n", mcs51_like?"internal":"");
1761       fprintf (asmFile, "%s", iComments2);
1762       dbuf_write_and_destroy (&ovrBuf, asmFile);
1763     }
1764
1765   /* create the stack segment MOF */
1766   if (mainf && IFFUNC_HASBODY (mainf->type))
1767     {
1768       fprintf (asmFile, "%s", iComments2);
1769       fprintf (asmFile, "; Stack segment in internal ram \n");
1770       fprintf (asmFile, "%s", iComments2);
1771       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1772                "__start__stack:\n\t.ds\t1\n\n");
1773     }
1774
1775   /* create the idata segment */
1776   if ((idata) && (mcs51_like))
1777     {
1778       fprintf (asmFile, "%s", iComments2);
1779       fprintf (asmFile, "; indirectly addressable internal ram data\n");
1780       fprintf (asmFile, "%s", iComments2);
1781       dbuf_write_and_destroy (&idata->oBuf, asmFile);
1782     }
1783
1784   /* create the absolute idata/data segment */
1785   if ((i_abs) && (mcs51_like))
1786     {
1787       fprintf (asmFile, "%s", iComments2);
1788       fprintf (asmFile, "; absolute internal ram data\n");
1789       fprintf (asmFile, "%s", iComments2);
1790       dbuf_write_and_destroy (&d_abs->oBuf, asmFile);
1791       dbuf_write_and_destroy (&i_abs->oBuf, asmFile);
1792     }
1793
1794   /* copy the bit segment */
1795   if (mcs51_like)
1796     {
1797       fprintf (asmFile, "%s", iComments2);
1798       fprintf (asmFile, "; bit data\n");
1799       fprintf (asmFile, "%s", iComments2);
1800       dbuf_write_and_destroy (&bit->oBuf, asmFile);
1801     }
1802
1803   /* copy paged external ram data */
1804   if (mcs51_like)
1805     {
1806       fprintf (asmFile, "%s", iComments2);
1807       fprintf (asmFile, "; paged external ram data\n");
1808       fprintf (asmFile, "%s", iComments2);
1809       dbuf_write_and_destroy (&pdata->oBuf, asmFile);
1810     }
1811
1812   /* if external stack then reserve space for it */
1813   if (mainf && IFFUNC_HASBODY (mainf->type) && options.useXstack)
1814     {
1815       fprintf (asmFile, "%s", iComments2);
1816       fprintf (asmFile, "; external stack \n");
1817       fprintf (asmFile, "%s", iComments2);
1818       fprintf (asmFile, "\t.area XSTK (PAG,XDATA)\n"
1819                "__start__xstack:\n\t.ds\t1\n\n");
1820     }
1821
1822   /* copy external ram data */
1823   if (mcs51_like)
1824     {
1825       fprintf (asmFile, "%s", iComments2);
1826       fprintf (asmFile, "; external ram data\n");
1827       fprintf (asmFile, "%s", iComments2);
1828       dbuf_write_and_destroy (&xdata->oBuf, asmFile);
1829     }
1830
1831   /* create the absolute xdata segment */
1832   if (mcs51_like || TARGET_IS_HC08)
1833     {
1834       fprintf (asmFile, "%s", iComments2);
1835       fprintf (asmFile, "; absolute external ram data\n");
1836       fprintf (asmFile, "%s", iComments2);
1837       dbuf_write_and_destroy (&x_abs->oBuf, asmFile);
1838     }
1839
1840   /* copy external initialized ram data */
1841   fprintf (asmFile, "%s", iComments2);
1842   fprintf (asmFile, "; external initialized ram data\n");
1843   fprintf (asmFile, "%s", iComments2);
1844   dbuf_write_and_destroy (&xidata->oBuf, asmFile);
1845
1846   /* If the port wants to generate any extra areas, let it do so. */
1847   if (port->extraAreas.genExtraAreaDeclaration)
1848     {
1849       port->extraAreas.genExtraAreaDeclaration(asmFile,
1850                                                mainf && IFFUNC_HASBODY(mainf->type));
1851     }
1852
1853   /* copy the interrupt vector table */
1854   if (mainf && IFFUNC_HASBODY (mainf->type))
1855     {
1856       fprintf (asmFile, "%s", iComments2);
1857       fprintf (asmFile, "; interrupt vector \n");
1858       fprintf (asmFile, "%s", iComments2);
1859       dbuf_write_and_destroy (&vBuf, asmFile);
1860     }
1861
1862   /* copy global & static initialisations */
1863   fprintf (asmFile, "%s", iComments2);
1864   fprintf (asmFile, "; global & static initialisations\n");
1865   fprintf (asmFile, "%s", iComments2);
1866
1867   /* Everywhere we generate a reference to the static_name area,
1868    * (which is currently only here), we immediately follow it with a
1869    * definition of the post_static_name area. This guarantees that
1870    * the post_static_name area will immediately follow the static_name
1871    * area.
1872    */
1873   tfprintf (asmFile, "\t!area\n", port->mem.home_name);
1874   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1875   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1876   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1877
1878   if (mainf && IFFUNC_HASBODY (mainf->type))
1879     {
1880       if (port->genInitStartup)
1881         {
1882            port->genInitStartup (asmFile);
1883         }
1884       else
1885         {
1886           assert (mcs51_like);
1887           fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1888           /* if external stack is specified then the
1889              higher order byte of the xdatalocation is
1890              going into P2 and the lower order going into
1891              spx */
1892           if (options.useXstack)
1893             {
1894               fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1895                        (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1896               fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1897                        (unsigned int) options.xdata_loc & 0xff);
1898             }
1899
1900           // This should probably be a port option, but I'm being lazy.
1901           // on the 400, the firmware boot loader gives us a valid stack
1902           // (see '400 data sheet pg. 85 (TINI400 ROM Initialization code)
1903           if (!TARGET_IS_DS400)
1904             {
1905               /* initialise the stack pointer.  JCF: aslink takes care of the location */
1906               fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");     /* MOF */
1907             }
1908
1909           fprintf (asmFile, "\t%ccall\t__sdcc_external_startup\n", options.acall_ajmp?'a':'l');
1910           fprintf (asmFile, "\tmov\ta,dpl\n");
1911           fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1912           fprintf (asmFile, "\t%cjmp\t__sdcc_program_startup\n", options.acall_ajmp?'a':'l');
1913           fprintf (asmFile, "__sdcc_init_data:\n");
1914
1915           // if the port can copy the XINIT segment to XISEG
1916           if (port->genXINIT)
1917             {
1918               port->genXINIT (asmFile);
1919             }
1920         }
1921     }
1922   dbuf_write_and_destroy (&statsg->oBuf, asmFile);
1923
1924   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY (mainf->type))
1925     {
1926       /* This code is generated in the post-static area.
1927        * This area is guaranteed to follow the static area
1928        * by the ugly shucking and jiving about 20 lines ago.
1929        */
1930       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1931       fprintf (asmFile, "\t%cjmp\t__sdcc_program_startup\n", options.acall_ajmp?'a':'l');
1932     }
1933
1934   fprintf (asmFile,
1935            "%s"
1936            "; Home\n"
1937            "%s", iComments2, iComments2);
1938   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1939   dbuf_write_and_destroy (&home->oBuf, asmFile);
1940
1941   if (mainf && IFFUNC_HASBODY (mainf->type))
1942     {
1943       /* entry point @ start of HOME */
1944       fprintf (asmFile, "__sdcc_program_startup:\n");
1945
1946       /* put in jump or call to main */
1947       if (options.mainreturn)
1948         {
1949           fprintf (asmFile, "\t%cjmp\t_main\n", options.acall_ajmp?'a':'l');   /* needed? */
1950           fprintf (asmFile, ";\treturn from main will return to caller\n");
1951         }
1952       else
1953         {
1954           fprintf (asmFile, "\t%ccall\t_main\n", options.acall_ajmp?'a':'l');
1955           fprintf (asmFile, ";\treturn from main will lock up\n");
1956           fprintf (asmFile, "\tsjmp .\n");
1957         }
1958     }
1959   /* copy over code */
1960   fprintf (asmFile, "%s", iComments2);
1961   fprintf (asmFile, "; code\n");
1962   fprintf (asmFile, "%s", iComments2);
1963   tfprintf (asmFile, "\t!areacode\n", options.code_seg);
1964   dbuf_write_and_destroy (&code->oBuf, asmFile);
1965
1966   if (port->genAssemblerEnd)
1967     {
1968       port->genAssemblerEnd (asmFile);
1969     }
1970   fclose (asmFile);
1971 }