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