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