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