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