* src/SDCCast.c (createIvalCharPtr),
[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               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))));
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);
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
1358       /* now for the other interrupts */
1359       for (; i < maxInterrupts; i++)
1360         {
1361           if (interrupts[i])
1362             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1363           else
1364             fprintf (vFile, "\treti\n\t.ds\t7\n");
1365         }
1366     }
1367 }
1368
1369 char *iComments1 =
1370 {
1371   ";--------------------------------------------------------\n"
1372   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1373
1374 char *iComments2 =
1375 {
1376   ";--------------------------------------------------------\n"};
1377
1378
1379 /*-----------------------------------------------------------------*/
1380 /* initialComments - puts in some initial comments                 */
1381 /*-----------------------------------------------------------------*/
1382 void 
1383 initialComments (FILE * afile)
1384 {
1385   time_t t;
1386   time (&t);
1387   fprintf (afile, "%s", iComments1);
1388   fprintf (afile, "; Version " SDCC_VERSION_STR " %s\n", asctime (localtime (&t)));
1389   fprintf (afile, "%s", iComments2);
1390 }
1391
1392 /*-----------------------------------------------------------------*/
1393 /* printPublics - generates .global for publics                    */
1394 /*-----------------------------------------------------------------*/
1395 void 
1396 printPublics (FILE * afile)
1397 {
1398   symbol *sym;
1399
1400   fprintf (afile, "%s", iComments2);
1401   fprintf (afile, "; Public variables in this module\n");
1402   fprintf (afile, "%s", iComments2);
1403
1404   for (sym = setFirstItem (publics); sym;
1405        sym = setNextItem (publics))
1406     tfprintf (afile, "\t!global\n", sym->rname);
1407 }
1408
1409 /*-----------------------------------------------------------------*/
1410 /* printExterns - generates .global for externs                    */
1411 /*-----------------------------------------------------------------*/
1412 void 
1413 printExterns (FILE * afile)
1414 {
1415   symbol *sym;
1416
1417   fprintf (afile, "%s", iComments2);
1418   fprintf (afile, "; Externals used\n");
1419   fprintf (afile, "%s", iComments2);
1420
1421   for (sym = setFirstItem (externs); sym;
1422        sym = setNextItem (externs))
1423     tfprintf (afile, "\t!extern\n", sym->rname);
1424 }
1425
1426 /*-----------------------------------------------------------------*/
1427 /* emitOverlay - will emit code for the overlay stuff              */
1428 /*-----------------------------------------------------------------*/
1429 static void 
1430 emitOverlay (FILE * afile)
1431 {
1432   set *ovrset;
1433
1434   if (!elementsInSet (ovrSetSets))
1435     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1436
1437   /* for each of the sets in the overlay segment do */
1438   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1439        ovrset = setNextItem (ovrSetSets))
1440     {
1441
1442       symbol *sym;
1443
1444       if (elementsInSet (ovrset))
1445         {
1446           /* output the area informtion */
1447           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1448         }
1449
1450       for (sym = setFirstItem (ovrset); sym;
1451            sym = setNextItem (ovrset))
1452         {
1453           /* if extern then it is in the publics table: do nothing */
1454           if (IS_EXTERN (sym->etype))
1455             continue;
1456
1457           /* if allocation required check is needed
1458              then check if the symbol really requires
1459              allocation only for local variables */
1460           if (!IS_AGGREGATE (sym->type) &&
1461               !(sym->_isparm && !IS_REGPARM (sym->etype))
1462               && !sym->allocreq && sym->level)
1463             continue;
1464
1465           /* if global variable & not static or extern
1466              and addPublics allowed then add it to the public set */
1467           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1468               && !IS_STATIC (sym->etype))
1469             {
1470               addSetHead (&publics, sym);
1471             }
1472
1473           /* if extern then do nothing or is a function
1474              then do nothing */
1475           if (IS_FUNC (sym->type))
1476             continue;
1477
1478           /* print extra debug info if required */
1479           if (options.debug)
1480             {
1481               if (!sym->level)
1482                 {               /* global */
1483                   if (IS_STATIC (sym->etype))
1484                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1485                   else
1486                     fprintf (afile, "G$");      /* scope is global */
1487                 }
1488               else
1489                 /* symbol is local */
1490                 fprintf (afile, "L%s$",
1491                          (sym->localof ? sym->localof->name : "-null-"));
1492               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1493             }
1494
1495           /* if is has an absolute address then generate
1496              an equate for this no need to allocate space */
1497           if (SPEC_ABSA (sym->etype))
1498             {
1499
1500               if (options.debug)
1501                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1502
1503               fprintf (afile, "%s\t=\t0x%04x\n",
1504                        sym->rname,
1505                        SPEC_ADDR (sym->etype));
1506             }
1507           else {
1508               int size = getSize(sym->type);
1509
1510               if (size==0) {
1511                   werrorfl (filename, sym->lineDef, E_UNKNOWN_SIZE);
1512               }       
1513               if (options.debug)
1514                   fprintf (afile, "==.\n");
1515               
1516               /* allocate space */
1517               tfprintf (afile, "!labeldef\n", sym->rname);
1518               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1519           }
1520           
1521         }
1522     }
1523 }
1524
1525
1526 /*-----------------------------------------------------------------*/
1527 /* spacesToUnderscores - replace spaces with underscores        */
1528 /*-----------------------------------------------------------------*/
1529 static char *
1530 spacesToUnderscores (char *dest, const char *src, size_t len)
1531 {
1532   int i;
1533   char *p;
1534
1535   assert(dest != NULL);
1536   assert(src != NULL);
1537   assert(len > 0);
1538
1539   --len;
1540   for (p = dest, i = 0; *src != '\0' && i < len; ++src, ++i) {
1541     *p++ = isspace(*src) ? '_' : *src;
1542   }
1543   *p = '\0';
1544
1545   return dest;
1546 }
1547
1548
1549 /*-----------------------------------------------------------------*/
1550 /* glue - the final glue that hold the whole thing together        */
1551 /*-----------------------------------------------------------------*/
1552 void 
1553 glue (void)
1554 {
1555   FILE *vFile;
1556   FILE *asmFile;
1557   FILE *ovrFile = tempfile ();
1558   char moduleBuf[PATH_MAX];
1559   int mcs51_like;
1560
1561   if(port->general.glue_up_main &&
1562     (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51 || TARGET_IS_DS400))
1563   {
1564       mcs51_like=1; /*So it has bits, sfr, sbits, data, idata, etc...*/
1565   }
1566   else
1567   {
1568       mcs51_like=0;
1569   }
1570
1571   addSetHead (&tmpfileSet, ovrFile);
1572   /* print the global struct definitions */
1573   if (options.debug)
1574     cdbStructBlock (0);
1575
1576   vFile = tempfile ();
1577   /* PENDING: this isnt the best place but it will do */
1578   if (port->general.glue_up_main)
1579     {
1580       /* create the interrupt vector table */
1581       createInterruptVect (vFile);
1582     }
1583
1584   addSetHead (&tmpfileSet, vFile);
1585
1586   /* emit code for the all the variables declared */
1587   emitMaps ();
1588   /* do the overlay segments */
1589   emitOverlay (ovrFile);
1590
1591   outputDebugSymbols();
1592
1593   /* now put it all together into the assembler file */
1594   /* create the assembler file name */
1595
1596   /* -o option overrides default name? */
1597   if ((noAssemble || options.c1mode) && fullDstFileName)
1598     {
1599       strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1600     }
1601   else
1602     {
1603       strncpyz (scratchFileName, dstFileName, PATH_MAX);
1604       strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1605     }
1606
1607   if (!(asmFile = fopen (scratchFileName, "w")))
1608     {
1609       werror (E_FILE_OPEN_ERR, scratchFileName);
1610       exit (1);
1611     }
1612
1613   /* initial comments */
1614   initialComments (asmFile);
1615
1616   /* print module name */
1617   tfprintf (asmFile, "\t!module\n",
1618     spacesToUnderscores (moduleBuf, moduleName, sizeof moduleBuf));
1619   if(mcs51_like)
1620   {
1621     fprintf (asmFile, "\t.optsdcc -m%s", port->target);
1622
1623     switch(options.model)
1624     {
1625         case MODEL_SMALL:   fprintf (asmFile, " --model-small");   break;
1626         case MODEL_COMPACT: fprintf (asmFile, " --model-compact"); break;
1627         case MODEL_MEDIUM:  fprintf (asmFile, " --model-medium");  break;
1628         case MODEL_LARGE:   fprintf (asmFile, " --model-large");   break;
1629         case MODEL_FLAT24:  fprintf (asmFile, " --model-flat24");  break;
1630         case MODEL_PAGE0:   fprintf (asmFile, " --model-page0");   break;
1631         default: break;
1632     }
1633     /*if(options.stackAuto)      fprintf (asmFile, " --stack-auto");*/
1634     if(options.useXstack)      fprintf (asmFile, " --xstack");
1635     /*if(options.intlong_rent)   fprintf (asmFile, " --int-long-rent");*/
1636     /*if(options.float_rent)     fprintf (asmFile, " --float-rent");*/
1637     if(options.noRegParams)    fprintf (asmFile, " --no-reg-params");
1638     if(options.parms_in_bank1) fprintf (asmFile, " --parms-in-bank1");
1639     fprintf (asmFile, "\n");
1640   }
1641   else if(TARGET_IS_Z80 || TARGET_IS_GBZ80 )
1642   {
1643     fprintf (asmFile, "\t.optsdcc -m%s\n", port->target);
1644   }
1645
1646   tfprintf (asmFile, "\t!fileprelude\n");
1647
1648   /* Let the port generate any global directives, etc. */
1649   if (port->genAssemblerPreamble)
1650     {
1651       port->genAssemblerPreamble (asmFile);
1652     }
1653
1654   /* print the global variables in this module */
1655   printPublics (asmFile);
1656   if (port->assembler.externGlobal)
1657     printExterns (asmFile);
1658
1659   if(( mcs51_like )
1660    ||( TARGET_IS_Z80 )) /*.p.t.20030924 need to output SFR table for Z80 as well */
1661   {
1662       /* copy the sfr segment */
1663       fprintf (asmFile, "%s", iComments2);
1664       fprintf (asmFile, "; special function registers\n");
1665       fprintf (asmFile, "%s", iComments2);
1666       copyFile (asmFile, sfr->oFile);
1667   }
1668   
1669   if(mcs51_like)
1670   {
1671       /* copy the sbit segment */
1672       fprintf (asmFile, "%s", iComments2);
1673       fprintf (asmFile, "; special function bits \n");
1674       fprintf (asmFile, "%s", iComments2);
1675       copyFile (asmFile, sfrbit->oFile);
1676   
1677       /*JCF: Create the areas for the register banks*/
1678           if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1679           {
1680                  fprintf (asmFile, "%s", iComments2);
1681                  fprintf (asmFile, "; overlayable register banks \n");
1682                  fprintf (asmFile, "%s", iComments2);
1683                  if(RegBankUsed[0])
1684                         fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1685                  if(RegBankUsed[1]||options.parms_in_bank1)
1686                         fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1687                  if(RegBankUsed[2])
1688                         fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1689                  if(RegBankUsed[3])
1690                         fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1691           }
1692   }
1693
1694   /* copy the data segment */
1695   fprintf (asmFile, "%s", iComments2);
1696   fprintf (asmFile, "; %s ram data\n", mcs51_like?"internal":"");
1697   fprintf (asmFile, "%s", iComments2);
1698   copyFile (asmFile, data->oFile);
1699
1700
1701   /* create the overlay segments */
1702   if (overlay) {
1703     fprintf (asmFile, "%s", iComments2);
1704     fprintf (asmFile, "; overlayable items in %s ram \n", mcs51_like?"internal":"");
1705     fprintf (asmFile, "%s", iComments2);
1706     copyFile (asmFile, ovrFile);
1707   }
1708
1709   /* create the stack segment MOF */
1710   if (mainf && IFFUNC_HASBODY(mainf->type))
1711     {
1712       fprintf (asmFile, "%s", iComments2);
1713       fprintf (asmFile, "; Stack segment in internal ram \n");
1714       fprintf (asmFile, "%s", iComments2);
1715       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1716                "__start__stack:\n\t.ds\t1\n\n");
1717     }
1718
1719   /* create the idata segment */
1720   if ( (idata) && (mcs51_like) ) {
1721     fprintf (asmFile, "%s", iComments2);
1722     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1723     fprintf (asmFile, "%s", iComments2);
1724     copyFile (asmFile, idata->oFile);
1725   }
1726
1727   /* copy the bit segment */
1728   if (mcs51_like) {
1729     fprintf (asmFile, "%s", iComments2);
1730     fprintf (asmFile, "; bit data\n");
1731     fprintf (asmFile, "%s", iComments2);
1732     copyFile (asmFile, bit->oFile);
1733   }
1734
1735   /* if external stack then reserve space of it */
1736   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1737     {
1738       fprintf (asmFile, "%s", iComments2);
1739       fprintf (asmFile, "; external stack \n");
1740       fprintf (asmFile, "%s", iComments2);
1741       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1742       fprintf (asmFile, "\t.ds 256\n");
1743     }
1744
1745
1746   /* copy xtern ram data */
1747   if (mcs51_like) {
1748     fprintf (asmFile, "%s", iComments2);
1749     fprintf (asmFile, "; external ram data\n");
1750     fprintf (asmFile, "%s", iComments2);
1751     copyFile (asmFile, xdata->oFile);
1752   }
1753
1754   /* copy xternal initialized ram data */
1755   fprintf (asmFile, "%s", iComments2);
1756   fprintf (asmFile, "; external initialized ram data\n");
1757   fprintf (asmFile, "%s", iComments2);
1758   copyFile (asmFile, xidata->oFile);
1759
1760   /* If the port wants to generate any extra areas, let it do so. */
1761   if (port->extraAreas.genExtraAreaDeclaration)
1762   {
1763       port->extraAreas.genExtraAreaDeclaration(asmFile, 
1764                                                mainf && IFFUNC_HASBODY(mainf->type));
1765   }
1766     
1767   /* copy the interrupt vector table */
1768   if (mainf && IFFUNC_HASBODY(mainf->type))
1769     {
1770       fprintf (asmFile, "%s", iComments2);
1771       fprintf (asmFile, "; interrupt vector \n");
1772       fprintf (asmFile, "%s", iComments2);
1773       copyFile (asmFile, vFile);
1774     }
1775
1776   /* copy global & static initialisations */
1777   fprintf (asmFile, "%s", iComments2);
1778   fprintf (asmFile, "; global & static initialisations\n");
1779   fprintf (asmFile, "%s", iComments2);
1780
1781   /* Everywhere we generate a reference to the static_name area,
1782    * (which is currently only here), we immediately follow it with a
1783    * definition of the post_static_name area. This guarantees that
1784    * the post_static_name area will immediately follow the static_name
1785    * area.
1786    */
1787   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1788   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1789   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1790
1791   if (mainf && IFFUNC_HASBODY(mainf->type))
1792     {
1793       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1794       /* if external stack is specified then the
1795          higher order byte of the xdatalocation is
1796          going into P2 and the lower order going into
1797          spx */
1798       if (options.useXstack)
1799         {
1800           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1801                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1802           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1803                    (unsigned int) options.xdata_loc & 0xff);
1804         }
1805
1806         // This should probably be a port option, but I'm being lazy.
1807         // on the 400, the firmware boot loader gives us a valid stack
1808         // (see '400 data sheet pg. 85 (TINI400 ROM Initialization code)
1809         if (!TARGET_IS_DS400)
1810         {
1811             /* initialise the stack pointer.  JCF: aslink takes care of the location */
1812             fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");       /* MOF */
1813         }
1814
1815       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1816       fprintf (asmFile, "\tmov\ta,dpl\n");
1817       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1818       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1819       fprintf (asmFile, "__sdcc_init_data:\n");
1820
1821       // if the port can copy the XINIT segment to XISEG
1822       if (port->genXINIT) {
1823         port->genXINIT(asmFile);
1824       }
1825
1826     }
1827   copyFile (asmFile, statsg->oFile);
1828
1829   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1830     {
1831       /* This code is generated in the post-static area.
1832        * This area is guaranteed to follow the static area
1833        * by the ugly shucking and jiving about 20 lines ago.
1834        */
1835       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1836       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1837     }
1838
1839   fprintf (asmFile,
1840            "%s"
1841            "; Home\n"
1842            "%s", iComments2, iComments2);
1843   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1844   copyFile (asmFile, home->oFile);
1845
1846   /* copy over code */
1847   fprintf (asmFile, "%s", iComments2);
1848   fprintf (asmFile, "; code\n");
1849   fprintf (asmFile, "%s", iComments2);
1850   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1851   if (mainf && IFFUNC_HASBODY(mainf->type))
1852     {
1853
1854       /* entry point @ start of CSEG */
1855       fprintf (asmFile, "__sdcc_program_startup:\n");
1856
1857       /* put in the call to main */
1858       fprintf (asmFile, "\tlcall\t_main\n");
1859       if (options.mainreturn)
1860         {
1861
1862           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1863           fprintf (asmFile, "\tret\n");
1864
1865         }
1866       else
1867         {
1868
1869           fprintf (asmFile, ";\treturn from main will lock up\n");
1870           fprintf (asmFile, "\tsjmp .\n");
1871         }
1872     }
1873   copyFile (asmFile, code->oFile);
1874
1875   if (port->genAssemblerEnd) {
1876       port->genAssemblerEnd(asmFile);
1877   }
1878   fclose (asmFile);
1879
1880   rm_tmpfiles ();
1881 }
1882
1883
1884 /** Creates a temporary file with unoque file name
1885     Scans, in order:
1886     - TMP, TEMP, TMPDIR env. varibles
1887     - if Un*x system: /usr/tmp and /tmp
1888     - root directory using mkstemp() if avaliable
1889     - default location using tempnam()
1890 */
1891 static int
1892 tempfileandname(char *fname, size_t len)
1893 {
1894 #define TEMPLATE      "sdccXXXXXX"
1895 #define TEMPLATE_LEN  ((sizeof TEMPLATE) - 1)
1896
1897   const char *tmpdir = NULL;
1898   int fd;
1899
1900   if ((tmpdir = getenv ("TMP")) == NULL)
1901     if ((tmpdir = getenv ("TEMP")) == NULL)
1902       tmpdir = getenv ("TMPDIR");
1903
1904 #if defined(_WIN32)
1905   {
1906     static int warning_emitted;
1907
1908     if (tmpdir == NULL)
1909       {
1910         tmpdir = "c:\\";
1911         if (!warning_emitted)
1912           {
1913             fprintf (stderr, "TMP not defined in environment, using %s for temporary files\n.", tmpdir);
1914             warning_emitted = 1;
1915           }
1916       }
1917   }
1918 #else
1919   {
1920     /* try with /usr/tmp and /tmp on Un*x systems */
1921     struct stat statbuf;
1922
1923     if (tmpdir == NULL) {
1924       if (stat("/usr/tmp", &statbuf) != -1)
1925         tmpdir = "/usr/tmp";
1926       else if (stat("/tmp", &statbuf) != -1)
1927         tmpdir = "/tmp";
1928     }
1929   }
1930 #endif
1931
1932 #ifdef HAVE_MKSTEMP
1933   {
1934     char fnamebuf[PATH_MAX];
1935     size_t name_len;
1936
1937     if (fname == NULL || len == 0) {
1938       fname = fnamebuf;
1939       len = sizeof fnamebuf;
1940     }
1941
1942     if (tmpdir) {
1943       name_len = strlen(tmpdir) + 1 + TEMPLATE_LEN;
1944
1945       assert(name_len < len);
1946       if (!(name_len < len))  /* in NDEBUG is defined */
1947         return -1;            /* buffer too small, temporary file can not be created */
1948
1949       sprintf(fname, "%s" DIR_SEPARATOR_STRING TEMPLATE, tmpdir);
1950     }
1951     else {
1952       name_len = TEMPLATE_LEN;
1953
1954       assert(name_len < len);
1955       if (!(name_len < len))  /* in NDEBUG is defined */
1956         return -1;            /* buffer too small, temporary file can not be created */
1957
1958       strcpy(fname, TEMPLATE);
1959     }
1960
1961     fd = mkstemp(fname);
1962   }
1963 #else
1964   {
1965     char *name = tempnam(tmpdir, "sdcc");
1966
1967     if (name == NULL) {
1968       perror("Can't create temporary file name");
1969       exit(1);
1970     }
1971
1972     assert(strlen(name) < len);
1973     if (!(strlen(name) < len))  /* in NDEBUG is defined */
1974       return -1;                /* buffer too small, temporary file can not be created */
1975
1976     strcpy(fname, name);
1977 #ifdef _WIN32
1978     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IREAD | S_IWRITE);
1979 #else
1980     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IRUSR | S_IWUSR);
1981 #endif
1982   }
1983 #endif
1984
1985   if (fd == -1) {
1986     perror("Can't create temporary file");
1987     exit(1);
1988   }
1989
1990   return fd;
1991 }
1992
1993
1994 /** Create a temporary file name
1995 */
1996 char *
1997 tempfilename(void)
1998 {
1999   int fd;
2000   static char fnamebuf[PATH_MAX];
2001
2002   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
2003     fprintf(stderr, "Can't create temporary file name!");
2004     exit(1);
2005   }
2006
2007   fd = close(fd);
2008   assert(fd != -1);
2009
2010   return fnamebuf;
2011 }
2012
2013
2014 /** Create a temporary file and add it to tmpfileNameSet,
2015     so that it is removed explicitly by rm_tmpfiles()
2016     or implicitly at program extit.
2017 */
2018 FILE *
2019 tempfile(void)
2020 {
2021   int fd;
2022   char *tmp;
2023   FILE *fp;
2024   char fnamebuf[PATH_MAX];
2025
2026   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
2027     fprintf(stderr, "Can't create temporary file!");
2028     exit(1);
2029   }
2030
2031   tmp = Safe_strdup(fnamebuf);
2032   if (tmp)
2033     addSetHead(&tmpfileNameSet, tmp);
2034
2035   if ((fp = fdopen(fd, "w+b")) == NULL) {
2036       perror("Can't create temporary file!");
2037       exit(1);
2038   }
2039
2040   return fp;
2041 }