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