sdccopt works for the hc08 port now
[fw/sdcc] / src / SDCCglue.c
1 /*-------------------------------------------------------------------------
2
3   SDCCglue.c - glues everything we have done together into one file.
4                 Written By -  Sandeep Dutta . sandeep.dutta@usa.net (1998)
5
6    This program is free software; you can redistribute it and/or modify it
7    under the terms of the GNU General Public License as published by the
8    Free Software Foundation; either version 2, or (at your option) any
9    later version.
10
11    This program is distributed in the hope that it will be useful,
12    but WITHOUT ANY WARRANTY; without even the implied warranty of
13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14    GNU General Public License for more details.
15
16    You should have received a copy of the GNU General Public License
17    along with this program; if not, write to the Free Software
18    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
19
20    In other words, you are welcome to use, share and improve this program.
21    You are forbidden to forbid anyone else to use, share and improve
22    what you give them.   Help stamp out software-hoarding!
23 -------------------------------------------------------------------------*/
24
25 #include "common.h"
26 #include "asm.h"
27 #include <time.h>
28 #include "newalloc.h"
29 #include <fcntl.h>
30 #include <sys/stat.h>
31
32 #ifdef _WIN32
33 #include <io.h>
34 #else
35 #include <unistd.h>
36 #endif
37
38 symbol *interrupts[INTNO_MAX+1];
39
40 void printIval (symbol *, sym_link *, initList *, FILE *);
41 set *publics = NULL;            /* public variables */
42 set *externs = NULL;            /* Varibles that are declared as extern */
43
44 /* TODO: this should be configurable (DS803C90 uses more than 6) */
45 unsigned maxInterrupts = 6;
46 int allocInfo = 1;
47 symbol *mainf;
48 set *pipeSet = NULL;            /* set of pipes */
49 set *tmpfileSet = NULL;         /* set of tmp file created by the compiler */
50 set *tmpfileNameSet = NULL;     /* All are unlinked at close. */
51
52 /*-----------------------------------------------------------------*/
53 /* closePipes - closes all pipes created by the compiler           */
54 /*-----------------------------------------------------------------*/
55 DEFSETFUNC (closePipes)
56 {
57   FILE *pfile = item;
58   int ret;
59
60   if (pfile) {
61     ret = pclose (pfile);
62     assert(ret != -1);
63   }
64
65   return 0;
66 }
67
68 /*-----------------------------------------------------------------*/
69 /* closeTmpFiles - closes all tmp files created by the compiler    */
70 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
71 /*-----------------------------------------------------------------*/
72 DEFSETFUNC (closeTmpFiles)
73 {
74   FILE *tfile = item;
75   int ret;
76
77   if (tfile) {
78     ret = fclose (tfile);
79     assert(ret == 0);
80   }
81
82   return 0;
83 }
84
85 /*-----------------------------------------------------------------*/
86 /* rmTmpFiles - unlinks all tmp files created by the compiler      */
87 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
88 /*-----------------------------------------------------------------*/
89 DEFSETFUNC (rmTmpFiles)
90 {
91   char *name = item;
92   int ret;
93
94   if (name) {
95       ret = unlink (name);
96       assert(ret == 0);
97       Safe_free (name);
98   }
99
100   return 0;
101 }
102
103 /*-----------------------------------------------------------------*/
104 /* rm_tmpfiles - close and remove temporary files and delete sets  */
105 /*-----------------------------------------------------------------*/
106 void
107 rm_tmpfiles (void)
108 {
109   /* close temporary files */
110   applyToSet (pipeSet, closePipes);
111   /* close temporary files */
112   deleteSet (&pipeSet);
113
114   applyToSet (tmpfileSet, closeTmpFiles);
115   /* remove temporary files */
116   applyToSet (tmpfileNameSet, rmTmpFiles);
117   /* delete temorary file sets */
118   deleteSet (&tmpfileSet);
119   deleteSet (&tmpfileNameSet);
120 }
121
122 /*-----------------------------------------------------------------*/
123 /* copyFile - copies source file to destination file               */
124 /*-----------------------------------------------------------------*/
125 void 
126 copyFile (FILE * dest, FILE * src)
127 {
128   int ch;
129
130   rewind (src);
131   while (!feof (src))
132     if ((ch = fgetc (src)) != EOF)
133       fputc (ch, dest);
134 }
135
136 char *
137 aopLiteralLong (value * val, int offset, int size)
138 {
139         union {
140                 float f;
141                 unsigned char c[4];
142         }
143         fl;
144
145         if (!val) {
146           // assuming we have been warned before
147           val=constVal("0");
148         }
149
150         /* if it is a float then it gets tricky */
151         /* otherwise it is fairly simple */
152         if (!IS_FLOAT (val->type)) {
153                 unsigned long v = (unsigned long) floatFromVal (val);
154
155                 v >>= (offset * 8);
156                 switch (size) {
157                 case 1:
158                         tsprintf (buffer, sizeof(buffer), 
159                                   "!immedbyte", (unsigned int) v & 0xff);
160                         break;
161                 case 2:
162                         tsprintf (buffer, sizeof(buffer), 
163                                   "!immedword", (unsigned int) v & 0xffff);
164                         break;
165                 default:
166                         /* Hmm.  Too big for now. */
167                         assert (0);
168                 }
169                 return Safe_strdup (buffer);
170         }
171
172         /* PENDING: For now size must be 1 */
173         assert (size == 1);
174
175         /* it is type float */
176         fl.f = (float) floatFromVal (val);
177 #ifdef WORDS_BIGENDIAN
178         tsprintf (buffer, sizeof(buffer), 
179                   "!immedbyte", fl.c[3 - offset]);
180 #else
181         tsprintf (buffer, sizeof(buffer), 
182                   "!immedbyte", fl.c[offset]);
183 #endif
184         return Safe_strdup (buffer);
185 }
186
187 /*-----------------------------------------------------------------*/
188 /* aopLiteral - string from a literal value                        */
189 /*-----------------------------------------------------------------*/
190 char *
191 aopLiteral (value * val, int offset)
192 {
193         return aopLiteralLong (val, offset, 1);
194 }
195
196 /*-----------------------------------------------------------------*/
197 /* emitRegularMap - emit code for maps with no special cases       */
198 /*-----------------------------------------------------------------*/
199 static void 
200 emitRegularMap (memmap * map, bool addPublics, bool arFlag)
201 {
202   symbol *sym;
203   ast *ival = NULL;
204
205   if (!map)
206     return;
207
208   if (addPublics)
209     {
210       /* PENDING: special case here - should remove */
211       if (!strcmp (map->sname, CODE_NAME))
212         tfprintf (map->oFile, "\t!areacode\n", map->sname);
213       else if (!strcmp (map->sname, DATA_NAME))
214         tfprintf (map->oFile, "\t!areadata\n", map->sname);
215       else if (!strcmp (map->sname, HOME_NAME))
216         tfprintf (map->oFile, "\t!areahome\n", map->sname);
217       else
218         tfprintf (map->oFile, "\t!area\n", map->sname);
219     }
220  
221   for (sym = setFirstItem (map->syms); sym;
222        sym = setNextItem (map->syms))
223     {
224       symbol *newSym=NULL;
225
226       /* if extern then add it into the extern list */
227       if (IS_EXTERN (sym->etype))
228         {
229           addSetHead (&externs, sym);
230           continue;
231         }
232
233       /* if allocation required check is needed
234          then check if the symbol really requires
235          allocation only for local variables */
236
237       if (arFlag && !IS_AGGREGATE (sym->type) &&
238           !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
239           !sym->allocreq && sym->level)
240         continue;
241
242       /* for bitvar locals and parameters */
243       if (!arFlag && !sym->allocreq && sym->level 
244           && !SPEC_ABSA (sym->etype)) {
245         continue;
246       }
247
248       /* if global variable & not static or extern
249          and addPublics allowed then add it to the public set */
250       if ((sym->level == 0 ||
251            (sym->_isparm && !IS_REGPARM (sym->etype))) &&
252           addPublics &&
253           !IS_STATIC (sym->etype) &&
254           (IS_FUNC(sym->type) ? (sym->used || IFFUNC_HASBODY(sym->type)) : 1))
255         {
256           addSetHead (&publics, sym);
257         }
258
259       /* if extern then do nothing or is a function
260          then do nothing */
261       if (IS_FUNC (sym->type) && !(sym->isitmp))
262         continue;
263
264       /* print extra debug info if required */
265       if (options.debug)
266         {
267           if (!sym->level) /* global */
268             {
269               if (IS_STATIC (sym->etype))
270                 fprintf (map->oFile, "F%s$", moduleName); /* scope is file */
271               else
272                 fprintf (map->oFile, "G$");     /* scope is global */
273             }
274           else
275             {
276               /* symbol is local */
277               fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-"));
278             }
279           fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block);
280         }
281       
282       /* if it has an initial value then do it only if
283          it is a global variable */
284       if (sym->ival && sym->level == 0) {
285         if (SPEC_OCLS(sym->etype)==xidata) {
286           /* create a new "XINIT (CODE)" symbol, that will be emitted later
287              in the static seg */
288           newSym=copySymbol (sym);
289           SPEC_OCLS(newSym->etype)=xinit;
290           SNPRINTF (newSym->name, sizeof(newSym->name), "__xinit_%s", sym->name);
291           SNPRINTF (newSym->rname, sizeof(newSym->rname), "__xinit_%s", sym->rname);
292           if (IS_SPEC (newSym->type))
293             SPEC_CONST (newSym->type) = 1;
294           else
295             DCL_PTR_CONST (newSym->type) = 1;
296           SPEC_STAT(newSym->etype)=1;
297           resolveIvalSym(newSym->ival, newSym->type);
298
299           // add it to the "XINIT (CODE)" segment
300           addSet(&xinit->syms, newSym);
301           sym->ival=NULL;
302         } else {
303           if (IS_AGGREGATE (sym->type)) {
304             ival = initAggregates (sym, sym->ival, NULL);
305           } else {
306             if (getNelements(sym->type, sym->ival)>1) {
307               werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "scalar", 
308                       sym->name);
309             }
310             ival = newNode ('=', newAst_VALUE (symbolVal (sym)),
311                             decorateType (resolveSymbols (list2expr (sym->ival)), RESULT_CHECK));
312           }
313           codeOutFile = statsg->oFile;
314
315           if (ival) {
316             // set ival's lineno to where the symbol was defined
317             setAstLineno (ival, lineno=sym->lineDef);
318             // check if this is not a constant expression
319             if (!constExprTree(ival)) {
320               werror (E_CONST_EXPECTED, "found expression");
321               // but try to do it anyway
322             }
323             allocInfo = 0;
324             if (!astErrors(ival))
325               eBBlockFromiCode (iCodeFromAst (ival));
326             allocInfo = 1;
327           }
328         }         
329         sym->ival = NULL;
330       }
331
332       /* if is has an absolute address then generate
333          an equate for this no need to allocate space */
334       if (SPEC_ABSA (sym->etype))
335         {
336           char *equ="=";
337           if (options.debug) {
338             fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
339           }
340           if (TARGET_IS_XA51) {
341             if (map==sfr) {
342               equ="sfr";
343             } else if (map==bit || map==sfrbit) {
344               equ="bit";
345             }
346           }
347           fprintf (map->oFile, "%s\t%s\t0x%04x\n",
348                    sym->rname, equ,
349                    SPEC_ADDR (sym->etype));
350         }
351       else {
352         int size = getSize (sym->type);
353         if (size==0) {
354           werrorfl (sym->fileDef, 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 (sym->fileDef, 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 (sym->fileDef, 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 (ilist->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 (ilist->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 (sym->fileDef, 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 (ilist->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 (sym->fileDef, 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 (sym->fileDef, 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 (ilist->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           fprintf (oFile, "; generic printIvalPtr\n");
1080           if (port->little_endian)
1081             {
1082               fprintf (oFile, "\t.byte %s,%s",
1083                        aopLiteral (val, 0), aopLiteral (val, 1));
1084             }
1085           else
1086             {
1087               fprintf (oFile, "\t.byte %s,%s",
1088                        aopLiteral (val, 1), aopLiteral (val, 0));
1089             }
1090           if (IS_GENPTR (val->type))
1091             fprintf (oFile, ",%s\n", aopLiteral (val, 2));
1092           else if (IS_PTR (val->type))
1093             fprintf (oFile, ",#%x\n", pointerTypeToGPByte (DCL_TYPE (val->type), NULL, NULL));
1094           else
1095             fprintf (oFile, ",%s\n", aopLiteral (val, 2));
1096         }
1097       return;
1098     }
1099
1100
1101   size = getSize (type);
1102
1103   if (size == 1)                /* Z80 specific?? */
1104     {
1105       tfprintf (oFile, "\t!dbs\n", val->name);
1106     }
1107   else if (size == FPTRSIZE)
1108     {
1109       if (port->use_dw_for_init) {
1110         tfprintf (oFile, "\t!dws\n", val->name);
1111       } else {
1112         printPointerType (oFile, val->name);
1113       }
1114     }
1115   else if (size == GPTRSIZE)
1116     {
1117       printGPointerType (oFile, val->name, sym->name,
1118                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1119                           PTR_TYPE (SPEC_OCLS (val->etype))));
1120     }
1121   return;
1122 }
1123
1124 /*-----------------------------------------------------------------*/
1125 /* printIval - generates code for initial value                    */
1126 /*-----------------------------------------------------------------*/
1127 void 
1128 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1129 {
1130   sym_link *itype;
1131   
1132   if (!ilist)
1133     return;
1134
1135   /* if structure then    */
1136   if (IS_STRUCT (type))
1137     {
1138       printIvalStruct (sym, type, ilist, oFile);
1139       return;
1140     }
1141
1142   /* if this is an array   */
1143   if (IS_ARRAY (type))
1144     {
1145       printIvalArray (sym, type, ilist, oFile);
1146       return;
1147     }
1148
1149   // not an aggregate, ilist must be a node
1150   if (ilist->type!=INIT_NODE) {
1151       // or a 1-element list
1152     if (ilist->init.deep->next) {
1153       werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "scalar", 
1154               sym->name);
1155     } else {
1156       ilist=ilist->init.deep;
1157     }
1158   }
1159
1160   // and the type must match
1161   itype=ilist->init.node->ftype;
1162
1163   if (compareType(type, itype)==0) {
1164     // special case for literal strings
1165     if (IS_ARRAY (itype) && IS_CHAR (getSpec(itype)) &&
1166         // which are really code pointers
1167         IS_PTR(type) && DCL_TYPE(type)==CPOINTER) {
1168       // no sweat
1169     } else {
1170       werrorfl (ilist->filename, ilist->lineno, E_TYPE_MISMATCH, "assignment", " ");
1171       printFromToType(itype, type);
1172     }
1173   }
1174
1175   /* if this is a pointer */
1176   if (IS_PTR (type))
1177     {
1178       printIvalPtr (sym, type, ilist, oFile);
1179       return;
1180     }
1181
1182   /* if type is SPECIFIER */
1183   if (IS_SPEC (type))
1184     {
1185       printIvalType (sym, type, ilist, oFile);
1186       return;
1187     }
1188 }
1189
1190 /*-----------------------------------------------------------------*/
1191 /* emitStaticSeg - emitcode for the static segment                 */
1192 /*-----------------------------------------------------------------*/
1193 void 
1194 emitStaticSeg (memmap * map, FILE * out)
1195 {
1196   symbol *sym;
1197
1198   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1199
1200   /* for all variables in this segment do */
1201   for (sym = setFirstItem (map->syms); sym;
1202        sym = setNextItem (map->syms))
1203     {
1204
1205       /* if it is "extern" then do nothing */
1206       if (IS_EXTERN (sym->etype))
1207         continue;
1208
1209       /* if it is not static add it to the public
1210          table */
1211       if (!IS_STATIC (sym->etype))
1212         {
1213           addSetHead (&publics, sym);
1214         }
1215
1216       /* print extra debug info if required */
1217       if (options.debug) {
1218
1219         if (!sym->level)
1220           {                     /* global */
1221             if (IS_STATIC (sym->etype))
1222               fprintf (out, "F%s$", moduleName);        /* scope is file */
1223             else
1224               fprintf (out, "G$");      /* scope is global */
1225           }
1226         else
1227           /* symbol is local */
1228           fprintf (out, "L%s$",
1229                    (sym->localof ? sym->localof->name : "-null-"));
1230         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1231       }
1232       
1233       /* if it has an absolute address */
1234       if (SPEC_ABSA (sym->etype))
1235         {
1236           if (options.debug)
1237             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1238           
1239           fprintf (out, "%s\t=\t0x%04x\n",
1240                    sym->rname,
1241                    SPEC_ADDR (sym->etype));
1242         }
1243       else
1244         {
1245           if (options.debug)
1246             fprintf (out, " == .\n");
1247           
1248           /* if it has an initial value */
1249           if (sym->ival)
1250             {
1251               fprintf (out, "%s:\n", sym->rname);
1252               noAlloc++;
1253               resolveIvalSym (sym->ival, sym->type);
1254               printIval (sym, sym->type, sym->ival, out);
1255               noAlloc--;
1256               /* if sym is a simple string and sym->ival is a string, 
1257                  WE don't need it anymore */
1258               if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) &&
1259                   IS_AST_SYM_VALUE(list2expr(sym->ival)) &&
1260                   list2val(sym->ival)->sym->isstrlit) {
1261                 freeStringSymbol(list2val(sym->ival)->sym);
1262               }
1263             }
1264           else {
1265               /* allocate space */
1266               int size = getSize (sym->type);
1267               
1268               if (size==0) {
1269                   werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE,sym->name);
1270               }
1271               fprintf (out, "%s:\n", sym->rname);
1272               /* special case for character strings */
1273               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1274                   SPEC_CVAL (sym->etype).v_char)
1275                   printChar (out,
1276                              SPEC_CVAL (sym->etype).v_char,
1277                              size);
1278               else
1279                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1280             }
1281         }
1282     }
1283 }
1284
1285 /*-----------------------------------------------------------------*/
1286 /* emitMaps - emits the code for the data portion the code         */
1287 /*-----------------------------------------------------------------*/
1288 void 
1289 emitMaps (void)
1290 {
1291   int publicsfr = TARGET_IS_MCS51; /* Ideally, this should be true for all  */
1292                                    /* ports but let's be conservative - EEP */
1293   
1294   inInitMode++;
1295   /* no special considerations for the following
1296      data, idata & bit & xdata */
1297   emitRegularMap (data, TRUE, TRUE);
1298   emitRegularMap (idata, TRUE, TRUE);
1299   emitRegularMap (bit, TRUE, FALSE);
1300   emitRegularMap (xdata, TRUE, TRUE);
1301   if (port->genXINIT) {
1302     emitRegularMap (xidata, TRUE, TRUE);
1303   }
1304   emitRegularMap (sfr, publicsfr, FALSE);
1305   emitRegularMap (sfrbit, publicsfr, FALSE);
1306   emitRegularMap (home, TRUE, FALSE);
1307   emitRegularMap (code, TRUE, FALSE);
1308
1309   emitStaticSeg (statsg, code->oFile);
1310   if (port->genXINIT) {
1311     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1312     emitStaticSeg (xinit, code->oFile);
1313   }
1314   inInitMode--;
1315 }
1316
1317 /*-----------------------------------------------------------------*/
1318 /* flushStatics - flush all currently defined statics out to file  */
1319 /*  and delete.  Temporary function                                */
1320 /*-----------------------------------------------------------------*/
1321 void 
1322 flushStatics (void)
1323 {
1324   emitStaticSeg (statsg, codeOutFile);
1325   statsg->syms = NULL;
1326 }
1327
1328 /*-----------------------------------------------------------------*/
1329 /* createInterruptVect - creates the interrupt vector              */
1330 /*-----------------------------------------------------------------*/
1331 void 
1332 createInterruptVect (FILE * vFile)
1333 {
1334   unsigned i = 0;
1335   mainf = newSymbol ("main", 0);
1336   mainf->block = 0;
1337
1338   /* only if the main function exists */
1339   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1340     {
1341       if (!options.cc_only && !noAssemble && !options.c1mode)
1342         werror (E_NO_MAIN);
1343       return;
1344     }
1345
1346   /* if the main is only a prototype ie. no body then do nothing */
1347   if (!IFFUNC_HASBODY(mainf->type))
1348     {
1349       /* if ! compile only then main function should be present */
1350       if (!options.cc_only && !noAssemble)
1351         werror (E_NO_MAIN);
1352       return;
1353     }
1354
1355   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1356   fprintf (vFile, "__interrupt_vect:\n");
1357
1358
1359   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1360     {
1361       /* "generic" interrupt table header (if port doesn't specify one).
1362        * Look suspiciously like 8051 code to me...
1363        */
1364
1365       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1366
1367       /* now for the other interrupts */
1368       for (; i < maxInterrupts; i++)
1369         {
1370           if (interrupts[i])
1371             {
1372               fprintf (vFile, "\tljmp\t%s\n", interrupts[i]->rname);
1373               if ( i != maxInterrupts - 1 )
1374                 fprintf (vFile, "\t.ds\t5\n");
1375             }
1376           else
1377             {
1378               fprintf (vFile, "\treti\n");
1379               if ( i != maxInterrupts - 1 )
1380                 fprintf (vFile, "\t.ds\t7\n");
1381             }
1382         }
1383     }
1384 }
1385
1386 char *iComments1 =
1387 {
1388   ";--------------------------------------------------------\n"
1389   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1390
1391 char *iComments2 =
1392 {
1393   ";--------------------------------------------------------\n"};
1394
1395
1396 /*-----------------------------------------------------------------*/
1397 /* initialComments - puts in some initial comments                 */
1398 /*-----------------------------------------------------------------*/
1399 void 
1400 initialComments (FILE * afile)
1401 {
1402   time_t t;
1403   time (&t);
1404   fprintf (afile, "%s", iComments1);
1405   fprintf (afile, "; Version " SDCC_VERSION_STR " (%s)\n", __DATE__);
1406   fprintf (afile, "; This file generated %s", asctime (localtime (&t)));
1407   fprintf (afile, "%s", iComments2);
1408 }
1409
1410 /*-----------------------------------------------------------------*/
1411 /* printPublics - generates .global for publics                    */
1412 /*-----------------------------------------------------------------*/
1413 void 
1414 printPublics (FILE * afile)
1415 {
1416   symbol *sym;
1417
1418   fprintf (afile, "%s", iComments2);
1419   fprintf (afile, "; Public variables in this module\n");
1420   fprintf (afile, "%s", iComments2);
1421
1422   for (sym = setFirstItem (publics); sym;
1423        sym = setNextItem (publics))
1424     tfprintf (afile, "\t!global\n", sym->rname);
1425 }
1426
1427 /*-----------------------------------------------------------------*/
1428 /* printExterns - generates .global for externs                    */
1429 /*-----------------------------------------------------------------*/
1430 void 
1431 printExterns (FILE * afile)
1432 {
1433   symbol *sym;
1434
1435   fprintf (afile, "%s", iComments2);
1436   fprintf (afile, "; Externals used\n");
1437   fprintf (afile, "%s", iComments2);
1438
1439   for (sym = setFirstItem (externs); sym;
1440        sym = setNextItem (externs))
1441     tfprintf (afile, "\t!extern\n", sym->rname);
1442 }
1443
1444 /*-----------------------------------------------------------------*/
1445 /* emitOverlay - will emit code for the overlay stuff              */
1446 /*-----------------------------------------------------------------*/
1447 static void 
1448 emitOverlay (FILE * afile)
1449 {
1450   set *ovrset;
1451
1452   if (!elementsInSet (ovrSetSets))
1453     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1454
1455   /* for each of the sets in the overlay segment do */
1456   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1457        ovrset = setNextItem (ovrSetSets))
1458     {
1459
1460       symbol *sym;
1461
1462       if (elementsInSet (ovrset))
1463         {
1464           /* output the area informtion */
1465           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1466         }
1467
1468       for (sym = setFirstItem (ovrset); sym;
1469            sym = setNextItem (ovrset))
1470         {
1471           /* if extern then it is in the publics table: do nothing */
1472           if (IS_EXTERN (sym->etype))
1473             continue;
1474
1475           /* if allocation required check is needed
1476              then check if the symbol really requires
1477              allocation only for local variables */
1478           if (!IS_AGGREGATE (sym->type) &&
1479               !(sym->_isparm && !IS_REGPARM (sym->etype))
1480               && !sym->allocreq && sym->level)
1481             continue;
1482
1483           /* if global variable & not static or extern
1484              and addPublics allowed then add it to the public set */
1485           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1486               && !IS_STATIC (sym->etype))
1487             {
1488               addSetHead (&publics, sym);
1489             }
1490
1491           /* if extern then do nothing or is a function
1492              then do nothing */
1493           if (IS_FUNC (sym->type))
1494             continue;
1495
1496           /* print extra debug info if required */
1497           if (options.debug)
1498             {
1499               if (!sym->level)
1500                 {               /* global */
1501                   if (IS_STATIC (sym->etype))
1502                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1503                   else
1504                     fprintf (afile, "G$");      /* scope is global */
1505                 }
1506               else
1507                 /* symbol is local */
1508                 fprintf (afile, "L%s$",
1509                          (sym->localof ? sym->localof->name : "-null-"));
1510               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1511             }
1512
1513           /* if is has an absolute address then generate
1514              an equate for this no need to allocate space */
1515           if (SPEC_ABSA (sym->etype))
1516             {
1517
1518               if (options.debug)
1519                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1520
1521               fprintf (afile, "%s\t=\t0x%04x\n",
1522                        sym->rname,
1523                        SPEC_ADDR (sym->etype));
1524             }
1525           else {
1526               int size = getSize(sym->type);
1527
1528               if (size==0) {
1529                   werrorfl (sym->fileDef, sym->lineDef, E_UNKNOWN_SIZE);
1530               }       
1531               if (options.debug)
1532                   fprintf (afile, "==.\n");
1533               
1534               /* allocate space */
1535               tfprintf (afile, "!labeldef\n", sym->rname);
1536               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1537           }
1538           
1539         }
1540     }
1541 }
1542
1543
1544 /*-----------------------------------------------------------------*/
1545 /* spacesToUnderscores - replace spaces with underscores        */
1546 /*-----------------------------------------------------------------*/
1547 static char *
1548 spacesToUnderscores (char *dest, const char *src, size_t len)
1549 {
1550   int i;
1551   char *p;
1552
1553   assert(dest != NULL);
1554   assert(src != NULL);
1555   assert(len > 0);
1556
1557   --len;
1558   for (p = dest, i = 0; *src != '\0' && i < len; ++src, ++i) {
1559     *p++ = isspace(*src) ? '_' : *src;
1560   }
1561   *p = '\0';
1562
1563   return dest;
1564 }
1565
1566
1567 /*-----------------------------------------------------------------*/
1568 /* glue - the final glue that hold the whole thing together        */
1569 /*-----------------------------------------------------------------*/
1570 void 
1571 glue (void)
1572 {
1573   FILE *vFile;
1574   FILE *asmFile;
1575   FILE *ovrFile = tempfile ();
1576   char moduleBuf[PATH_MAX];
1577   int mcs51_like;
1578
1579   if(port->general.glue_up_main &&
1580     (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51 || TARGET_IS_DS400))
1581   {
1582       mcs51_like=1; /*So it has bits, sfr, sbits, data, idata, etc...*/
1583   }
1584   else
1585   {
1586       mcs51_like=0;
1587   }
1588
1589   addSetHead (&tmpfileSet, ovrFile);
1590   /* print the global struct definitions */
1591   if (options.debug)
1592     cdbStructBlock (0);
1593
1594   vFile = tempfile ();
1595   /* PENDING: this isnt the best place but it will do */
1596   if (port->general.glue_up_main)
1597     {
1598       /* create the interrupt vector table */
1599       createInterruptVect (vFile);
1600     }
1601
1602   addSetHead (&tmpfileSet, vFile);
1603
1604   /* emit code for the all the variables declared */
1605   emitMaps ();
1606   /* do the overlay segments */
1607   emitOverlay (ovrFile);
1608
1609   outputDebugSymbols();
1610
1611   /* now put it all together into the assembler file */
1612   /* create the assembler file name */
1613
1614   /* -o option overrides default name? */
1615   if ((noAssemble || options.c1mode) && fullDstFileName)
1616     {
1617       strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1618     }
1619   else
1620     {
1621       strncpyz (scratchFileName, dstFileName, PATH_MAX);
1622       strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1623     }
1624
1625   if (!(asmFile = fopen (scratchFileName, "w")))
1626     {
1627       werror (E_FILE_OPEN_ERR, scratchFileName);
1628       exit (1);
1629     }
1630
1631   /* initial comments */
1632   initialComments (asmFile);
1633
1634   /* print module name */
1635   tfprintf (asmFile, "\t!module\n",
1636     spacesToUnderscores (moduleBuf, moduleName, sizeof moduleBuf));
1637   if(mcs51_like)
1638   {
1639     fprintf (asmFile, "\t.optsdcc -m%s", port->target);
1640
1641     switch(options.model)
1642     {
1643         case MODEL_SMALL:   fprintf (asmFile, " --model-small");   break;
1644         case MODEL_COMPACT: fprintf (asmFile, " --model-compact"); break;
1645         case MODEL_MEDIUM:  fprintf (asmFile, " --model-medium");  break;
1646         case MODEL_LARGE:   fprintf (asmFile, " --model-large");   break;
1647         case MODEL_FLAT24:  fprintf (asmFile, " --model-flat24");  break;
1648         case MODEL_PAGE0:   fprintf (asmFile, " --model-page0");   break;
1649         default: break;
1650     }
1651     /*if(options.stackAuto)      fprintf (asmFile, " --stack-auto");*/
1652     if(options.useXstack)      fprintf (asmFile, " --xstack");
1653     /*if(options.intlong_rent)   fprintf (asmFile, " --int-long-rent");*/
1654     /*if(options.float_rent)     fprintf (asmFile, " --float-rent");*/
1655     if(options.noRegParams)    fprintf (asmFile, " --no-reg-params");
1656     if(options.parms_in_bank1) fprintf (asmFile, " --parms-in-bank1");
1657     fprintf (asmFile, "\n");
1658   }
1659   else if(TARGET_IS_Z80 || TARGET_IS_GBZ80 || TARGET_IS_HC08)
1660   {
1661     fprintf (asmFile, "\t.optsdcc -m%s\n", port->target);
1662   }
1663
1664   tfprintf (asmFile, "\t!fileprelude\n");
1665
1666   /* Let the port generate any global directives, etc. */
1667   if (port->genAssemblerPreamble)
1668     {
1669       port->genAssemblerPreamble (asmFile);
1670     }
1671
1672   /* print the global variables in this module */
1673   printPublics (asmFile);
1674   if (port->assembler.externGlobal)
1675     printExterns (asmFile);
1676
1677   if(( mcs51_like )
1678    ||( TARGET_IS_Z80 )) /*.p.t.20030924 need to output SFR table for Z80 as well */
1679   {
1680       /* copy the sfr segment */
1681       fprintf (asmFile, "%s", iComments2);
1682       fprintf (asmFile, "; special function registers\n");
1683       fprintf (asmFile, "%s", iComments2);
1684       copyFile (asmFile, sfr->oFile);
1685   }
1686   
1687   if(mcs51_like)
1688   {
1689       /* copy the sbit segment */
1690       fprintf (asmFile, "%s", iComments2);
1691       fprintf (asmFile, "; special function bits \n");
1692       fprintf (asmFile, "%s", iComments2);
1693       copyFile (asmFile, sfrbit->oFile);
1694   
1695       /*JCF: Create the areas for the register banks*/
1696           if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1697           {
1698                  fprintf (asmFile, "%s", iComments2);
1699                  fprintf (asmFile, "; overlayable register banks \n");
1700                  fprintf (asmFile, "%s", iComments2);
1701                  if(RegBankUsed[0])
1702                         fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1703                  if(RegBankUsed[1]||options.parms_in_bank1)
1704                         fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1705                  if(RegBankUsed[2])
1706                         fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1707                  if(RegBankUsed[3])
1708                         fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1709           }
1710   }
1711
1712   /* copy the data segment */
1713   fprintf (asmFile, "%s", iComments2);
1714   fprintf (asmFile, "; %s ram data\n", mcs51_like?"internal":"");
1715   fprintf (asmFile, "%s", iComments2);
1716   copyFile (asmFile, data->oFile);
1717
1718
1719   /* create the overlay segments */
1720   if (overlay) {
1721     fprintf (asmFile, "%s", iComments2);
1722     fprintf (asmFile, "; overlayable items in %s ram \n", mcs51_like?"internal":"");
1723     fprintf (asmFile, "%s", iComments2);
1724     copyFile (asmFile, ovrFile);
1725   }
1726
1727   /* create the stack segment MOF */
1728   if (mainf && IFFUNC_HASBODY(mainf->type))
1729     {
1730       fprintf (asmFile, "%s", iComments2);
1731       fprintf (asmFile, "; Stack segment in internal ram \n");
1732       fprintf (asmFile, "%s", iComments2);
1733       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1734                "__start__stack:\n\t.ds\t1\n\n");
1735     }
1736
1737   /* create the idata segment */
1738   if ( (idata) && (mcs51_like) ) {
1739     fprintf (asmFile, "%s", iComments2);
1740     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1741     fprintf (asmFile, "%s", iComments2);
1742     copyFile (asmFile, idata->oFile);
1743   }
1744
1745   /* copy the bit segment */
1746   if (mcs51_like) {
1747     fprintf (asmFile, "%s", iComments2);
1748     fprintf (asmFile, "; bit data\n");
1749     fprintf (asmFile, "%s", iComments2);
1750     copyFile (asmFile, bit->oFile);
1751   }
1752
1753   /* if external stack then reserve space of it */
1754   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1755     {
1756       fprintf (asmFile, "%s", iComments2);
1757       fprintf (asmFile, "; external stack \n");
1758       fprintf (asmFile, "%s", iComments2);
1759       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1760       fprintf (asmFile, "\t.ds 256\n");
1761     }
1762
1763
1764   /* copy xtern ram data */
1765   if (mcs51_like) {
1766     fprintf (asmFile, "%s", iComments2);
1767     fprintf (asmFile, "; external ram data\n");
1768     fprintf (asmFile, "%s", iComments2);
1769     copyFile (asmFile, xdata->oFile);
1770   }
1771
1772   /* copy xternal initialized ram data */
1773   fprintf (asmFile, "%s", iComments2);
1774   fprintf (asmFile, "; external initialized ram data\n");
1775   fprintf (asmFile, "%s", iComments2);
1776   copyFile (asmFile, xidata->oFile);
1777
1778   /* If the port wants to generate any extra areas, let it do so. */
1779   if (port->extraAreas.genExtraAreaDeclaration)
1780   {
1781       port->extraAreas.genExtraAreaDeclaration(asmFile, 
1782                                                mainf && IFFUNC_HASBODY(mainf->type));
1783   }
1784     
1785   /* copy the interrupt vector table */
1786   if (mainf && IFFUNC_HASBODY(mainf->type))
1787     {
1788       fprintf (asmFile, "%s", iComments2);
1789       fprintf (asmFile, "; interrupt vector \n");
1790       fprintf (asmFile, "%s", iComments2);
1791       copyFile (asmFile, vFile);
1792     }
1793
1794   /* copy global & static initialisations */
1795   fprintf (asmFile, "%s", iComments2);
1796   fprintf (asmFile, "; global & static initialisations\n");
1797   fprintf (asmFile, "%s", iComments2);
1798
1799   /* Everywhere we generate a reference to the static_name area,
1800    * (which is currently only here), we immediately follow it with a
1801    * definition of the post_static_name area. This guarantees that
1802    * the post_static_name area will immediately follow the static_name
1803    * area.
1804    */
1805   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1806   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1807   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1808
1809   if (mainf && IFFUNC_HASBODY(mainf->type))
1810     {
1811       if (port->genInitStartup)
1812         {
1813            port->genInitStartup(asmFile);
1814         }
1815       else
1816         {
1817           fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1818           /* if external stack is specified then the
1819              higher order byte of the xdatalocation is
1820              going into P2 and the lower order going into
1821              spx */
1822           if (options.useXstack)
1823             {
1824               fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1825                        (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1826               fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1827                        (unsigned int) options.xdata_loc & 0xff);
1828             }
1829
1830           // This should probably be a port option, but I'm being lazy.
1831           // on the 400, the firmware boot loader gives us a valid stack
1832           // (see '400 data sheet pg. 85 (TINI400 ROM Initialization code)
1833           if (!TARGET_IS_DS400)
1834             {
1835               /* initialise the stack pointer.  JCF: aslink takes care of the location */
1836               fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");     /* MOF */
1837             }
1838
1839           fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1840           fprintf (asmFile, "\tmov\ta,dpl\n");
1841           fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1842           fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1843           fprintf (asmFile, "__sdcc_init_data:\n");
1844
1845           // if the port can copy the XINIT segment to XISEG
1846           if (port->genXINIT)
1847             {
1848               port->genXINIT(asmFile);
1849             }
1850         }
1851
1852     }
1853   copyFile (asmFile, statsg->oFile);
1854
1855   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1856     {
1857       /* This code is generated in the post-static area.
1858        * This area is guaranteed to follow the static area
1859        * by the ugly shucking and jiving about 20 lines ago.
1860        */
1861       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1862       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1863     }
1864
1865   fprintf (asmFile,
1866            "%s"
1867            "; Home\n"
1868            "%s", iComments2, iComments2);
1869   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1870   copyFile (asmFile, home->oFile);
1871
1872   /* copy over code */
1873   fprintf (asmFile, "%s", iComments2);
1874   fprintf (asmFile, "; code\n");
1875   fprintf (asmFile, "%s", iComments2);
1876   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1877   if (mainf && IFFUNC_HASBODY(mainf->type))
1878     {
1879
1880       /* entry point @ start of CSEG */
1881       fprintf (asmFile, "__sdcc_program_startup:\n");
1882
1883       /* put in the call to main */
1884       fprintf (asmFile, "\tlcall\t_main\n");
1885       if (options.mainreturn)
1886         {
1887
1888           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1889           fprintf (asmFile, "\tret\n");
1890
1891         }
1892       else
1893         {
1894
1895           fprintf (asmFile, ";\treturn from main will lock up\n");
1896           fprintf (asmFile, "\tsjmp .\n");
1897         }
1898     }
1899   copyFile (asmFile, code->oFile);
1900
1901   if (port->genAssemblerEnd) {
1902       port->genAssemblerEnd(asmFile);
1903   }
1904   fclose (asmFile);
1905
1906   rm_tmpfiles ();
1907 }
1908
1909
1910 /** Creates a temporary file with unoque file name
1911     Scans, in order:
1912     - TMP, TEMP, TMPDIR env. varibles
1913     - if Un*x system: /usr/tmp and /tmp
1914     - root directory using mkstemp() if avaliable
1915     - default location using tempnam()
1916 */
1917 static int
1918 tempfileandname(char *fname, size_t len)
1919 {
1920 #define TEMPLATE      "sdccXXXXXX"
1921 #define TEMPLATE_LEN  ((sizeof TEMPLATE) - 1)
1922
1923   const char *tmpdir = NULL;
1924   int fd;
1925
1926   if ((tmpdir = getenv ("TMP")) == NULL)
1927     if ((tmpdir = getenv ("TEMP")) == NULL)
1928       tmpdir = getenv ("TMPDIR");
1929
1930 #if defined(_WIN32)
1931   {
1932     static int warning_emitted;
1933
1934     if (tmpdir == NULL)
1935       {
1936         tmpdir = "c:\\";
1937         if (!warning_emitted)
1938           {
1939             fprintf (stderr, "TMP not defined in environment, using %s for temporary files\n.", tmpdir);
1940             warning_emitted = 1;
1941           }
1942       }
1943   }
1944 #else
1945   {
1946     /* try with /usr/tmp and /tmp on Un*x systems */
1947     struct stat statbuf;
1948
1949     if (tmpdir == NULL) {
1950       if (stat("/usr/tmp", &statbuf) != -1)
1951         tmpdir = "/usr/tmp";
1952       else if (stat("/tmp", &statbuf) != -1)
1953         tmpdir = "/tmp";
1954     }
1955   }
1956 #endif
1957
1958 #ifdef HAVE_MKSTEMP
1959   {
1960     char fnamebuf[PATH_MAX];
1961     size_t name_len;
1962
1963     if (fname == NULL || len == 0) {
1964       fname = fnamebuf;
1965       len = sizeof fnamebuf;
1966     }
1967
1968     if (tmpdir) {
1969       name_len = strlen(tmpdir) + 1 + TEMPLATE_LEN;
1970
1971       assert(name_len < len);
1972       if (!(name_len < len))  /* in NDEBUG is defined */
1973         return -1;            /* buffer too small, temporary file can not be created */
1974
1975       sprintf(fname, "%s" DIR_SEPARATOR_STRING TEMPLATE, tmpdir);
1976     }
1977     else {
1978       name_len = TEMPLATE_LEN;
1979
1980       assert(name_len < len);
1981       if (!(name_len < len))  /* in NDEBUG is defined */
1982         return -1;            /* buffer too small, temporary file can not be created */
1983
1984       strcpy(fname, TEMPLATE);
1985     }
1986
1987     fd = mkstemp(fname);
1988   }
1989 #else
1990   {
1991     char *name = tempnam(tmpdir, "sdcc");
1992
1993     if (name == NULL) {
1994       perror("Can't create temporary file name");
1995       exit(1);
1996     }
1997
1998     assert(strlen(name) < len);
1999     if (!(strlen(name) < len))  /* in NDEBUG is defined */
2000       return -1;                /* buffer too small, temporary file can not be created */
2001
2002     strcpy(fname, name);
2003 #ifdef _WIN32
2004     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IREAD | S_IWRITE);
2005 #else
2006     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IRUSR | S_IWUSR);
2007 #endif
2008   }
2009 #endif
2010
2011   if (fd == -1) {
2012     perror("Can't create temporary file");
2013     exit(1);
2014   }
2015
2016   return fd;
2017 }
2018
2019
2020 /** Create a temporary file name
2021 */
2022 char *
2023 tempfilename(void)
2024 {
2025   int fd;
2026   static char fnamebuf[PATH_MAX];
2027
2028   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
2029     fprintf(stderr, "Can't create temporary file name!");
2030     exit(1);
2031   }
2032
2033   fd = close(fd);
2034   assert(fd != -1);
2035
2036   return fnamebuf;
2037 }
2038
2039
2040 /** Create a temporary file and add it to tmpfileNameSet,
2041     so that it is removed explicitly by rm_tmpfiles()
2042     or implicitly at program extit.
2043 */
2044 FILE *
2045 tempfile(void)
2046 {
2047   int fd;
2048   char *tmp;
2049   FILE *fp;
2050   char fnamebuf[PATH_MAX];
2051
2052   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
2053     fprintf(stderr, "Can't create temporary file!");
2054     exit(1);
2055   }
2056
2057   tmp = Safe_strdup(fnamebuf);
2058   if (tmp)
2059     addSetHead(&tmpfileNameSet, tmp);
2060
2061   if ((fp = fdopen(fd, "w+b")) == NULL) {
2062       perror("Can't create temporary file!");
2063       exit(1);
2064   }
2065
2066   return fp;
2067 }