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