fixed bug #700797
[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 ();
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 ();
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; last_type && DCL_ELEM (last_type); last_type = last_type->next)
814     lcnt *= DCL_ELEM (last_type);
815
816   for (;;)
817     {
818       size++;
819       printIval (sym, type->next, iloop, oFile);
820       iloop = (iloop ? iloop->next : NULL);
821
822
823       /* if not array limits given & we */
824       /* are out of initialisers then   */
825       if (!DCL_ELEM (type) && !iloop)
826         break;
827
828       /* no of elements given and we    */
829       /* have generated for all of them */
830       if (!--lcnt) {
831         /* if initializers left */
832         if (iloop) {
833           werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef);
834         }
835         break;
836       }
837     }
838
839   /* if we have not been given a size  */
840   if (!DCL_ELEM (type))
841     DCL_ELEM (type) = size;
842
843   return;
844 }
845
846 /*-----------------------------------------------------------------*/
847 /* printIvalFuncPtr - generate initial value for function pointers */
848 /*-----------------------------------------------------------------*/
849 void 
850 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
851 {
852   value *val;
853   int dLvl = 0;
854
855   val = list2val (ilist);
856
857   if (!val) {
858     // an error has been thrown allready
859     val=constVal("0");
860   }
861
862   if (IS_LITERAL(val->etype)) {
863     if (compareType(type,val->etype)==0) {
864       werror (E_INCOMPAT_TYPES);
865       printFromToType (val->type, type);
866     }
867     printIvalCharPtr (NULL, type, val, oFile);
868     return;
869   }
870
871   /* check the types   */
872   if ((dLvl = compareType (val->type, type->next)) <= 0)
873     {
874       tfprintf (oFile, "\t!dw !constword\n", 0);
875       return;
876     }
877
878   /* now generate the name */
879   if (!val->sym)
880     {
881       if (port->use_dw_for_init)
882         {
883           tfprintf (oFile, "\t!dws\n", val->name);
884         }
885       else
886         {
887           printPointerType (oFile, val->name);
888         }
889     }
890   else if (port->use_dw_for_init)
891     {
892       tfprintf (oFile, "\t!dws\n", val->sym->rname);
893     }
894   else
895     {
896       printPointerType (oFile, val->sym->rname);
897     }
898
899   return;
900 }
901
902 /*-----------------------------------------------------------------*/
903 /* printIvalCharPtr - generates initial values for character pointers */
904 /*-----------------------------------------------------------------*/
905 int 
906 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
907 {
908   int size = 0;
909
910   /* PENDING: this is _very_ mcs51 specific, including a magic
911      number...
912      It's also endin specific.
913    */
914   size = getSize (type);
915
916   if (val->name && strlen (val->name))
917     {
918       if (size == 1)            /* This appears to be Z80 specific?? */
919         {
920           tfprintf (oFile,
921                     "\t!dbs\n", val->name);
922         }
923       else if (size == FPTRSIZE)
924         {
925           if (port->use_dw_for_init)
926             {
927               tfprintf (oFile, "\t!dws\n", val->name);
928             }
929           else
930             {
931               printPointerType (oFile, val->name);
932             }
933         }
934       else if (size == GPTRSIZE)
935         {
936           int type;
937           if (IS_PTR (val->type)) {
938             type = DCL_TYPE (val->type);
939           } else {
940             type = PTR_TYPE (SPEC_OCLS (val->etype));
941           }
942           if (val->sym && val->sym->isstrlit) {
943             // this is a literal string
944             type=CPOINTER;
945           }
946           printGPointerType (oFile, val->name, sym->name, type);
947         }
948       else
949         {
950           fprintf (stderr, "*** internal error: unknown size in "
951                    "printIvalCharPtr.\n");
952         }
953     }
954   else
955     {
956       // these are literals assigned to pointers
957       switch (size)
958         {
959         case 1:
960           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
961           break;
962         case 2:
963           if (port->use_dw_for_init)
964             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
965           else
966             tfprintf (oFile, "\t.byte %s,%s\n",
967                       aopLiteral (val, 0), aopLiteral (val, 1));
968           break;
969         case 3:
970           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
971             // non-zero mcs51 generic pointer
972             werror (E_LITERAL_GENERIC);
973           }
974           fprintf (oFile, "\t.byte %s,%s,%s\n",
975                    aopLiteral (val, 0), 
976                    aopLiteral (val, 1),
977                    aopLiteral (val, 2));
978           break;
979         case 4:
980           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
981             // non-zero ds390 generic pointer
982             werror (E_LITERAL_GENERIC);
983           }
984           fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
985                    aopLiteral (val, 0), 
986                    aopLiteral (val, 1), 
987                    aopLiteral (val, 2),
988                    aopLiteral (val, 3));
989           break;
990         default:
991           assert (0);
992         }
993     }
994
995   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
996     addSet (&statsg->syms, val->sym);
997   }
998
999   return 1;
1000 }
1001
1002 /*-----------------------------------------------------------------*/
1003 /* printIvalPtr - generates initial value for pointers             */
1004 /*-----------------------------------------------------------------*/
1005 void 
1006 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1007 {
1008   value *val;
1009   int size;
1010
1011   /* if deep then   */
1012   if (ilist->type == INIT_DEEP)
1013     ilist = ilist->init.deep;
1014
1015   /* function pointer     */
1016   if (IS_FUNC (type->next))
1017     {
1018       printIvalFuncPtr (type, ilist, oFile);
1019       return;
1020     }
1021
1022   if (!(val = initPointer (ilist, type)))
1023     return;
1024
1025   /* if character pointer */
1026   if (IS_CHAR (type->next))
1027     if (printIvalCharPtr (sym, type, val, oFile))
1028       return;
1029
1030   /* check the type      */
1031   if (compareType (type, val->type) == 0) {
1032     werror (W_INIT_WRONG);
1033     printFromToType (val->type, type);
1034   }
1035
1036   /* if val is literal */
1037   if (IS_LITERAL (val->etype))
1038     {
1039       switch (getSize (type))
1040         {
1041         case 1:
1042           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
1043           break;
1044         case 2:
1045           if (port->use_dw_for_init)
1046             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
1047           else
1048             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1049           break;
1050         case 3: // how about '390??
1051           fprintf (oFile, "\t.byte %s,%s,#0x%d\n",
1052                    aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE);
1053         }
1054       return;
1055     }
1056
1057
1058   size = getSize (type);
1059
1060   if (size == 1)                /* Z80 specific?? */
1061     {
1062       tfprintf (oFile, "\t!dbs\n", val->name);
1063     }
1064   else if (size == FPTRSIZE)
1065     {
1066       if (port->use_dw_for_init) {
1067         tfprintf (oFile, "\t!dws\n", val->name);
1068       } else {
1069         printPointerType (oFile, val->name);
1070       }
1071     }
1072   else if (size == GPTRSIZE)
1073     {
1074       printGPointerType (oFile, val->name, sym->name,
1075                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1076                           PTR_TYPE (SPEC_OCLS (val->etype))));
1077     }
1078   return;
1079 }
1080
1081 /*-----------------------------------------------------------------*/
1082 /* printIval - generates code for initial value                    */
1083 /*-----------------------------------------------------------------*/
1084 void 
1085 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1086 {
1087   if (!ilist)
1088     return;
1089
1090   /* update line number for error msgs */
1091   lineno=sym->lineDef;
1092
1093   /* if structure then    */
1094   if (IS_STRUCT (type))
1095     {
1096       printIvalStruct (sym, type, ilist, oFile);
1097       return;
1098     }
1099
1100   /* if this is a pointer */
1101   if (IS_PTR (type))
1102     {
1103       printIvalPtr (sym, type, ilist, oFile);
1104       return;
1105     }
1106
1107   /* if this is an array   */
1108   if (IS_ARRAY (type))
1109     {
1110       printIvalArray (sym, type, ilist, oFile);
1111       return;
1112     }
1113
1114   /* if type is SPECIFIER */
1115   if (IS_SPEC (type))
1116     {
1117       printIvalType (sym, type, ilist, oFile);
1118       return;
1119     }
1120 }
1121
1122 /*-----------------------------------------------------------------*/
1123 /* emitStaticSeg - emitcode for the static segment                 */
1124 /*-----------------------------------------------------------------*/
1125 void 
1126 emitStaticSeg (memmap * map, FILE * out)
1127 {
1128   symbol *sym;
1129
1130   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1131
1132   /* for all variables in this segment do */
1133   for (sym = setFirstItem (map->syms); sym;
1134        sym = setNextItem (map->syms))
1135     {
1136
1137       /* if it is "extern" then do nothing */
1138       if (IS_EXTERN (sym->etype))
1139         continue;
1140
1141       /* if it is not static add it to the public
1142          table */
1143       if (!IS_STATIC (sym->etype))
1144         {
1145           addSetHead (&publics, sym);
1146         }
1147
1148       /* print extra debug info if required */
1149       if (options.debug) {
1150         cdbSymbol (sym, cdbFile, FALSE, FALSE);
1151         if (!sym->level)
1152           {                     /* global */
1153             if (IS_STATIC (sym->etype))
1154               fprintf (out, "F%s$", moduleName);        /* scope is file */
1155             else
1156               fprintf (out, "G$");      /* scope is global */
1157           }
1158         else
1159           /* symbol is local */
1160           fprintf (out, "L%s$",
1161                    (sym->localof ? sym->localof->name : "-null-"));
1162         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1163       }
1164       
1165       /* if it has an absolute address */
1166       if (SPEC_ABSA (sym->etype))
1167         {
1168           if (options.debug)
1169             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1170           
1171           fprintf (out, "%s\t=\t0x%04x\n",
1172                    sym->rname,
1173                    SPEC_ADDR (sym->etype));
1174         }
1175       else
1176         {
1177           if (options.debug)
1178             fprintf (out, " == .\n");
1179           
1180           /* if it has an initial value */
1181           if (sym->ival)
1182             {
1183               fprintf (out, "%s:\n", sym->rname);
1184               noAlloc++;
1185               resolveIvalSym (sym->ival);
1186               printIval (sym, sym->type, sym->ival, out);
1187               noAlloc--;
1188               /* if sym is a simple string and sym->ival is a string, 
1189                  WE don't need it anymore */
1190               if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) &&
1191                   IS_AST_SYM_VALUE(list2expr(sym->ival)) &&
1192                   list2val(sym->ival)->sym->isstrlit) {
1193                 freeStringSymbol(list2val(sym->ival)->sym);
1194               }
1195             }
1196           else {
1197               /* allocate space */
1198               int size = getSize (sym->type);
1199               
1200               if (size==0) {
1201                   werror(E_UNKNOWN_SIZE,sym->name);
1202               }
1203               fprintf (out, "%s:\n", sym->rname);
1204               /* special case for character strings */
1205               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1206                   SPEC_CVAL (sym->etype).v_char)
1207                   printChar (out,
1208                              SPEC_CVAL (sym->etype).v_char,
1209                              strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1210               else
1211                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1212             }
1213         }
1214     }
1215 }
1216
1217 /*-----------------------------------------------------------------*/
1218 /* emitMaps - emits the code for the data portion the code         */
1219 /*-----------------------------------------------------------------*/
1220 void 
1221 emitMaps (void)
1222 {
1223   inInitMode++;
1224   /* no special considerations for the following
1225      data, idata & bit & xdata */
1226   emitRegularMap (data, TRUE, TRUE);
1227   emitRegularMap (idata, TRUE, TRUE);
1228   emitRegularMap (bit, TRUE, FALSE);
1229   emitRegularMap (xdata, TRUE, TRUE);
1230   if (port->genXINIT) {
1231     emitRegularMap (xidata, TRUE, TRUE);
1232   }
1233   emitRegularMap (sfr, FALSE, FALSE);
1234   emitRegularMap (sfrbit, FALSE, FALSE);
1235   emitRegularMap (home, TRUE, FALSE);
1236   emitRegularMap (code, TRUE, FALSE);
1237
1238   emitStaticSeg (statsg, code->oFile);
1239   if (port->genXINIT) {
1240     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1241     emitStaticSeg (xinit, code->oFile);
1242   }
1243   inInitMode--;
1244 }
1245
1246 /*-----------------------------------------------------------------*/
1247 /* flushStatics - flush all currently defined statics out to file  */
1248 /*  and delete.  Temporary function                                */
1249 /*-----------------------------------------------------------------*/
1250 void 
1251 flushStatics (void)
1252 {
1253   emitStaticSeg (statsg, codeOutFile);
1254   statsg->syms = NULL;
1255 }
1256
1257 /*-----------------------------------------------------------------*/
1258 /* createInterruptVect - creates the interrupt vector              */
1259 /*-----------------------------------------------------------------*/
1260 void 
1261 createInterruptVect (FILE * vFile)
1262 {
1263   unsigned i = 0;
1264   mainf = newSymbol ("main", 0);
1265   mainf->block = 0;
1266
1267   /* only if the main function exists */
1268   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1269     {
1270       if (!options.cc_only && !noAssemble && !options.c1mode)
1271         werror (E_NO_MAIN);
1272       return;
1273     }
1274
1275   /* if the main is only a prototype ie. no body then do nothing */
1276   if (!IFFUNC_HASBODY(mainf->type))
1277     {
1278       /* if ! compile only then main function should be present */
1279       if (!options.cc_only && !noAssemble)
1280         werror (E_NO_MAIN);
1281       return;
1282     }
1283
1284   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1285   fprintf (vFile, "__interrupt_vect:\n");
1286
1287
1288   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1289     {
1290       /* "generic" interrupt table header (if port doesn't specify one).
1291        * Look suspiciously like 8051 code to me...
1292        */
1293
1294       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1295
1296
1297       /* now for the other interrupts */
1298       for (; i < maxInterrupts; i++)
1299         {
1300           if (interrupts[i])
1301             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1302           else
1303             fprintf (vFile, "\treti\n\t.ds\t7\n");
1304         }
1305     }
1306 }
1307
1308 char *iComments1 =
1309 {
1310   ";--------------------------------------------------------\n"
1311   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1312
1313 char *iComments2 =
1314 {
1315   ";--------------------------------------------------------\n"};
1316
1317
1318 /*-----------------------------------------------------------------*/
1319 /* initialComments - puts in some initial comments                 */
1320 /*-----------------------------------------------------------------*/
1321 void 
1322 initialComments (FILE * afile)
1323 {
1324   time_t t;
1325   time (&t);
1326   fprintf (afile, "%s", iComments1);
1327   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1328   fprintf (afile, "%s", iComments2);
1329 }
1330
1331 /*-----------------------------------------------------------------*/
1332 /* printPublics - generates .global for publics                    */
1333 /*-----------------------------------------------------------------*/
1334 void 
1335 printPublics (FILE * afile)
1336 {
1337   symbol *sym;
1338
1339   fprintf (afile, "%s", iComments2);
1340   fprintf (afile, "; Public variables in this module\n");
1341   fprintf (afile, "%s", iComments2);
1342
1343   for (sym = setFirstItem (publics); sym;
1344        sym = setNextItem (publics))
1345     tfprintf (afile, "\t!global\n", sym->rname);
1346 }
1347
1348 /*-----------------------------------------------------------------*/
1349 /* printExterns - generates .global for externs                    */
1350 /*-----------------------------------------------------------------*/
1351 void 
1352 printExterns (FILE * afile)
1353 {
1354   symbol *sym;
1355
1356   fprintf (afile, "%s", iComments2);
1357   fprintf (afile, "; Externals used\n");
1358   fprintf (afile, "%s", iComments2);
1359
1360   for (sym = setFirstItem (externs); sym;
1361        sym = setNextItem (externs))
1362     tfprintf (afile, "\t!extern\n", sym->rname);
1363 }
1364
1365 /*-----------------------------------------------------------------*/
1366 /* emitOverlay - will emit code for the overlay stuff              */
1367 /*-----------------------------------------------------------------*/
1368 static void 
1369 emitOverlay (FILE * afile)
1370 {
1371   set *ovrset;
1372
1373   if (!elementsInSet (ovrSetSets))
1374     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1375
1376   /* for each of the sets in the overlay segment do */
1377   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1378        ovrset = setNextItem (ovrSetSets))
1379     {
1380
1381       symbol *sym;
1382
1383       if (elementsInSet (ovrset))
1384         {
1385           /* output the area informtion */
1386           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1387         }
1388
1389       for (sym = setFirstItem (ovrset); sym;
1390            sym = setNextItem (ovrset))
1391         {
1392           /* if extern then it is in the publics table: do nothing */
1393           if (IS_EXTERN (sym->etype))
1394             continue;
1395
1396           /* if allocation required check is needed
1397              then check if the symbol really requires
1398              allocation only for local variables */
1399           if (!IS_AGGREGATE (sym->type) &&
1400               !(sym->_isparm && !IS_REGPARM (sym->etype))
1401               && !sym->allocreq && sym->level)
1402             continue;
1403
1404           /* if global variable & not static or extern
1405              and addPublics allowed then add it to the public set */
1406           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1407               && !IS_STATIC (sym->etype))
1408             {
1409               addSetHead (&publics, sym);
1410             }
1411
1412           /* if extern then do nothing or is a function
1413              then do nothing */
1414           if (IS_FUNC (sym->type))
1415             continue;
1416
1417           /* print extra debug info if required */
1418           if (options.debug)
1419             {
1420               cdbSymbol (sym, cdbFile, FALSE, FALSE);
1421
1422               if (!sym->level)
1423                 {               /* global */
1424                   if (IS_STATIC (sym->etype))
1425                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1426                   else
1427                     fprintf (afile, "G$");      /* scope is global */
1428                 }
1429               else
1430                 /* symbol is local */
1431                 fprintf (afile, "L%s$",
1432                          (sym->localof ? sym->localof->name : "-null-"));
1433               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1434             }
1435
1436           /* if is has an absolute address then generate
1437              an equate for this no need to allocate space */
1438           if (SPEC_ABSA (sym->etype))
1439             {
1440
1441               if (options.debug)
1442                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1443
1444               fprintf (afile, "%s\t=\t0x%04x\n",
1445                        sym->rname,
1446                        SPEC_ADDR (sym->etype));
1447             }
1448           else {
1449               int size = getSize(sym->type);
1450
1451               if (size==0) {
1452                   werror(E_UNKNOWN_SIZE,sym->name);
1453               }       
1454               if (options.debug)
1455                   fprintf (afile, "==.\n");
1456               
1457               /* allocate space */
1458               tfprintf (afile, "!labeldef\n", sym->rname);
1459               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1460           }
1461           
1462         }
1463     }
1464 }
1465
1466 /*-----------------------------------------------------------------*/
1467 /* glue - the final glue that hold the whole thing together        */
1468 /*-----------------------------------------------------------------*/
1469 void 
1470 glue (void)
1471 {
1472   FILE *vFile;
1473   FILE *asmFile;
1474   FILE *ovrFile = tempfile ();
1475
1476   addSetHead (&tmpfileSet, ovrFile);
1477   /* print the global struct definitions */
1478   if (options.debug)
1479     cdbStructBlock (0, cdbFile);
1480
1481   vFile = tempfile ();
1482   /* PENDING: this isnt the best place but it will do */
1483   if (port->general.glue_up_main)
1484     {
1485       /* create the interrupt vector table */
1486       createInterruptVect (vFile);
1487     }
1488
1489   addSetHead (&tmpfileSet, vFile);
1490
1491   /* emit code for the all the variables declared */
1492   emitMaps ();
1493   /* do the overlay segments */
1494   emitOverlay (ovrFile);
1495
1496   /* now put it all together into the assembler file */
1497   /* create the assembler file name */
1498
1499   /* -o option overrides default name? */
1500   if ((noAssemble || options.c1mode) && fullDstFileName)
1501     {
1502       strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1503     }
1504   else
1505     {
1506       strncpyz (scratchFileName, dstFileName, PATH_MAX);
1507       strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1508     }
1509
1510   if (!(asmFile = fopen (scratchFileName, "w")))
1511     {
1512       werror (E_FILE_OPEN_ERR, scratchFileName);
1513       exit (1);
1514     }
1515
1516   /* initial comments */
1517   initialComments (asmFile);
1518
1519   /* print module name */
1520   tfprintf (asmFile, "\t!module\n", moduleName);
1521   tfprintf (asmFile, "\t!fileprelude\n");
1522
1523   /* Let the port generate any global directives, etc. */
1524   if (port->genAssemblerPreamble)
1525     {
1526       port->genAssemblerPreamble (asmFile);
1527     }
1528
1529   /* print the global variables in this module */
1530   printPublics (asmFile);
1531   if (port->assembler.externGlobal)
1532     printExterns (asmFile);
1533
1534   /* copy the sfr segment */
1535   fprintf (asmFile, "%s", iComments2);
1536   fprintf (asmFile, "; special function registers\n");
1537   fprintf (asmFile, "%s", iComments2);
1538   copyFile (asmFile, sfr->oFile);
1539
1540   /* copy the sbit segment */
1541   fprintf (asmFile, "%s", iComments2);
1542   fprintf (asmFile, "; special function bits \n");
1543   fprintf (asmFile, "%s", iComments2);
1544   copyFile (asmFile, sfrbit->oFile);
1545   
1546   /*JCF: Create the areas for the register banks*/
1547   if(port->general.glue_up_main &&
1548      (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51))
1549   {
1550           if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1551           {
1552                  fprintf (asmFile, "%s", iComments2);
1553                  fprintf (asmFile, "; overlayable register banks \n");
1554                  fprintf (asmFile, "%s", iComments2);
1555                  if(RegBankUsed[0])
1556                         fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1557                  if(RegBankUsed[1]||options.parms_in_bank1)
1558                         fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1559                  if(RegBankUsed[2])
1560                         fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1561                  if(RegBankUsed[3])
1562                         fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1563           }
1564   }
1565
1566   /* copy the data segment */
1567   fprintf (asmFile, "%s", iComments2);
1568   fprintf (asmFile, "; internal ram data\n");
1569   fprintf (asmFile, "%s", iComments2);
1570   copyFile (asmFile, data->oFile);
1571
1572
1573   /* create the overlay segments */
1574   if (overlay) {
1575     fprintf (asmFile, "%s", iComments2);
1576     fprintf (asmFile, "; overlayable items in internal ram \n");
1577     fprintf (asmFile, "%s", iComments2);
1578     copyFile (asmFile, ovrFile);
1579   }
1580
1581   /* create the stack segment MOF */
1582   if (mainf && IFFUNC_HASBODY(mainf->type))
1583     {
1584       fprintf (asmFile, "%s", iComments2);
1585       fprintf (asmFile, "; Stack segment in internal ram \n");
1586       fprintf (asmFile, "%s", iComments2);
1587       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1588                "__start__stack:\n\t.ds\t1\n\n");
1589     }
1590
1591   /* create the idata segment */
1592   if (idata) {
1593     fprintf (asmFile, "%s", iComments2);
1594     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1595     fprintf (asmFile, "%s", iComments2);
1596     copyFile (asmFile, idata->oFile);
1597   }
1598
1599   /* copy the bit segment */
1600   fprintf (asmFile, "%s", iComments2);
1601   fprintf (asmFile, "; bit data\n");
1602   fprintf (asmFile, "%s", iComments2);
1603   copyFile (asmFile, bit->oFile);
1604
1605   /* if external stack then reserve space of it */
1606   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1607     {
1608       fprintf (asmFile, "%s", iComments2);
1609       fprintf (asmFile, "; external stack \n");
1610       fprintf (asmFile, "%s", iComments2);
1611       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1612       fprintf (asmFile, "\t.ds 256\n");
1613     }
1614
1615
1616   /* copy xtern ram data */
1617   fprintf (asmFile, "%s", iComments2);
1618   fprintf (asmFile, "; external ram data\n");
1619   fprintf (asmFile, "%s", iComments2);
1620   copyFile (asmFile, xdata->oFile);
1621
1622   /* copy xternal initialized ram data */
1623   fprintf (asmFile, "%s", iComments2);
1624   fprintf (asmFile, "; external initialized ram data\n");
1625   fprintf (asmFile, "%s", iComments2);
1626   copyFile (asmFile, xidata->oFile);
1627
1628   /* copy the interrupt vector table */
1629   if (mainf && IFFUNC_HASBODY(mainf->type))
1630     {
1631       fprintf (asmFile, "%s", iComments2);
1632       fprintf (asmFile, "; interrupt vector \n");
1633       fprintf (asmFile, "%s", iComments2);
1634       copyFile (asmFile, vFile);
1635     }
1636
1637   /* copy global & static initialisations */
1638   fprintf (asmFile, "%s", iComments2);
1639   fprintf (asmFile, "; global & static initialisations\n");
1640   fprintf (asmFile, "%s", iComments2);
1641
1642   /* Everywhere we generate a reference to the static_name area,
1643    * (which is currently only here), we immediately follow it with a
1644    * definition of the post_static_name area. This guarantees that
1645    * the post_static_name area will immediately follow the static_name
1646    * area.
1647    */
1648   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1649   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1650   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1651
1652   if (mainf && IFFUNC_HASBODY(mainf->type))
1653     {
1654       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1655       /* if external stack is specified then the
1656          higher order byte of the xdatalocation is
1657          going into P2 and the lower order going into
1658          spx */
1659       if (options.useXstack)
1660         {
1661           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1662                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1663           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1664                    (unsigned int) options.xdata_loc & 0xff);
1665         }
1666
1667       /* initialise the stack pointer.  JCF: aslink takes care of the location */
1668         fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");   /* MOF */
1669
1670       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1671       fprintf (asmFile, "\tmov\ta,dpl\n");
1672       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1673       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1674       fprintf (asmFile, "__sdcc_init_data:\n");
1675
1676       // if the port can copy the XINIT segment to XISEG
1677       if (port->genXINIT) {
1678         port->genXINIT(asmFile);
1679       }
1680
1681     }
1682   copyFile (asmFile, statsg->oFile);
1683
1684   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1685     {
1686       /* This code is generated in the post-static area.
1687        * This area is guaranteed to follow the static area
1688        * by the ugly shucking and jiving about 20 lines ago.
1689        */
1690       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1691       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1692     }
1693
1694   fprintf (asmFile,
1695            "%s"
1696            "; Home\n"
1697            "%s", iComments2, iComments2);
1698   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1699   copyFile (asmFile, home->oFile);
1700
1701   /* copy over code */
1702   fprintf (asmFile, "%s", iComments2);
1703   fprintf (asmFile, "; code\n");
1704   fprintf (asmFile, "%s", iComments2);
1705   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1706   if (mainf && IFFUNC_HASBODY(mainf->type))
1707     {
1708
1709       /* entry point @ start of CSEG */
1710       fprintf (asmFile, "__sdcc_program_startup:\n");
1711
1712       /* put in the call to main */
1713       fprintf (asmFile, "\tlcall\t_main\n");
1714       if (options.mainreturn)
1715         {
1716
1717           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1718           fprintf (asmFile, "\tret\n");
1719
1720         }
1721       else
1722         {
1723
1724           fprintf (asmFile, ";\treturn from main will lock up\n");
1725           fprintf (asmFile, "\tsjmp .\n");
1726         }
1727     }
1728   copyFile (asmFile, code->oFile);
1729
1730   if (port->genAssemblerEnd) {
1731       port->genAssemblerEnd(asmFile);
1732   }
1733   fclose (asmFile);
1734
1735   rm_tmpfiles ();
1736 }
1737
1738
1739 /** Creates a temporary file with unoque file name
1740     Scans, in order:
1741     - TMP, TEMP, TMPDIR env. varibles
1742     - if Un*x system: /usr/tmp and /tmp
1743     - root directory using mkstemp() if avaliable
1744     - default location using tempnam()
1745 */
1746 static int
1747 tempfileandname(char *fname, size_t len)
1748 {
1749 #define TEMPLATE      "sdccXXXXXX"
1750 #define TEMPLATE_LEN  ((sizeof TEMPLATE) - 1)
1751
1752   const char *tmpdir = NULL;
1753   int fd;
1754
1755   if ((tmpdir = getenv ("TMP")) == NULL)
1756     if ((tmpdir = getenv ("TEMP")) == NULL)
1757       tmpdir = getenv ("TMPDIR");
1758
1759 #ifndef _WIN32
1760   {
1761     /* try with /usr/tmp and /tmp on Un*x systems */
1762     struct stat statbuf;
1763
1764     if (tmpdir == NULL) {
1765       if (stat("/usr/tmp", &statbuf) != -1)
1766         tmpdir = "/usr/tmp";
1767       else if (stat("/tmp", &statbuf) != -1)
1768         tmpdir = "/tmp";
1769     }
1770   }
1771 #endif
1772
1773 #ifdef HAVE_MKSTEMP
1774   {
1775     char fnamebuf[PATH_MAX];
1776     size_t name_len;
1777
1778     if (fname == NULL || len == 0) {
1779       fname = fnamebuf;
1780       len = sizeof fnamebuf;
1781     }
1782
1783     if (tmpdir) {
1784       name_len = strlen(tmpdir) + 1 + TEMPLATE_LEN;
1785
1786       assert(name_len < len);
1787       if (!(name_len < len))  /* in NDEBUG is defined */
1788         return -1;            /* buffer too small, temporary file can not be created */
1789
1790       sprintf(fname, "%s" DIR_SEPARATOR_STRING TEMPLATE, tmpdir);
1791     }
1792     else {
1793       name_len = TEMPLATE_LEN;
1794
1795       assert(name_len < len);
1796       if (!(name_len < len))  /* in NDEBUG is defined */
1797         return -1;            /* buffer too small, temporary file can not be created */
1798
1799       strcpy(fname, TEMPLATE);
1800     }
1801
1802     fd = mkstemp(fname);
1803   }
1804 #else
1805   {
1806     char *name = tempnam(tmpdir, "sdcc");
1807
1808     if (name == NULL) {
1809       perror("Can't create temporary file name");
1810       exit(1);
1811     }
1812
1813     assert(strlen(name) < len);
1814     if (!(strlen(name) < len))  /* in NDEBUG is defined */
1815       return -1;                /* buffer too small, temporary file can not be created */
1816
1817     strcpy(fname, name);
1818 #ifdef _WIN32
1819     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IREAD | S_IWRITE);
1820 #else
1821     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IRUSR | S_IWUSR);
1822 #endif
1823   }
1824 #endif
1825
1826   if (fd == -1) {
1827     perror("Can't create temporary file");
1828     exit(1);
1829   }
1830
1831   return fd;
1832 }
1833
1834
1835 /** Create a temporary file name
1836 */
1837 char *
1838 tempfilename(void)
1839 {
1840   int fd;
1841   static char fnamebuf[PATH_MAX];
1842
1843   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1844     fprintf(stderr, "Can't create temporary file name!");
1845     exit(1);
1846   }
1847
1848   fd = close(fd);
1849   assert(fd != -1);
1850
1851   return fnamebuf;
1852 }
1853
1854
1855 /** Create a temporary file and add it to tmpfileNameSet,
1856     so that it is removed explicitly by rm_tmpfiles()
1857     or implicitly at program extit.
1858 */
1859 FILE *
1860 tempfile(void)
1861 {
1862   int fd;
1863   char *tmp;
1864   FILE *fp;
1865   char fnamebuf[PATH_MAX];
1866
1867   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1868     fprintf(stderr, "Can't create temporary file!");
1869     exit(1);
1870   }
1871
1872   tmp = Safe_strdup(fnamebuf);
1873   if (tmp)
1874     addSetHead(&tmpfileNameSet, tmp);
1875
1876   if ((fp = fdopen(fd, "w+b")) == NULL) {
1877       perror("Can't create temporary file!");
1878       exit(1);
1879   }
1880
1881   return fp;
1882 }