* doc/cdbfile.html: removed, replaced by cdbfileformat.lyx
[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[256];
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 extern char *VersionString;
49 set *pipeSet = NULL;            /* set of pipes */
50 set *tmpfileSet = NULL;         /* set of tmp file created by the compiler */
51 set *tmpfileNameSet = NULL;     /* All are unlinked at close. */
52
53 /*-----------------------------------------------------------------*/
54 /* closePipes - closes all pipes created by the compiler           */
55 /*-----------------------------------------------------------------*/
56 DEFSETFUNC (closePipes)
57 {
58   FILE *pfile = item;
59   int ret;
60
61   if (pfile) {
62     ret = pclose (pfile);
63     assert(ret != -1);
64   }
65
66   return 0;
67 }
68
69 /*-----------------------------------------------------------------*/
70 /* closeTmpFiles - closes all tmp files created by the compiler    */
71 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
72 /*-----------------------------------------------------------------*/
73 DEFSETFUNC (closeTmpFiles)
74 {
75   FILE *tfile = item;
76   int ret;
77
78   if (tfile) {
79     ret = fclose (tfile);
80     assert(ret == 0);
81   }
82
83   return 0;
84 }
85
86 /*-----------------------------------------------------------------*/
87 /* rmTmpFiles - unlinks all tmp files created by the compiler      */
88 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
89 /*-----------------------------------------------------------------*/
90 DEFSETFUNC (rmTmpFiles)
91 {
92   char *name = item;
93   int ret;
94
95   if (name) {
96       ret = unlink (name);
97       assert(ret == 0);
98       Safe_free (name);
99   }
100
101   return 0;
102 }
103
104 /*-----------------------------------------------------------------*/
105 /* rm_tmpfiles - close and remove temporary files and delete sets  */
106 /*-----------------------------------------------------------------*/
107 void
108 rm_tmpfiles (void)
109 {
110   /* close temporary files */
111   applyToSet (pipeSet, closePipes);
112   /* close temporary files */
113   deleteSet (&pipeSet);
114
115   applyToSet (tmpfileSet, closeTmpFiles);
116   /* remove temporary files */
117   applyToSet (tmpfileNameSet, rmTmpFiles);
118   /* delete temorary file sets */
119   deleteSet (&tmpfileSet);
120   deleteSet (&tmpfileNameSet);
121 }
122
123 /*-----------------------------------------------------------------*/
124 /* copyFile - copies source file to destination file               */
125 /*-----------------------------------------------------------------*/
126 void 
127 copyFile (FILE * dest, FILE * src)
128 {
129   int ch;
130
131   rewind (src);
132   while (!feof (src))
133     if ((ch = fgetc (src)) != EOF)
134       fputc (ch, dest);
135 }
136
137 char *
138 aopLiteralLong (value * val, int offset, int size)
139 {
140         union {
141                 float f;
142                 unsigned char c[4];
143         }
144         fl;
145
146         if (!val) {
147           // assuming we have been warned before
148           val=constVal("0");
149         }
150
151         /* if it is a float then it gets tricky */
152         /* otherwise it is fairly simple */
153         if (!IS_FLOAT (val->type)) {
154                 unsigned long v = (unsigned long) floatFromVal (val);
155
156                 v >>= (offset * 8);
157                 switch (size) {
158                 case 1:
159                         tsprintf (buffer, sizeof(buffer), 
160                                   "!immedbyte", (unsigned int) v & 0xff);
161                         break;
162                 case 2:
163                         tsprintf (buffer, sizeof(buffer), 
164                                   "!immedword", (unsigned int) v & 0xffff);
165                         break;
166                 default:
167                         /* Hmm.  Too big for now. */
168                         assert (0);
169                 }
170                 return Safe_strdup (buffer);
171         }
172
173         /* PENDING: For now size must be 1 */
174         assert (size == 1);
175
176         /* it is type float */
177         fl.f = (float) floatFromVal (val);
178 #ifdef WORDS_BIGENDIAN
179         tsprintf (buffer, sizeof(buffer), 
180                   "!immedbyte", fl.c[3 - offset]);
181 #else
182         tsprintf (buffer, sizeof(buffer), 
183                   "!immedbyte", fl.c[offset]);
184 #endif
185         return Safe_strdup (buffer);
186 }
187
188 /*-----------------------------------------------------------------*/
189 /* aopLiteral - string from a literal value                        */
190 /*-----------------------------------------------------------------*/
191 char *
192 aopLiteral (value * val, int offset)
193 {
194         return aopLiteralLong (val, offset, 1);
195 }
196
197 /*-----------------------------------------------------------------*/
198 /* emitRegularMap - emit code for maps with no special cases       */
199 /*-----------------------------------------------------------------*/
200 static void 
201 emitRegularMap (memmap * map, bool addPublics, bool arFlag)
202 {
203   symbol *sym;
204   ast *ival = NULL;
205
206   if (!map)
207     return;
208
209   if (addPublics)
210     {
211       /* PENDING: special case here - should remove */
212       if (!strcmp (map->sname, CODE_NAME))
213         tfprintf (map->oFile, "\t!areacode\n", map->sname);
214       else if (!strcmp (map->sname, DATA_NAME))
215         tfprintf (map->oFile, "\t!areadata\n", map->sname);
216       else if (!strcmp (map->sname, HOME_NAME))
217         tfprintf (map->oFile, "\t!areahome\n", map->sname);
218       else
219         tfprintf (map->oFile, "\t!area\n", map->sname);
220     }
221  
222   for (sym = setFirstItem (map->syms); sym;
223        sym = setNextItem (map->syms))
224     {
225       symbol *newSym=NULL;
226
227       /* if extern then add it into the extern list */
228       if (IS_EXTERN (sym->etype))
229         {
230           addSetHead (&externs, sym);
231           continue;
232         }
233
234       /* if allocation required check is needed
235          then check if the symbol really requires
236          allocation only for local variables */
237
238       if (arFlag && !IS_AGGREGATE (sym->type) &&
239           !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
240           !sym->allocreq && sym->level)
241         continue;
242
243       /* for bitvar locals and parameters */
244       if (!arFlag && !sym->allocreq && sym->level 
245           && !SPEC_ABSA (sym->etype)) {
246         continue;
247       }
248
249       /* if global variable & not static or extern
250          and addPublics allowed then add it to the public set */
251       if ((sym->level == 0 ||
252            (sym->_isparm && !IS_REGPARM (sym->etype))) &&
253           addPublics &&
254           !IS_STATIC (sym->etype) &&
255           (IS_FUNC(sym->type) ? (sym->used || IFFUNC_HASBODY(sym->type)) : 1))
256         {
257           addSetHead (&publics, sym);
258         }
259
260       /* if extern then do nothing or is a function
261          then do nothing */
262       if (IS_FUNC (sym->type))
263         continue;
264
265       /* print extra debug info if required */
266       if (options.debug)
267         {
268           if (!sym->level) /* global */
269             {
270               if (IS_STATIC (sym->etype))
271                 fprintf (map->oFile, "F%s$", moduleName); /* scope is file */
272               else
273                 fprintf (map->oFile, "G$");     /* scope is global */
274             }
275           else
276             {
277               /* symbol is local */
278               fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-"));
279             }
280           fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block);
281         }
282       
283       /* if it has an initial value then do it only if
284          it is a global variable */
285       if (sym->ival && sym->level == 0) {
286         if (SPEC_OCLS(sym->etype)==xidata) {
287           // create a new "XINIT (CODE)" symbol, that will be emitted later
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 (TARGET_IS_DS390) */
583   if (options.model == MODEL_FLAT24)
584     {
585       fprintf (oFile, "\t.byte %s,(%s >> 8),(%s >> 16)", name, name, name);
586     }
587   else
588     {
589       fprintf (oFile, "\t.byte %s,(%s >> 8)", name, name);
590     }
591 }
592
593 /*-----------------------------------------------------------------*/
594 /* printPointerType - generates ival for pointer type              */
595 /*-----------------------------------------------------------------*/
596 void 
597 printPointerType (FILE * oFile, const char *name)
598 {
599   _printPointerType (oFile, name);
600   fprintf (oFile, "\n");
601 }
602
603 /*-----------------------------------------------------------------*/
604 /* printGPointerType - generates ival for generic pointer type     */
605 /*-----------------------------------------------------------------*/
606 void 
607 printGPointerType (FILE * oFile, const char *iname, const char *oname,
608                    const unsigned int type)
609 {
610   _printPointerType (oFile, iname);
611   fprintf (oFile, ",#0x%02x\n", pointerTypeToGPByte (type, iname, oname));
612 }
613
614 /*-----------------------------------------------------------------*/
615 /* printIvalType - generates ival for int/char                     */
616 /*-----------------------------------------------------------------*/
617 void 
618 printIvalType (symbol *sym, sym_link * type, initList * ilist, FILE * oFile)
619 {
620         value *val;
621
622         /* if initList is deep */
623         if (ilist->type == INIT_DEEP)
624                 ilist = ilist->init.deep;
625
626         if (!IS_AGGREGATE(sym->type) && getNelements(type, ilist)>1) {
627           werror (W_EXCESS_INITIALIZERS, "scalar", sym->name, sym->lineDef);
628         }
629
630         if (!(val = list2val (ilist))) {
631           // assuming a warning has been thrown
632           val=constVal("0");
633         }
634
635         if (val->type != type) {
636           val = valCastLiteral(type, floatFromVal(val));
637         }
638         
639         switch (getSize (type)) {
640         case 1:
641                 if (!val)
642                         tfprintf (oFile, "\t!db !constbyte\n", 0);
643                 else
644                         tfprintf (oFile, "\t!dbs\n",
645                                   aopLiteral (val, 0));
646                 break;
647
648         case 2:
649                 if (port->use_dw_for_init)
650                         tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
651                 else
652                         fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
653                 break;
654         case 4:
655                 if (!val) {
656                         tfprintf (oFile, "\t!dw !constword\n", 0);
657                         tfprintf (oFile, "\t!dw !constword\n", 0);
658                 }
659                 else {
660                         fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
661                                  aopLiteral (val, 0), aopLiteral (val, 1),
662                                  aopLiteral (val, 2), aopLiteral (val, 3));
663                 }
664                 break;
665         }
666 }
667
668 /*-----------------------------------------------------------------*/
669 /* printIvalBitFields - generate initializer for bitfields         */
670 /*-----------------------------------------------------------------*/
671 void printIvalBitFields(symbol **sym, initList **ilist, FILE * oFile)
672 {
673         value *val ;
674         symbol *lsym = *sym;
675         initList *lilist = *ilist ;
676         unsigned long ival = 0;
677         int size =0;
678
679         
680         do {
681                 unsigned long i;
682                 val = list2val(lilist);
683                 if (size) {
684                         if (SPEC_BLEN(lsym->etype) > 8) {
685                                 size += ((SPEC_BLEN (lsym->etype) / 8) + 
686                                          (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
687                         }
688                 } else {
689                         size = ((SPEC_BLEN (lsym->etype) / 8) + 
690                                  (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
691                 }
692                 i = (unsigned long)floatFromVal(val);
693                 i <<= SPEC_BSTR (lsym->etype);
694                 ival |= i;
695                 if (! ( lsym->next &&
696                         (IS_BITFIELD(lsym->next->type)) &&
697                         (SPEC_BSTR(lsym->next->etype)))) break;
698                 lsym = lsym->next;
699                 lilist = lilist->next;
700         } while (1);
701         switch (size) {
702         case 1:
703                 tfprintf (oFile, "\t!db !constbyte\n",ival);
704                 break;
705
706         case 2:
707                 tfprintf (oFile, "\t!dw !constword\n",ival);
708                 break;
709         case 4:
710                 tfprintf (oFile, "\t!db  !constword,!constword\n",
711                          (ival >> 8) & 0xffff, (ival & 0xffff));
712                 break;
713         }
714         *sym = lsym;
715         *ilist = lilist;
716 }
717
718 /*-----------------------------------------------------------------*/
719 /* printIvalStruct - generates initial value for structures        */
720 /*-----------------------------------------------------------------*/
721 void 
722 printIvalStruct (symbol * sym, sym_link * type,
723                  initList * ilist, FILE * oFile)
724 {
725         symbol *sflds;
726         initList *iloop;
727
728         sflds = SPEC_STRUCT (type)->fields;
729         if (ilist->type != INIT_DEEP) {
730                 werror (E_INIT_STRUCT, sym->name);
731                 return;
732         }
733
734         iloop = ilist->init.deep;
735
736         for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) {
737                 if (IS_BITFIELD(sflds->type)) {
738                         printIvalBitFields(&sflds,&iloop,oFile);
739                 } else {
740                         printIval (sym, sflds->type, iloop, oFile);
741                 }
742         }
743         if (iloop) {
744           werror (W_EXCESS_INITIALIZERS, "struct", sym->name, sym->lineDef);
745         }
746         return;
747 }
748
749 /*-----------------------------------------------------------------*/
750 /* printIvalChar - generates initital value for character array    */
751 /*-----------------------------------------------------------------*/
752 int 
753 printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s)
754 {
755   value *val;
756   int remain;
757
758   if (!s)
759     {
760
761       val = list2val (ilist);
762       /* if the value is a character string  */
763       if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
764         {
765           if (!DCL_ELEM (type))
766             DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1;
767
768           printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type));
769
770           if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) - 1)) > 0)
771             while (remain--)
772               tfprintf (oFile, "\t!db !constbyte\n", 0);
773
774           return 1;
775         }
776       else
777         return 0;
778     }
779   else
780     printChar (oFile, s, strlen (s) + 1);
781   return 1;
782 }
783
784 /*-----------------------------------------------------------------*/
785 /* printIvalArray - generates code for array initialization        */
786 /*-----------------------------------------------------------------*/
787 void
788 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
789                 FILE * oFile)
790 {
791   initList *iloop;
792   int lcnt = 0, size = 0;
793   sym_link *last_type;
794
795   /* take care of the special   case  */
796   /* array of characters can be init  */
797   /* by a string                      */
798   if (IS_CHAR (type->next)) {
799     if (!IS_LITERAL(list2val(ilist)->etype)) {
800       werror (E_CONST_EXPECTED);
801       return;
802     }
803     if (printIvalChar (type,
804                        (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
805                        oFile, SPEC_CVAL (sym->etype).v_char))
806       return;
807   }
808   /* not the special case             */
809   if (ilist->type != INIT_DEEP)
810     {
811       werror (E_INIT_STRUCT, sym->name);
812       return;
813     }
814
815   iloop = ilist->init.deep;
816   lcnt = DCL_ELEM (type);
817   for (last_type = type->next; 
818        last_type && IS_DECL(last_type) && DCL_ELEM (last_type); 
819        last_type = last_type->next) {
820     lcnt *= DCL_ELEM (last_type);
821   }
822
823   for (;;)
824     {
825       size++;
826       printIval (sym, type->next, iloop, oFile);
827       iloop = (iloop ? iloop->next : NULL);
828
829
830       /* if not array limits given & we */
831       /* are out of initialisers then   */
832       if (!DCL_ELEM (type) && !iloop)
833         break;
834
835       /* no of elements given and we    */
836       /* have generated for all of them */
837       if (!--lcnt) {
838         /* if initializers left */
839         if (iloop) {
840           werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef);
841         }
842         break;
843       }
844     }
845
846   /* if we have not been given a size  */
847   if (!DCL_ELEM (type))
848     DCL_ELEM (type) = size;
849
850   return;
851 }
852
853 /*-----------------------------------------------------------------*/
854 /* printIvalFuncPtr - generate initial value for function pointers */
855 /*-----------------------------------------------------------------*/
856 void 
857 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
858 {
859   value *val;
860   int dLvl = 0;
861
862   val = list2val (ilist);
863
864   if (!val) {
865     // an error has been thrown allready
866     val=constVal("0");
867   }
868
869   if (IS_LITERAL(val->etype)) {
870     if (compareType(type,val->etype)==0) {
871       werror (E_INCOMPAT_TYPES);
872       printFromToType (val->type, type);
873     }
874     printIvalCharPtr (NULL, type, val, oFile);
875     return;
876   }
877
878   /* check the types   */
879   if ((dLvl = compareType (val->type, type->next)) <= 0)
880     {
881       tfprintf (oFile, "\t!dw !constword\n", 0);
882       return;
883     }
884
885   /* now generate the name */
886   if (!val->sym)
887     {
888       if (port->use_dw_for_init)
889         {
890           tfprintf (oFile, "\t!dws\n", val->name);
891         }
892       else
893         {
894           printPointerType (oFile, val->name);
895         }
896     }
897   else if (port->use_dw_for_init)
898     {
899       tfprintf (oFile, "\t!dws\n", val->sym->rname);
900     }
901   else
902     {
903       printPointerType (oFile, val->sym->rname);
904     }
905
906   return;
907 }
908
909 /*-----------------------------------------------------------------*/
910 /* printIvalCharPtr - generates initial values for character pointers */
911 /*-----------------------------------------------------------------*/
912 int 
913 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
914 {
915   int size = 0;
916
917   /* PENDING: this is _very_ mcs51 specific, including a magic
918      number...
919      It's also endin specific.
920    */
921   size = getSize (type);
922
923   if (val->name && strlen (val->name))
924     {
925       if (size == 1)            /* This appears to be Z80 specific?? */
926         {
927           tfprintf (oFile,
928                     "\t!dbs\n", val->name);
929         }
930       else if (size == FPTRSIZE)
931         {
932           if (port->use_dw_for_init)
933             {
934               tfprintf (oFile, "\t!dws\n", val->name);
935             }
936           else
937             {
938               printPointerType (oFile, val->name);
939             }
940         }
941       else if (size == GPTRSIZE)
942         {
943           int type;
944           if (IS_PTR (val->type)) {
945             type = DCL_TYPE (val->type);
946           } else {
947             type = PTR_TYPE (SPEC_OCLS (val->etype));
948           }
949           if (val->sym && val->sym->isstrlit) {
950             // this is a literal string
951             type=CPOINTER;
952           }
953           printGPointerType (oFile, val->name, sym->name, type);
954         }
955       else
956         {
957           fprintf (stderr, "*** internal error: unknown size in "
958                    "printIvalCharPtr.\n");
959         }
960     }
961   else
962     {
963       // these are literals assigned to pointers
964       switch (size)
965         {
966         case 1:
967           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
968           break;
969         case 2:
970           if (port->use_dw_for_init)
971             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
972           else
973             tfprintf (oFile, "\t.byte %s,%s\n",
974                       aopLiteral (val, 0), aopLiteral (val, 1));
975           break;
976         case 3:
977           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
978             // non-zero mcs51 generic pointer
979             werror (E_LITERAL_GENERIC);
980           }
981           fprintf (oFile, "\t.byte %s,%s,%s\n",
982                    aopLiteral (val, 0), 
983                    aopLiteral (val, 1),
984                    aopLiteral (val, 2));
985           break;
986         case 4:
987           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
988             // non-zero ds390 generic pointer
989             werror (E_LITERAL_GENERIC);
990           }
991           fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
992                    aopLiteral (val, 0), 
993                    aopLiteral (val, 1), 
994                    aopLiteral (val, 2),
995                    aopLiteral (val, 3));
996           break;
997         default:
998           assert (0);
999         }
1000     }
1001
1002   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
1003     addSet (&statsg->syms, val->sym);
1004   }
1005
1006   return 1;
1007 }
1008
1009 /*-----------------------------------------------------------------*/
1010 /* printIvalPtr - generates initial value for pointers             */
1011 /*-----------------------------------------------------------------*/
1012 void 
1013 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1014 {
1015   value *val;
1016   int size;
1017
1018   /* if deep then   */
1019   if (ilist->type == INIT_DEEP)
1020     ilist = ilist->init.deep;
1021
1022   /* function pointer     */
1023   if (IS_FUNC (type->next))
1024     {
1025       printIvalFuncPtr (type, ilist, oFile);
1026       return;
1027     }
1028
1029   if (!(val = initPointer (ilist, type)))
1030     return;
1031
1032   /* if character pointer */
1033   if (IS_CHAR (type->next))
1034     if (printIvalCharPtr (sym, type, val, oFile))
1035       return;
1036
1037   /* check the type      */
1038   if (compareType (type, val->type) == 0) {
1039     werror (W_INIT_WRONG);
1040     printFromToType (val->type, type);
1041   }
1042
1043   /* if val is literal */
1044   if (IS_LITERAL (val->etype))
1045     {
1046       switch (getSize (type))
1047         {
1048         case 1:
1049           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
1050           break;
1051         case 2:
1052           if (port->use_dw_for_init)
1053             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
1054           else
1055             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1056           break;
1057         case 3: // how about '390??
1058           fprintf (oFile, "\t.byte %s,%s,#0x%d\n",
1059                    aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE);
1060         }
1061       return;
1062     }
1063
1064
1065   size = getSize (type);
1066
1067   if (size == 1)                /* Z80 specific?? */
1068     {
1069       tfprintf (oFile, "\t!dbs\n", val->name);
1070     }
1071   else if (size == FPTRSIZE)
1072     {
1073       if (port->use_dw_for_init) {
1074         tfprintf (oFile, "\t!dws\n", val->name);
1075       } else {
1076         printPointerType (oFile, val->name);
1077       }
1078     }
1079   else if (size == GPTRSIZE)
1080     {
1081       printGPointerType (oFile, val->name, sym->name,
1082                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1083                           PTR_TYPE (SPEC_OCLS (val->etype))));
1084     }
1085   return;
1086 }
1087
1088 /*-----------------------------------------------------------------*/
1089 /* printIval - generates code for initial value                    */
1090 /*-----------------------------------------------------------------*/
1091 void 
1092 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1093 {
1094   if (!ilist)
1095     return;
1096
1097   /* update line number for error msgs */
1098   lineno=sym->lineDef;
1099
1100   /* if structure then    */
1101   if (IS_STRUCT (type))
1102     {
1103       printIvalStruct (sym, type, ilist, oFile);
1104       return;
1105     }
1106
1107   /* if this is a pointer */
1108   if (IS_PTR (type))
1109     {
1110       printIvalPtr (sym, type, ilist, oFile);
1111       return;
1112     }
1113
1114   /* if this is an array   */
1115   if (IS_ARRAY (type))
1116     {
1117       printIvalArray (sym, type, ilist, oFile);
1118       return;
1119     }
1120
1121   /* if type is SPECIFIER */
1122   if (IS_SPEC (type))
1123     {
1124       printIvalType (sym, type, ilist, oFile);
1125       return;
1126     }
1127 }
1128
1129 /*-----------------------------------------------------------------*/
1130 /* emitStaticSeg - emitcode for the static segment                 */
1131 /*-----------------------------------------------------------------*/
1132 void 
1133 emitStaticSeg (memmap * map, FILE * out)
1134 {
1135   symbol *sym;
1136
1137   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1138
1139   /* for all variables in this segment do */
1140   for (sym = setFirstItem (map->syms); sym;
1141        sym = setNextItem (map->syms))
1142     {
1143
1144       /* if it is "extern" then do nothing */
1145       if (IS_EXTERN (sym->etype))
1146         continue;
1147
1148       /* if it is not static add it to the public
1149          table */
1150       if (!IS_STATIC (sym->etype))
1151         {
1152           addSetHead (&publics, sym);
1153         }
1154
1155       /* print extra debug info if required */
1156       if (options.debug) {
1157
1158         if (!sym->level)
1159           {                     /* global */
1160             if (IS_STATIC (sym->etype))
1161               fprintf (out, "F%s$", moduleName);        /* scope is file */
1162             else
1163               fprintf (out, "G$");      /* scope is global */
1164           }
1165         else
1166           /* symbol is local */
1167           fprintf (out, "L%s$",
1168                    (sym->localof ? sym->localof->name : "-null-"));
1169         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1170       }
1171       
1172       /* if it has an absolute address */
1173       if (SPEC_ABSA (sym->etype))
1174         {
1175           if (options.debug)
1176             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1177           
1178           fprintf (out, "%s\t=\t0x%04x\n",
1179                    sym->rname,
1180                    SPEC_ADDR (sym->etype));
1181         }
1182       else
1183         {
1184           if (options.debug)
1185             fprintf (out, " == .\n");
1186           
1187           /* if it has an initial value */
1188           if (sym->ival)
1189             {
1190               fprintf (out, "%s:\n", sym->rname);
1191               noAlloc++;
1192               resolveIvalSym (sym->ival);
1193               printIval (sym, sym->type, sym->ival, out);
1194               noAlloc--;
1195               /* if sym is a simple string and sym->ival is a string, 
1196                  WE don't need it anymore */
1197               if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) &&
1198                   IS_AST_SYM_VALUE(list2expr(sym->ival)) &&
1199                   list2val(sym->ival)->sym->isstrlit) {
1200                 freeStringSymbol(list2val(sym->ival)->sym);
1201               }
1202             }
1203           else {
1204               /* allocate space */
1205               int size = getSize (sym->type);
1206               
1207               if (size==0) {
1208                   werror(E_UNKNOWN_SIZE,sym->name);
1209               }
1210               fprintf (out, "%s:\n", sym->rname);
1211               /* special case for character strings */
1212               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1213                   SPEC_CVAL (sym->etype).v_char)
1214                   printChar (out,
1215                              SPEC_CVAL (sym->etype).v_char,
1216                              strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1217               else
1218                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1219             }
1220         }
1221     }
1222 }
1223
1224 /*-----------------------------------------------------------------*/
1225 /* emitMaps - emits the code for the data portion the code         */
1226 /*-----------------------------------------------------------------*/
1227 void 
1228 emitMaps (void)
1229 {
1230   inInitMode++;
1231   /* no special considerations for the following
1232      data, idata & bit & xdata */
1233   emitRegularMap (data, TRUE, TRUE);
1234   emitRegularMap (idata, TRUE, TRUE);
1235   emitRegularMap (bit, TRUE, FALSE);
1236   emitRegularMap (xdata, TRUE, TRUE);
1237   if (port->genXINIT) {
1238     emitRegularMap (xidata, TRUE, TRUE);
1239   }
1240   emitRegularMap (sfr, FALSE, FALSE);
1241   emitRegularMap (sfrbit, FALSE, FALSE);
1242   emitRegularMap (home, TRUE, FALSE);
1243   emitRegularMap (code, TRUE, FALSE);
1244
1245   emitStaticSeg (statsg, code->oFile);
1246   if (port->genXINIT) {
1247     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1248     emitStaticSeg (xinit, code->oFile);
1249   }
1250   inInitMode--;
1251 }
1252
1253 /*-----------------------------------------------------------------*/
1254 /* flushStatics - flush all currently defined statics out to file  */
1255 /*  and delete.  Temporary function                                */
1256 /*-----------------------------------------------------------------*/
1257 void 
1258 flushStatics (void)
1259 {
1260   emitStaticSeg (statsg, codeOutFile);
1261   statsg->syms = NULL;
1262 }
1263
1264 /*-----------------------------------------------------------------*/
1265 /* createInterruptVect - creates the interrupt vector              */
1266 /*-----------------------------------------------------------------*/
1267 void 
1268 createInterruptVect (FILE * vFile)
1269 {
1270   unsigned i = 0;
1271   mainf = newSymbol ("main", 0);
1272   mainf->block = 0;
1273
1274   /* only if the main function exists */
1275   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1276     {
1277       if (!options.cc_only && !noAssemble && !options.c1mode)
1278         werror (E_NO_MAIN);
1279       return;
1280     }
1281
1282   /* if the main is only a prototype ie. no body then do nothing */
1283   if (!IFFUNC_HASBODY(mainf->type))
1284     {
1285       /* if ! compile only then main function should be present */
1286       if (!options.cc_only && !noAssemble)
1287         werror (E_NO_MAIN);
1288       return;
1289     }
1290
1291   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1292   fprintf (vFile, "__interrupt_vect:\n");
1293
1294
1295   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1296     {
1297       /* "generic" interrupt table header (if port doesn't specify one).
1298        * Look suspiciously like 8051 code to me...
1299        */
1300
1301       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1302
1303
1304       /* now for the other interrupts */
1305       for (; i < maxInterrupts; i++)
1306         {
1307           if (interrupts[i])
1308             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1309           else
1310             fprintf (vFile, "\treti\n\t.ds\t7\n");
1311         }
1312     }
1313 }
1314
1315 char *iComments1 =
1316 {
1317   ";--------------------------------------------------------\n"
1318   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1319
1320 char *iComments2 =
1321 {
1322   ";--------------------------------------------------------\n"};
1323
1324
1325 /*-----------------------------------------------------------------*/
1326 /* initialComments - puts in some initial comments                 */
1327 /*-----------------------------------------------------------------*/
1328 void 
1329 initialComments (FILE * afile)
1330 {
1331   time_t t;
1332   time (&t);
1333   fprintf (afile, "%s", iComments1);
1334   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1335   fprintf (afile, "%s", iComments2);
1336 }
1337
1338 /*-----------------------------------------------------------------*/
1339 /* printPublics - generates .global for publics                    */
1340 /*-----------------------------------------------------------------*/
1341 void 
1342 printPublics (FILE * afile)
1343 {
1344   symbol *sym;
1345
1346   fprintf (afile, "%s", iComments2);
1347   fprintf (afile, "; Public variables in this module\n");
1348   fprintf (afile, "%s", iComments2);
1349
1350   for (sym = setFirstItem (publics); sym;
1351        sym = setNextItem (publics))
1352     tfprintf (afile, "\t!global\n", sym->rname);
1353 }
1354
1355 /*-----------------------------------------------------------------*/
1356 /* printExterns - generates .global for externs                    */
1357 /*-----------------------------------------------------------------*/
1358 void 
1359 printExterns (FILE * afile)
1360 {
1361   symbol *sym;
1362
1363   fprintf (afile, "%s", iComments2);
1364   fprintf (afile, "; Externals used\n");
1365   fprintf (afile, "%s", iComments2);
1366
1367   for (sym = setFirstItem (externs); sym;
1368        sym = setNextItem (externs))
1369     tfprintf (afile, "\t!extern\n", sym->rname);
1370 }
1371
1372 /*-----------------------------------------------------------------*/
1373 /* emitOverlay - will emit code for the overlay stuff              */
1374 /*-----------------------------------------------------------------*/
1375 static void 
1376 emitOverlay (FILE * afile)
1377 {
1378   set *ovrset;
1379
1380   if (!elementsInSet (ovrSetSets))
1381     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1382
1383   /* for each of the sets in the overlay segment do */
1384   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1385        ovrset = setNextItem (ovrSetSets))
1386     {
1387
1388       symbol *sym;
1389
1390       if (elementsInSet (ovrset))
1391         {
1392           /* output the area informtion */
1393           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1394         }
1395
1396       for (sym = setFirstItem (ovrset); sym;
1397            sym = setNextItem (ovrset))
1398         {
1399           /* if extern then it is in the publics table: do nothing */
1400           if (IS_EXTERN (sym->etype))
1401             continue;
1402
1403           /* if allocation required check is needed
1404              then check if the symbol really requires
1405              allocation only for local variables */
1406           if (!IS_AGGREGATE (sym->type) &&
1407               !(sym->_isparm && !IS_REGPARM (sym->etype))
1408               && !sym->allocreq && sym->level)
1409             continue;
1410
1411           /* if global variable & not static or extern
1412              and addPublics allowed then add it to the public set */
1413           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1414               && !IS_STATIC (sym->etype))
1415             {
1416               addSetHead (&publics, sym);
1417             }
1418
1419           /* if extern then do nothing or is a function
1420              then do nothing */
1421           if (IS_FUNC (sym->type))
1422             continue;
1423
1424           /* print extra debug info if required */
1425           if (options.debug)
1426             {
1427               if (!sym->level)
1428                 {               /* global */
1429                   if (IS_STATIC (sym->etype))
1430                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1431                   else
1432                     fprintf (afile, "G$");      /* scope is global */
1433                 }
1434               else
1435                 /* symbol is local */
1436                 fprintf (afile, "L%s$",
1437                          (sym->localof ? sym->localof->name : "-null-"));
1438               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1439             }
1440
1441           /* if is has an absolute address then generate
1442              an equate for this no need to allocate space */
1443           if (SPEC_ABSA (sym->etype))
1444             {
1445
1446               if (options.debug)
1447                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1448
1449               fprintf (afile, "%s\t=\t0x%04x\n",
1450                        sym->rname,
1451                        SPEC_ADDR (sym->etype));
1452             }
1453           else {
1454               int size = getSize(sym->type);
1455
1456               if (size==0) {
1457                   werror(E_UNKNOWN_SIZE,sym->name);
1458               }       
1459               if (options.debug)
1460                   fprintf (afile, "==.\n");
1461               
1462               /* allocate space */
1463               tfprintf (afile, "!labeldef\n", sym->rname);
1464               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1465           }
1466           
1467         }
1468     }
1469 }
1470
1471 /*-----------------------------------------------------------------*/
1472 /* glue - the final glue that hold the whole thing together        */
1473 /*-----------------------------------------------------------------*/
1474 void 
1475 glue (void)
1476 {
1477   FILE *vFile;
1478   FILE *asmFile;
1479   FILE *ovrFile = tempfile ();
1480
1481   addSetHead (&tmpfileSet, ovrFile);
1482   /* print the global struct definitions */
1483   if (options.debug)
1484     cdbStructBlock (0);
1485
1486   vFile = tempfile ();
1487   /* PENDING: this isnt the best place but it will do */
1488   if (port->general.glue_up_main)
1489     {
1490       /* create the interrupt vector table */
1491       createInterruptVect (vFile);
1492     }
1493
1494   addSetHead (&tmpfileSet, vFile);
1495
1496   /* emit code for the all the variables declared */
1497   emitMaps ();
1498   /* do the overlay segments */
1499   emitOverlay (ovrFile);
1500
1501   outputDebugSymbols();
1502
1503   /* now put it all together into the assembler file */
1504   /* create the assembler file name */
1505
1506   /* -o option overrides default name? */
1507   if ((noAssemble || options.c1mode) && fullDstFileName)
1508     {
1509       strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1510     }
1511   else
1512     {
1513       strncpyz (scratchFileName, dstFileName, PATH_MAX);
1514       strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1515     }
1516
1517   if (!(asmFile = fopen (scratchFileName, "w")))
1518     {
1519       werror (E_FILE_OPEN_ERR, scratchFileName);
1520       exit (1);
1521     }
1522
1523   /* initial comments */
1524   initialComments (asmFile);
1525
1526   /* print module name */
1527   tfprintf (asmFile, "\t!module\n", moduleName);
1528   tfprintf (asmFile, "\t!fileprelude\n");
1529
1530   /* Let the port generate any global directives, etc. */
1531   if (port->genAssemblerPreamble)
1532     {
1533       port->genAssemblerPreamble (asmFile);
1534     }
1535
1536   /* print the global variables in this module */
1537   printPublics (asmFile);
1538   if (port->assembler.externGlobal)
1539     printExterns (asmFile);
1540
1541   /* copy the sfr segment */
1542   fprintf (asmFile, "%s", iComments2);
1543   fprintf (asmFile, "; special function registers\n");
1544   fprintf (asmFile, "%s", iComments2);
1545   copyFile (asmFile, sfr->oFile);
1546
1547   /* copy the sbit segment */
1548   fprintf (asmFile, "%s", iComments2);
1549   fprintf (asmFile, "; special function bits \n");
1550   fprintf (asmFile, "%s", iComments2);
1551   copyFile (asmFile, sfrbit->oFile);
1552   
1553   /*JCF: Create the areas for the register banks*/
1554   if(port->general.glue_up_main &&
1555      (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51))
1556   {
1557           if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1558           {
1559                  fprintf (asmFile, "%s", iComments2);
1560                  fprintf (asmFile, "; overlayable register banks \n");
1561                  fprintf (asmFile, "%s", iComments2);
1562                  if(RegBankUsed[0])
1563                         fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1564                  if(RegBankUsed[1]||options.parms_in_bank1)
1565                         fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1566                  if(RegBankUsed[2])
1567                         fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1568                  if(RegBankUsed[3])
1569                         fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1570           }
1571   }
1572
1573   /* copy the data segment */
1574   fprintf (asmFile, "%s", iComments2);
1575   fprintf (asmFile, "; internal ram data\n");
1576   fprintf (asmFile, "%s", iComments2);
1577   copyFile (asmFile, data->oFile);
1578
1579
1580   /* create the overlay segments */
1581   if (overlay) {
1582     fprintf (asmFile, "%s", iComments2);
1583     fprintf (asmFile, "; overlayable items in internal ram \n");
1584     fprintf (asmFile, "%s", iComments2);
1585     copyFile (asmFile, ovrFile);
1586   }
1587
1588   /* create the stack segment MOF */
1589   if (mainf && IFFUNC_HASBODY(mainf->type))
1590     {
1591       fprintf (asmFile, "%s", iComments2);
1592       fprintf (asmFile, "; Stack segment in internal ram \n");
1593       fprintf (asmFile, "%s", iComments2);
1594       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1595                "__start__stack:\n\t.ds\t1\n\n");
1596     }
1597
1598   /* create the idata segment */
1599   if (idata) {
1600     fprintf (asmFile, "%s", iComments2);
1601     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1602     fprintf (asmFile, "%s", iComments2);
1603     copyFile (asmFile, idata->oFile);
1604   }
1605
1606   /* copy the bit segment */
1607   fprintf (asmFile, "%s", iComments2);
1608   fprintf (asmFile, "; bit data\n");
1609   fprintf (asmFile, "%s", iComments2);
1610   copyFile (asmFile, bit->oFile);
1611
1612   /* if external stack then reserve space of it */
1613   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1614     {
1615       fprintf (asmFile, "%s", iComments2);
1616       fprintf (asmFile, "; external stack \n");
1617       fprintf (asmFile, "%s", iComments2);
1618       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1619       fprintf (asmFile, "\t.ds 256\n");
1620     }
1621
1622
1623   /* copy xtern ram data */
1624   fprintf (asmFile, "%s", iComments2);
1625   fprintf (asmFile, "; external ram data\n");
1626   fprintf (asmFile, "%s", iComments2);
1627   copyFile (asmFile, xdata->oFile);
1628
1629   /* copy xternal initialized ram data */
1630   fprintf (asmFile, "%s", iComments2);
1631   fprintf (asmFile, "; external initialized ram data\n");
1632   fprintf (asmFile, "%s", iComments2);
1633   copyFile (asmFile, xidata->oFile);
1634
1635   /* copy the interrupt vector table */
1636   if (mainf && IFFUNC_HASBODY(mainf->type))
1637     {
1638       fprintf (asmFile, "%s", iComments2);
1639       fprintf (asmFile, "; interrupt vector \n");
1640       fprintf (asmFile, "%s", iComments2);
1641       copyFile (asmFile, vFile);
1642     }
1643
1644   /* copy global & static initialisations */
1645   fprintf (asmFile, "%s", iComments2);
1646   fprintf (asmFile, "; global & static initialisations\n");
1647   fprintf (asmFile, "%s", iComments2);
1648
1649   /* Everywhere we generate a reference to the static_name area,
1650    * (which is currently only here), we immediately follow it with a
1651    * definition of the post_static_name area. This guarantees that
1652    * the post_static_name area will immediately follow the static_name
1653    * area.
1654    */
1655   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1656   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1657   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1658
1659   if (mainf && IFFUNC_HASBODY(mainf->type))
1660     {
1661       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1662       /* if external stack is specified then the
1663          higher order byte of the xdatalocation is
1664          going into P2 and the lower order going into
1665          spx */
1666       if (options.useXstack)
1667         {
1668           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1669                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1670           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1671                    (unsigned int) options.xdata_loc & 0xff);
1672         }
1673
1674       /* initialise the stack pointer.  JCF: aslink takes care of the location */
1675         fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");   /* MOF */
1676
1677       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1678       fprintf (asmFile, "\tmov\ta,dpl\n");
1679       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1680       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1681       fprintf (asmFile, "__sdcc_init_data:\n");
1682
1683       // if the port can copy the XINIT segment to XISEG
1684       if (port->genXINIT) {
1685         port->genXINIT(asmFile);
1686       }
1687
1688     }
1689   copyFile (asmFile, statsg->oFile);
1690
1691   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1692     {
1693       /* This code is generated in the post-static area.
1694        * This area is guaranteed to follow the static area
1695        * by the ugly shucking and jiving about 20 lines ago.
1696        */
1697       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1698       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1699     }
1700
1701   fprintf (asmFile,
1702            "%s"
1703            "; Home\n"
1704            "%s", iComments2, iComments2);
1705   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1706   copyFile (asmFile, home->oFile);
1707
1708   /* copy over code */
1709   fprintf (asmFile, "%s", iComments2);
1710   fprintf (asmFile, "; code\n");
1711   fprintf (asmFile, "%s", iComments2);
1712   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1713   if (mainf && IFFUNC_HASBODY(mainf->type))
1714     {
1715
1716       /* entry point @ start of CSEG */
1717       fprintf (asmFile, "__sdcc_program_startup:\n");
1718
1719       /* put in the call to main */
1720       fprintf (asmFile, "\tlcall\t_main\n");
1721       if (options.mainreturn)
1722         {
1723
1724           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1725           fprintf (asmFile, "\tret\n");
1726
1727         }
1728       else
1729         {
1730
1731           fprintf (asmFile, ";\treturn from main will lock up\n");
1732           fprintf (asmFile, "\tsjmp .\n");
1733         }
1734     }
1735   copyFile (asmFile, code->oFile);
1736
1737   if (port->genAssemblerEnd) {
1738       port->genAssemblerEnd(asmFile);
1739   }
1740   fclose (asmFile);
1741
1742   rm_tmpfiles ();
1743 }
1744
1745
1746 /** Creates a temporary file with unoque file name
1747     Scans, in order:
1748     - TMP, TEMP, TMPDIR env. varibles
1749     - if Un*x system: /usr/tmp and /tmp
1750     - root directory using mkstemp() if avaliable
1751     - default location using tempnam()
1752 */
1753 static int
1754 tempfileandname(char *fname, size_t len)
1755 {
1756 #define TEMPLATE      "sdccXXXXXX"
1757 #define TEMPLATE_LEN  ((sizeof TEMPLATE) - 1)
1758
1759   const char *tmpdir = NULL;
1760   int fd;
1761
1762   if ((tmpdir = getenv ("TMP")) == NULL)
1763     if ((tmpdir = getenv ("TEMP")) == NULL)
1764       tmpdir = getenv ("TMPDIR");
1765
1766 #ifndef _WIN32
1767   {
1768     /* try with /usr/tmp and /tmp on Un*x systems */
1769     struct stat statbuf;
1770
1771     if (tmpdir == NULL) {
1772       if (stat("/usr/tmp", &statbuf) != -1)
1773         tmpdir = "/usr/tmp";
1774       else if (stat("/tmp", &statbuf) != -1)
1775         tmpdir = "/tmp";
1776     }
1777   }
1778 #endif
1779
1780 #ifdef HAVE_MKSTEMP
1781   {
1782     char fnamebuf[PATH_MAX];
1783     size_t name_len;
1784
1785     if (fname == NULL || len == 0) {
1786       fname = fnamebuf;
1787       len = sizeof fnamebuf;
1788     }
1789
1790     if (tmpdir) {
1791       name_len = strlen(tmpdir) + 1 + TEMPLATE_LEN;
1792
1793       assert(name_len < len);
1794       if (!(name_len < len))  /* in NDEBUG is defined */
1795         return -1;            /* buffer too small, temporary file can not be created */
1796
1797       sprintf(fname, "%s" DIR_SEPARATOR_STRING TEMPLATE, tmpdir);
1798     }
1799     else {
1800       name_len = TEMPLATE_LEN;
1801
1802       assert(name_len < len);
1803       if (!(name_len < len))  /* in NDEBUG is defined */
1804         return -1;            /* buffer too small, temporary file can not be created */
1805
1806       strcpy(fname, TEMPLATE);
1807     }
1808
1809     fd = mkstemp(fname);
1810   }
1811 #else
1812   {
1813     char *name = tempnam(tmpdir, "sdcc");
1814
1815     if (name == NULL) {
1816       perror("Can't create temporary file name");
1817       exit(1);
1818     }
1819
1820     assert(strlen(name) < len);
1821     if (!(strlen(name) < len))  /* in NDEBUG is defined */
1822       return -1;                /* buffer too small, temporary file can not be created */
1823
1824     strcpy(fname, name);
1825 #ifdef _WIN32
1826     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IREAD | S_IWRITE);
1827 #else
1828     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IRUSR | S_IWUSR);
1829 #endif
1830   }
1831 #endif
1832
1833   if (fd == -1) {
1834     perror("Can't create temporary file");
1835     exit(1);
1836   }
1837
1838   return fd;
1839 }
1840
1841
1842 /** Create a temporary file name
1843 */
1844 char *
1845 tempfilename(void)
1846 {
1847   int fd;
1848   static char fnamebuf[PATH_MAX];
1849
1850   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1851     fprintf(stderr, "Can't create temporary file name!");
1852     exit(1);
1853   }
1854
1855   fd = close(fd);
1856   assert(fd != -1);
1857
1858   return fnamebuf;
1859 }
1860
1861
1862 /** Create a temporary file and add it to tmpfileNameSet,
1863     so that it is removed explicitly by rm_tmpfiles()
1864     or implicitly at program extit.
1865 */
1866 FILE *
1867 tempfile(void)
1868 {
1869   int fd;
1870   char *tmp;
1871   FILE *fp;
1872   char fnamebuf[PATH_MAX];
1873
1874   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1875     fprintf(stderr, "Can't create temporary file!");
1876     exit(1);
1877   }
1878
1879   tmp = Safe_strdup(fnamebuf);
1880   if (tmp)
1881     addSetHead(&tmpfileNameSet, tmp);
1882
1883   if ((fp = fdopen(fd, "w+b")) == NULL) {
1884       perror("Can't create temporary file!");
1885       exit(1);
1886   }
1887
1888   return fp;
1889 }