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