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