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