22af1da0f784aa77e84af58fff25718008f98005
[fw/sdcc] / src / SDCCglue.c
1 /*-------------------------------------------------------------------------
2
3   SDCCglue.c - glues everything we have done together into one file.
4                 Written By -  Sandeep Dutta . sandeep.dutta@usa.net (1998)
5
6    This program is free software; you can redistribute it and/or modify it
7    under the terms of the GNU General Public License as published by the
8    Free Software Foundation; either version 2, or (at your option) any
9    later version.
10
11    This program is distributed in the hope that it will be useful,
12    but WITHOUT ANY WARRANTY; without even the implied warranty of
13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14    GNU General Public License for more details.
15
16    You should have received a copy of the GNU General Public License
17    along with this program; if not, write to the Free Software
18    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
19
20    In other words, you are welcome to use, share and improve this program.
21    You are forbidden to forbid anyone else to use, share and improve
22    what you give them.   Help stamp out software-hoarding!
23 -------------------------------------------------------------------------*/
24
25 #include "common.h"
26 #include "asm.h"
27 #include <time.h>
28 #include "newalloc.h"
29 #include <fcntl.h>
30 #include <sys/stat.h>
31
32 #ifdef _WIN32
33 #include <io.h>
34 #else
35 #include <unistd.h>
36 #endif
37
38 symbol *interrupts[256];
39
40 void printIval (symbol *, sym_link *, initList *, FILE *);
41 set *publics = NULL;            /* public variables */
42 set *externs = NULL;            /* Varibles that are declared as extern */
43
44 /* TODO: this should be configurable (DS803C90 uses more than 6) */
45 unsigned maxInterrupts = 6;
46 int allocInfo = 1;
47 symbol *mainf;
48 extern char *VersionString;
49 set *pipeSet = NULL;            /* set of pipes */
50 set *tmpfileSet = NULL;         /* set of tmp file created by the compiler */
51 set *tmpfileNameSet = NULL;     /* All are unlinked at close. */
52
53 /*-----------------------------------------------------------------*/
54 /* closePipes - closes all pipes created by the compiler           */
55 /*-----------------------------------------------------------------*/
56 DEFSETFUNC (closePipes)
57 {
58   FILE *pfile = item;
59   int ret;
60
61   if (pfile) {
62     ret = pclose (pfile);
63     assert(ret != -1);
64   }
65
66   return 0;
67 }
68
69 /*-----------------------------------------------------------------*/
70 /* closeTmpFiles - closes all tmp files created by the compiler    */
71 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
72 /*-----------------------------------------------------------------*/
73 DEFSETFUNC (closeTmpFiles)
74 {
75   FILE *tfile = item;
76   int ret;
77
78   if (tfile) {
79     ret = fclose (tfile);
80     assert(ret == 0);
81   }
82
83   return 0;
84 }
85
86 /*-----------------------------------------------------------------*/
87 /* rmTmpFiles - unlinks all tmp files created by the compiler      */
88 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
89 /*-----------------------------------------------------------------*/
90 DEFSETFUNC (rmTmpFiles)
91 {
92   char *name = item;
93   int ret;
94
95   if (name) {
96       ret = unlink (name);
97       assert(ret == 0);
98       Safe_free (name);
99   }
100
101   return 0;
102 }
103
104 /*-----------------------------------------------------------------*/
105 /* rm_tmpfiles - close and remove temporary files and delete sets  */
106 /*-----------------------------------------------------------------*/
107 void
108 rm_tmpfiles (void)
109 {
110   /* close temporary files */
111   applyToSet (pipeSet, closePipes);
112   /* close temporary files */
113   deleteSet (&pipeSet);
114
115   applyToSet (tmpfileSet, closeTmpFiles);
116   /* remove temporary files */
117   applyToSet (tmpfileNameSet, rmTmpFiles);
118   /* delete temorary file sets */
119   deleteSet (&tmpfileSet);
120   deleteSet (&tmpfileNameSet);
121 }
122
123 /*-----------------------------------------------------------------*/
124 /* copyFile - copies source file to destination file               */
125 /*-----------------------------------------------------------------*/
126 void 
127 copyFile (FILE * dest, FILE * src)
128 {
129   int ch;
130
131   rewind (src);
132   while (!feof (src))
133     if ((ch = fgetc (src)) != EOF)
134       fputc (ch, dest);
135 }
136
137 char *
138 aopLiteralLong (value * val, int offset, int size)
139 {
140         union {
141                 float f;
142                 unsigned char c[4];
143         }
144         fl;
145
146         if (!val) {
147           // assuming we have been warned before
148           val=constVal("0");
149         }
150
151         /* if it is a float then it gets tricky */
152         /* otherwise it is fairly simple */
153         if (!IS_FLOAT (val->type)) {
154                 unsigned long v = (unsigned long) floatFromVal (val);
155
156                 v >>= (offset * 8);
157                 switch (size) {
158                 case 1:
159                         tsprintf (buffer, sizeof(buffer), 
160                                   "!immedbyte", (unsigned int) v & 0xff);
161                         break;
162                 case 2:
163                         tsprintf (buffer, sizeof(buffer), 
164                                   "!immedword", (unsigned int) v & 0xffff);
165                         break;
166                 default:
167                         /* Hmm.  Too big for now. */
168                         assert (0);
169                 }
170                 return Safe_strdup (buffer);
171         }
172
173         /* PENDING: For now size must be 1 */
174         assert (size == 1);
175
176         /* it is type float */
177         fl.f = (float) floatFromVal (val);
178 #ifdef WORDS_BIGENDIAN
179         tsprintf (buffer, sizeof(buffer), 
180                   "!immedbyte", fl.c[3 - offset]);
181 #else
182         tsprintf (buffer, sizeof(buffer), 
183                   "!immedbyte", fl.c[offset]);
184 #endif
185         return Safe_strdup (buffer);
186 }
187
188 /*-----------------------------------------------------------------*/
189 /* aopLiteral - string from a literal value                        */
190 /*-----------------------------------------------------------------*/
191 char *
192 aopLiteral (value * val, int offset)
193 {
194         return aopLiteralLong (val, offset, 1);
195 }
196
197 /*-----------------------------------------------------------------*/
198 /* emitRegularMap - emit code for maps with no special cases       */
199 /*-----------------------------------------------------------------*/
200 static void 
201 emitRegularMap (memmap * map, bool addPublics, bool arFlag)
202 {
203   symbol *sym;
204   ast *ival = NULL;
205
206   if (!map)
207     return;
208
209   if (addPublics)
210     {
211       /* PENDING: special case here - should remove */
212       if (!strcmp (map->sname, CODE_NAME))
213         tfprintf (map->oFile, "\t!areacode\n", map->sname);
214       else if (!strcmp (map->sname, DATA_NAME))
215         tfprintf (map->oFile, "\t!areadata\n", map->sname);
216       else if (!strcmp (map->sname, HOME_NAME))
217         tfprintf (map->oFile, "\t!areahome\n", map->sname);
218       else
219         tfprintf (map->oFile, "\t!area\n", map->sname);
220     }
221  
222   for (sym = setFirstItem (map->syms); sym;
223        sym = setNextItem (map->syms))
224     {
225       symbol *newSym=NULL;
226
227       /* if extern then add it into the extern list */
228       if (IS_EXTERN (sym->etype))
229         {
230           addSetHead (&externs, sym);
231           continue;
232         }
233
234       /* if allocation required check is needed
235          then check if the symbol really requires
236          allocation only for local variables */
237
238       if (arFlag && !IS_AGGREGATE (sym->type) &&
239           !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
240           !sym->allocreq && sym->level)
241         continue;
242
243       /* for bitvar locals and parameters */
244       if (!arFlag && !sym->allocreq && sym->level 
245           && !SPEC_ABSA (sym->etype)) {
246         continue;
247       }
248
249       /* if global variable & not static or extern
250          and addPublics allowed then add it to the public set */
251       if ((sym->level == 0 ||
252            (sym->_isparm && !IS_REGPARM (sym->etype))) &&
253           addPublics &&
254           !IS_STATIC (sym->etype) &&
255           (IS_FUNC(sym->type) ? (sym->used || IFFUNC_HASBODY(sym->type)) : 1))
256         {
257           addSetHead (&publics, sym);
258         }
259
260       /* if extern then do nothing or is a function
261          then do nothing */
262       if (IS_FUNC (sym->type))
263         continue;
264
265       /* print extra debug info if required */
266       if (options.debug) {
267         cdbSymbol (sym, cdbFile, FALSE, FALSE);
268         if (!sym->level) /* global */
269           if (IS_STATIC (sym->etype))
270             fprintf (map->oFile, "F%s$", moduleName); /* scope is file */
271           else
272             fprintf (map->oFile, "G$"); /* scope is global */
273         else
274           /* symbol is local */
275           fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-"));
276         fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block);
277       }
278       
279       /* if it has an initial value then do it only if
280          it is a global variable */
281       if (sym->ival && sym->level == 0) {
282         if (SPEC_OCLS(sym->etype)==xidata) {
283           // create a new "XINIT (CODE)" symbol, that will be emitted later
284           newSym=copySymbol (sym);
285           SPEC_OCLS(newSym->etype)=xinit;
286           SNPRINTF (newSym->name, sizeof(newSym->name), "__xinit_%s", sym->name);
287           SNPRINTF (newSym->rname, sizeof(newSym->rname), "__xinit_%s", sym->rname);
288           SPEC_CONST(newSym->etype)=1;
289           SPEC_STAT(newSym->etype)=1;
290           resolveIvalSym(newSym->ival);
291
292           // add it to the "XINIT (CODE)" segment
293           addSet(&xinit->syms, newSym);
294           sym->ival=NULL;
295         } else {
296           if (IS_AGGREGATE (sym->type)) {
297             ival = initAggregates (sym, sym->ival, NULL);
298           } else {
299             if (getNelements(sym->type, sym->ival)>1) {
300               werror (W_EXCESS_INITIALIZERS, "scalar", 
301                       sym->name, sym->lineDef);
302             }
303             ival = newNode ('=', newAst_VALUE (symbolVal (sym)),
304                             decorateType (resolveSymbols (list2expr (sym->ival))));
305           }
306           codeOutFile = statsg->oFile;
307
308           if (ival) {
309             // set ival's lineno to where the symbol was defined
310             setAstLineno (ival, lineno=sym->lineDef);
311             // check if this is not a constant expression
312             if (!constExprTree(ival)) {
313               werror (E_CONST_EXPECTED, "found expression");
314               // but try to do it anyway
315             }
316             allocInfo = 0;
317             eBBlockFromiCode (iCodeFromAst (ival));
318             allocInfo = 1;
319           }
320         }         
321         sym->ival = NULL;
322       }
323
324       /* if is has an absolute address then generate
325          an equate for this no need to allocate space */
326       if (SPEC_ABSA (sym->etype))
327         {
328           char *equ="=";
329           if (options.debug) {
330             fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
331           }
332           if (TARGET_IS_XA51) {
333             if (map==sfr) {
334               equ="sfr";
335             } else if (map==bit || map==sfrbit) {
336               equ="bit";
337             }
338           }
339           fprintf (map->oFile, "%s\t%s\t0x%04x\n",
340                    sym->rname, equ,
341                    SPEC_ADDR (sym->etype));
342         }
343       else {
344         int size = getSize (sym->type);
345         if (size==0) {
346           werror(E_UNKNOWN_SIZE,sym->name);
347         }
348         /* allocate space */
349         if (options.debug) {
350           fprintf (map->oFile, "==.\n");
351         }
352         if (IS_STATIC (sym->etype))
353           tfprintf (map->oFile, "!slabeldef\n", sym->rname);
354         else
355           tfprintf (map->oFile, "!labeldef\n", sym->rname);           
356         tfprintf (map->oFile, "\t!ds\n", 
357                   (unsigned int)  size & 0xffff);
358       }
359     }
360 }
361
362 /*-----------------------------------------------------------------*/
363 /* initPointer - pointer initialization code massaging             */
364 /*-----------------------------------------------------------------*/
365 value *
366 initPointer (initList * ilist, sym_link *toType)
367 {
368         value *val;
369         ast *expr = list2expr (ilist);
370         
371         if (!expr)
372                 goto wrong;
373         
374         /* try it the oldway first */
375         if ((val = constExprValue (expr, FALSE)))
376                 return val;
377         
378         /* ( ptr + constant ) */
379         if (IS_AST_OP (expr) &&
380             (expr->opval.op == '+' || expr->opval.op == '-') &&
381             IS_AST_SYM_VALUE (expr->left) &&
382             (IS_ARRAY(expr->left->ftype) || IS_PTR(expr->left->ftype)) &&
383             compareType(toType, expr->left->ftype) &&
384             IS_AST_LIT_VALUE (expr->right)) {
385           return valForCastAggr (expr->left, expr->left->ftype,
386                                       expr->right,
387                                       expr->opval.op);
388         }
389         
390         /* (char *)&a */
391         if (IS_AST_OP(expr) && expr->opval.op==CAST &&
392             IS_AST_OP(expr->right) && expr->right->opval.op=='&') {
393           if (compareType(toType, expr->left->ftype)!=1) {
394             werror (W_INIT_WRONG);
395             printFromToType(expr->left->ftype, toType);
396           }
397           // skip the cast ???
398           expr=expr->right;
399         }
400
401         /* no then we have to do these cludgy checks */
402         /* pointers can be initialized with address of
403            a variable or address of an array element */
404         if (IS_AST_OP (expr) && expr->opval.op == '&') {
405                 /* address of symbol */
406                 if (IS_AST_SYM_VALUE (expr->left)) {
407                         val = copyValue (AST_VALUE (expr->left));
408                         val->type = newLink (DECLARATOR);
409                         if (SPEC_SCLS (expr->left->etype) == S_CODE) {
410                                 DCL_TYPE (val->type) = CPOINTER;
411                         }
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 (DECLARATOR);
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; 
812        last_type && IS_DECL(last_type) && DCL_ELEM (last_type); 
813        last_type = last_type->next) {
814     lcnt *= DCL_ELEM (last_type);
815   }
816
817   for (;;)
818     {
819       size++;
820       printIval (sym, type->next, iloop, oFile);
821       iloop = (iloop ? iloop->next : NULL);
822
823
824       /* if not array limits given & we */
825       /* are out of initialisers then   */
826       if (!DCL_ELEM (type) && !iloop)
827         break;
828
829       /* no of elements given and we    */
830       /* have generated for all of them */
831       if (!--lcnt) {
832         /* if initializers left */
833         if (iloop) {
834           werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef);
835         }
836         break;
837       }
838     }
839
840   /* if we have not been given a size  */
841   if (!DCL_ELEM (type))
842     DCL_ELEM (type) = size;
843
844   return;
845 }
846
847 /*-----------------------------------------------------------------*/
848 /* printIvalFuncPtr - generate initial value for function pointers */
849 /*-----------------------------------------------------------------*/
850 void 
851 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
852 {
853   value *val;
854   int dLvl = 0;
855
856   val = list2val (ilist);
857
858   if (!val) {
859     // an error has been thrown allready
860     val=constVal("0");
861   }
862
863   if (IS_LITERAL(val->etype)) {
864     if (compareType(type,val->etype)==0) {
865       werror (E_INCOMPAT_TYPES);
866       printFromToType (val->type, type);
867     }
868     printIvalCharPtr (NULL, type, val, oFile);
869     return;
870   }
871
872   /* check the types   */
873   if ((dLvl = compareType (val->type, type->next)) <= 0)
874     {
875       tfprintf (oFile, "\t!dw !constword\n", 0);
876       return;
877     }
878
879   /* now generate the name */
880   if (!val->sym)
881     {
882       if (port->use_dw_for_init)
883         {
884           tfprintf (oFile, "\t!dws\n", val->name);
885         }
886       else
887         {
888           printPointerType (oFile, val->name);
889         }
890     }
891   else if (port->use_dw_for_init)
892     {
893       tfprintf (oFile, "\t!dws\n", val->sym->rname);
894     }
895   else
896     {
897       printPointerType (oFile, val->sym->rname);
898     }
899
900   return;
901 }
902
903 /*-----------------------------------------------------------------*/
904 /* printIvalCharPtr - generates initial values for character pointers */
905 /*-----------------------------------------------------------------*/
906 int 
907 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
908 {
909   int size = 0;
910
911   /* PENDING: this is _very_ mcs51 specific, including a magic
912      number...
913      It's also endin specific.
914    */
915   size = getSize (type);
916
917   if (val->name && strlen (val->name))
918     {
919       if (size == 1)            /* This appears to be Z80 specific?? */
920         {
921           tfprintf (oFile,
922                     "\t!dbs\n", val->name);
923         }
924       else if (size == FPTRSIZE)
925         {
926           if (port->use_dw_for_init)
927             {
928               tfprintf (oFile, "\t!dws\n", val->name);
929             }
930           else
931             {
932               printPointerType (oFile, val->name);
933             }
934         }
935       else if (size == GPTRSIZE)
936         {
937           int type;
938           if (IS_PTR (val->type)) {
939             type = DCL_TYPE (val->type);
940           } else {
941             type = PTR_TYPE (SPEC_OCLS (val->etype));
942           }
943           if (val->sym && val->sym->isstrlit) {
944             // this is a literal string
945             type=CPOINTER;
946           }
947           printGPointerType (oFile, val->name, sym->name, type);
948         }
949       else
950         {
951           fprintf (stderr, "*** internal error: unknown size in "
952                    "printIvalCharPtr.\n");
953         }
954     }
955   else
956     {
957       // these are literals assigned to pointers
958       switch (size)
959         {
960         case 1:
961           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
962           break;
963         case 2:
964           if (port->use_dw_for_init)
965             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
966           else
967             tfprintf (oFile, "\t.byte %s,%s\n",
968                       aopLiteral (val, 0), aopLiteral (val, 1));
969           break;
970         case 3:
971           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
972             // non-zero mcs51 generic pointer
973             werror (E_LITERAL_GENERIC);
974           }
975           fprintf (oFile, "\t.byte %s,%s,%s\n",
976                    aopLiteral (val, 0), 
977                    aopLiteral (val, 1),
978                    aopLiteral (val, 2));
979           break;
980         case 4:
981           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
982             // non-zero ds390 generic pointer
983             werror (E_LITERAL_GENERIC);
984           }
985           fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
986                    aopLiteral (val, 0), 
987                    aopLiteral (val, 1), 
988                    aopLiteral (val, 2),
989                    aopLiteral (val, 3));
990           break;
991         default:
992           assert (0);
993         }
994     }
995
996   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
997     addSet (&statsg->syms, val->sym);
998   }
999
1000   return 1;
1001 }
1002
1003 /*-----------------------------------------------------------------*/
1004 /* printIvalPtr - generates initial value for pointers             */
1005 /*-----------------------------------------------------------------*/
1006 void 
1007 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1008 {
1009   value *val;
1010   int size;
1011
1012   /* if deep then   */
1013   if (ilist->type == INIT_DEEP)
1014     ilist = ilist->init.deep;
1015
1016   /* function pointer     */
1017   if (IS_FUNC (type->next))
1018     {
1019       printIvalFuncPtr (type, ilist, oFile);
1020       return;
1021     }
1022
1023   if (!(val = initPointer (ilist, type)))
1024     return;
1025
1026   /* if character pointer */
1027   if (IS_CHAR (type->next))
1028     if (printIvalCharPtr (sym, type, val, oFile))
1029       return;
1030
1031   /* check the type      */
1032   if (compareType (type, val->type) == 0) {
1033     werror (W_INIT_WRONG);
1034     printFromToType (val->type, type);
1035   }
1036
1037   /* if val is literal */
1038   if (IS_LITERAL (val->etype))
1039     {
1040       switch (getSize (type))
1041         {
1042         case 1:
1043           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
1044           break;
1045         case 2:
1046           if (port->use_dw_for_init)
1047             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
1048           else
1049             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1050           break;
1051         case 3: // how about '390??
1052           fprintf (oFile, "\t.byte %s,%s,#0x%d\n",
1053                    aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE);
1054         }
1055       return;
1056     }
1057
1058
1059   size = getSize (type);
1060
1061   if (size == 1)                /* Z80 specific?? */
1062     {
1063       tfprintf (oFile, "\t!dbs\n", val->name);
1064     }
1065   else if (size == FPTRSIZE)
1066     {
1067       if (port->use_dw_for_init) {
1068         tfprintf (oFile, "\t!dws\n", val->name);
1069       } else {
1070         printPointerType (oFile, val->name);
1071       }
1072     }
1073   else if (size == GPTRSIZE)
1074     {
1075       printGPointerType (oFile, val->name, sym->name,
1076                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1077                           PTR_TYPE (SPEC_OCLS (val->etype))));
1078     }
1079   return;
1080 }
1081
1082 /*-----------------------------------------------------------------*/
1083 /* printIval - generates code for initial value                    */
1084 /*-----------------------------------------------------------------*/
1085 void 
1086 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1087 {
1088   if (!ilist)
1089     return;
1090
1091   /* update line number for error msgs */
1092   lineno=sym->lineDef;
1093
1094   /* if structure then    */
1095   if (IS_STRUCT (type))
1096     {
1097       printIvalStruct (sym, type, ilist, oFile);
1098       return;
1099     }
1100
1101   /* if this is a pointer */
1102   if (IS_PTR (type))
1103     {
1104       printIvalPtr (sym, type, ilist, oFile);
1105       return;
1106     }
1107
1108   /* if this is an array   */
1109   if (IS_ARRAY (type))
1110     {
1111       printIvalArray (sym, type, ilist, oFile);
1112       return;
1113     }
1114
1115   /* if type is SPECIFIER */
1116   if (IS_SPEC (type))
1117     {
1118       printIvalType (sym, type, ilist, oFile);
1119       return;
1120     }
1121 }
1122
1123 /*-----------------------------------------------------------------*/
1124 /* emitStaticSeg - emitcode for the static segment                 */
1125 /*-----------------------------------------------------------------*/
1126 void 
1127 emitStaticSeg (memmap * map, FILE * out)
1128 {
1129   symbol *sym;
1130
1131   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1132
1133   /* for all variables in this segment do */
1134   for (sym = setFirstItem (map->syms); sym;
1135        sym = setNextItem (map->syms))
1136     {
1137
1138       /* if it is "extern" then do nothing */
1139       if (IS_EXTERN (sym->etype))
1140         continue;
1141
1142       /* if it is not static add it to the public
1143          table */
1144       if (!IS_STATIC (sym->etype))
1145         {
1146           addSetHead (&publics, sym);
1147         }
1148
1149       /* print extra debug info if required */
1150       if (options.debug) {
1151         cdbSymbol (sym, cdbFile, FALSE, FALSE);
1152         if (!sym->level)
1153           {                     /* global */
1154             if (IS_STATIC (sym->etype))
1155               fprintf (out, "F%s$", moduleName);        /* scope is file */
1156             else
1157               fprintf (out, "G$");      /* scope is global */
1158           }
1159         else
1160           /* symbol is local */
1161           fprintf (out, "L%s$",
1162                    (sym->localof ? sym->localof->name : "-null-"));
1163         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1164       }
1165       
1166       /* if it has an absolute address */
1167       if (SPEC_ABSA (sym->etype))
1168         {
1169           if (options.debug)
1170             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1171           
1172           fprintf (out, "%s\t=\t0x%04x\n",
1173                    sym->rname,
1174                    SPEC_ADDR (sym->etype));
1175         }
1176       else
1177         {
1178           if (options.debug)
1179             fprintf (out, " == .\n");
1180           
1181           /* if it has an initial value */
1182           if (sym->ival)
1183             {
1184               fprintf (out, "%s:\n", sym->rname);
1185               noAlloc++;
1186               resolveIvalSym (sym->ival);
1187               printIval (sym, sym->type, sym->ival, out);
1188               noAlloc--;
1189               /* if sym is a simple string and sym->ival is a string, 
1190                  WE don't need it anymore */
1191               if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) &&
1192                   IS_AST_SYM_VALUE(list2expr(sym->ival)) &&
1193                   list2val(sym->ival)->sym->isstrlit) {
1194                 freeStringSymbol(list2val(sym->ival)->sym);
1195               }
1196             }
1197           else {
1198               /* allocate space */
1199               int size = getSize (sym->type);
1200               
1201               if (size==0) {
1202                   werror(E_UNKNOWN_SIZE,sym->name);
1203               }
1204               fprintf (out, "%s:\n", sym->rname);
1205               /* special case for character strings */
1206               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1207                   SPEC_CVAL (sym->etype).v_char)
1208                   printChar (out,
1209                              SPEC_CVAL (sym->etype).v_char,
1210                              strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1211               else
1212                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1213             }
1214         }
1215     }
1216 }
1217
1218 /*-----------------------------------------------------------------*/
1219 /* emitMaps - emits the code for the data portion the code         */
1220 /*-----------------------------------------------------------------*/
1221 void 
1222 emitMaps (void)
1223 {
1224   inInitMode++;
1225   /* no special considerations for the following
1226      data, idata & bit & xdata */
1227   emitRegularMap (data, TRUE, TRUE);
1228   emitRegularMap (idata, TRUE, TRUE);
1229   emitRegularMap (bit, TRUE, FALSE);
1230   emitRegularMap (xdata, TRUE, TRUE);
1231   if (port->genXINIT) {
1232     emitRegularMap (xidata, TRUE, TRUE);
1233   }
1234   emitRegularMap (sfr, FALSE, FALSE);
1235   emitRegularMap (sfrbit, FALSE, FALSE);
1236   emitRegularMap (home, TRUE, FALSE);
1237   emitRegularMap (code, TRUE, FALSE);
1238
1239   emitStaticSeg (statsg, code->oFile);
1240   if (port->genXINIT) {
1241     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1242     emitStaticSeg (xinit, code->oFile);
1243   }
1244   inInitMode--;
1245 }
1246
1247 /*-----------------------------------------------------------------*/
1248 /* flushStatics - flush all currently defined statics out to file  */
1249 /*  and delete.  Temporary function                                */
1250 /*-----------------------------------------------------------------*/
1251 void 
1252 flushStatics (void)
1253 {
1254   emitStaticSeg (statsg, codeOutFile);
1255   statsg->syms = NULL;
1256 }
1257
1258 /*-----------------------------------------------------------------*/
1259 /* createInterruptVect - creates the interrupt vector              */
1260 /*-----------------------------------------------------------------*/
1261 void 
1262 createInterruptVect (FILE * vFile)
1263 {
1264   unsigned i = 0;
1265   mainf = newSymbol ("main", 0);
1266   mainf->block = 0;
1267
1268   /* only if the main function exists */
1269   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1270     {
1271       if (!options.cc_only && !noAssemble && !options.c1mode)
1272         werror (E_NO_MAIN);
1273       return;
1274     }
1275
1276   /* if the main is only a prototype ie. no body then do nothing */
1277   if (!IFFUNC_HASBODY(mainf->type))
1278     {
1279       /* if ! compile only then main function should be present */
1280       if (!options.cc_only && !noAssemble)
1281         werror (E_NO_MAIN);
1282       return;
1283     }
1284
1285   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1286   fprintf (vFile, "__interrupt_vect:\n");
1287
1288
1289   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1290     {
1291       /* "generic" interrupt table header (if port doesn't specify one).
1292        * Look suspiciously like 8051 code to me...
1293        */
1294
1295       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1296
1297
1298       /* now for the other interrupts */
1299       for (; i < maxInterrupts; i++)
1300         {
1301           if (interrupts[i])
1302             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1303           else
1304             fprintf (vFile, "\treti\n\t.ds\t7\n");
1305         }
1306     }
1307 }
1308
1309 char *iComments1 =
1310 {
1311   ";--------------------------------------------------------\n"
1312   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1313
1314 char *iComments2 =
1315 {
1316   ";--------------------------------------------------------\n"};
1317
1318
1319 /*-----------------------------------------------------------------*/
1320 /* initialComments - puts in some initial comments                 */
1321 /*-----------------------------------------------------------------*/
1322 void 
1323 initialComments (FILE * afile)
1324 {
1325   time_t t;
1326   time (&t);
1327   fprintf (afile, "%s", iComments1);
1328   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1329   fprintf (afile, "%s", iComments2);
1330 }
1331
1332 /*-----------------------------------------------------------------*/
1333 /* printPublics - generates .global for publics                    */
1334 /*-----------------------------------------------------------------*/
1335 void 
1336 printPublics (FILE * afile)
1337 {
1338   symbol *sym;
1339
1340   fprintf (afile, "%s", iComments2);
1341   fprintf (afile, "; Public variables in this module\n");
1342   fprintf (afile, "%s", iComments2);
1343
1344   for (sym = setFirstItem (publics); sym;
1345        sym = setNextItem (publics))
1346     tfprintf (afile, "\t!global\n", sym->rname);
1347 }
1348
1349 /*-----------------------------------------------------------------*/
1350 /* printExterns - generates .global for externs                    */
1351 /*-----------------------------------------------------------------*/
1352 void 
1353 printExterns (FILE * afile)
1354 {
1355   symbol *sym;
1356
1357   fprintf (afile, "%s", iComments2);
1358   fprintf (afile, "; Externals used\n");
1359   fprintf (afile, "%s", iComments2);
1360
1361   for (sym = setFirstItem (externs); sym;
1362        sym = setNextItem (externs))
1363     tfprintf (afile, "\t!extern\n", sym->rname);
1364 }
1365
1366 /*-----------------------------------------------------------------*/
1367 /* emitOverlay - will emit code for the overlay stuff              */
1368 /*-----------------------------------------------------------------*/
1369 static void 
1370 emitOverlay (FILE * afile)
1371 {
1372   set *ovrset;
1373
1374   if (!elementsInSet (ovrSetSets))
1375     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1376
1377   /* for each of the sets in the overlay segment do */
1378   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1379        ovrset = setNextItem (ovrSetSets))
1380     {
1381
1382       symbol *sym;
1383
1384       if (elementsInSet (ovrset))
1385         {
1386           /* output the area informtion */
1387           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1388         }
1389
1390       for (sym = setFirstItem (ovrset); sym;
1391            sym = setNextItem (ovrset))
1392         {
1393           /* if extern then it is in the publics table: do nothing */
1394           if (IS_EXTERN (sym->etype))
1395             continue;
1396
1397           /* if allocation required check is needed
1398              then check if the symbol really requires
1399              allocation only for local variables */
1400           if (!IS_AGGREGATE (sym->type) &&
1401               !(sym->_isparm && !IS_REGPARM (sym->etype))
1402               && !sym->allocreq && sym->level)
1403             continue;
1404
1405           /* if global variable & not static or extern
1406              and addPublics allowed then add it to the public set */
1407           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1408               && !IS_STATIC (sym->etype))
1409             {
1410               addSetHead (&publics, sym);
1411             }
1412
1413           /* if extern then do nothing or is a function
1414              then do nothing */
1415           if (IS_FUNC (sym->type))
1416             continue;
1417
1418           /* print extra debug info if required */
1419           if (options.debug)
1420             {
1421               cdbSymbol (sym, cdbFile, FALSE, FALSE);
1422
1423               if (!sym->level)
1424                 {               /* global */
1425                   if (IS_STATIC (sym->etype))
1426                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1427                   else
1428                     fprintf (afile, "G$");      /* scope is global */
1429                 }
1430               else
1431                 /* symbol is local */
1432                 fprintf (afile, "L%s$",
1433                          (sym->localof ? sym->localof->name : "-null-"));
1434               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1435             }
1436
1437           /* if is has an absolute address then generate
1438              an equate for this no need to allocate space */
1439           if (SPEC_ABSA (sym->etype))
1440             {
1441
1442               if (options.debug)
1443                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1444
1445               fprintf (afile, "%s\t=\t0x%04x\n",
1446                        sym->rname,
1447                        SPEC_ADDR (sym->etype));
1448             }
1449           else {
1450               int size = getSize(sym->type);
1451
1452               if (size==0) {
1453                   werror(E_UNKNOWN_SIZE,sym->name);
1454               }       
1455               if (options.debug)
1456                   fprintf (afile, "==.\n");
1457               
1458               /* allocate space */
1459               tfprintf (afile, "!labeldef\n", sym->rname);
1460               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1461           }
1462           
1463         }
1464     }
1465 }
1466
1467 /*-----------------------------------------------------------------*/
1468 /* glue - the final glue that hold the whole thing together        */
1469 /*-----------------------------------------------------------------*/
1470 void 
1471 glue (void)
1472 {
1473   FILE *vFile;
1474   FILE *asmFile;
1475   FILE *ovrFile = tempfile ();
1476
1477   addSetHead (&tmpfileSet, ovrFile);
1478   /* print the global struct definitions */
1479   if (options.debug)
1480     cdbStructBlock (0, cdbFile);
1481
1482   vFile = tempfile ();
1483   /* PENDING: this isnt the best place but it will do */
1484   if (port->general.glue_up_main)
1485     {
1486       /* create the interrupt vector table */
1487       createInterruptVect (vFile);
1488     }
1489
1490   addSetHead (&tmpfileSet, vFile);
1491
1492   /* emit code for the all the variables declared */
1493   emitMaps ();
1494   /* do the overlay segments */
1495   emitOverlay (ovrFile);
1496
1497   /* now put it all together into the assembler file */
1498   /* create the assembler file name */
1499
1500   /* -o option overrides default name? */
1501   if ((noAssemble || options.c1mode) && fullDstFileName)
1502     {
1503       strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1504     }
1505   else
1506     {
1507       strncpyz (scratchFileName, dstFileName, PATH_MAX);
1508       strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1509     }
1510
1511   if (!(asmFile = fopen (scratchFileName, "w")))
1512     {
1513       werror (E_FILE_OPEN_ERR, scratchFileName);
1514       exit (1);
1515     }
1516
1517   /* initial comments */
1518   initialComments (asmFile);
1519
1520   /* print module name */
1521   tfprintf (asmFile, "\t!module\n", moduleName);
1522   tfprintf (asmFile, "\t!fileprelude\n");
1523
1524   /* Let the port generate any global directives, etc. */
1525   if (port->genAssemblerPreamble)
1526     {
1527       port->genAssemblerPreamble (asmFile);
1528     }
1529
1530   /* print the global variables in this module */
1531   printPublics (asmFile);
1532   if (port->assembler.externGlobal)
1533     printExterns (asmFile);
1534
1535   /* copy the sfr segment */
1536   fprintf (asmFile, "%s", iComments2);
1537   fprintf (asmFile, "; special function registers\n");
1538   fprintf (asmFile, "%s", iComments2);
1539   copyFile (asmFile, sfr->oFile);
1540
1541   /* copy the sbit segment */
1542   fprintf (asmFile, "%s", iComments2);
1543   fprintf (asmFile, "; special function bits \n");
1544   fprintf (asmFile, "%s", iComments2);
1545   copyFile (asmFile, sfrbit->oFile);
1546   
1547   /*JCF: Create the areas for the register banks*/
1548   if(port->general.glue_up_main &&
1549      (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51))
1550   {
1551           if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1552           {
1553                  fprintf (asmFile, "%s", iComments2);
1554                  fprintf (asmFile, "; overlayable register banks \n");
1555                  fprintf (asmFile, "%s", iComments2);
1556                  if(RegBankUsed[0])
1557                         fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1558                  if(RegBankUsed[1]||options.parms_in_bank1)
1559                         fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1560                  if(RegBankUsed[2])
1561                         fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1562                  if(RegBankUsed[3])
1563                         fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1564           }
1565   }
1566
1567   /* copy the data segment */
1568   fprintf (asmFile, "%s", iComments2);
1569   fprintf (asmFile, "; internal ram data\n");
1570   fprintf (asmFile, "%s", iComments2);
1571   copyFile (asmFile, data->oFile);
1572
1573
1574   /* create the overlay segments */
1575   if (overlay) {
1576     fprintf (asmFile, "%s", iComments2);
1577     fprintf (asmFile, "; overlayable items in internal ram \n");
1578     fprintf (asmFile, "%s", iComments2);
1579     copyFile (asmFile, ovrFile);
1580   }
1581
1582   /* create the stack segment MOF */
1583   if (mainf && IFFUNC_HASBODY(mainf->type))
1584     {
1585       fprintf (asmFile, "%s", iComments2);
1586       fprintf (asmFile, "; Stack segment in internal ram \n");
1587       fprintf (asmFile, "%s", iComments2);
1588       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1589                "__start__stack:\n\t.ds\t1\n\n");
1590     }
1591
1592   /* create the idata segment */
1593   if (idata) {
1594     fprintf (asmFile, "%s", iComments2);
1595     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1596     fprintf (asmFile, "%s", iComments2);
1597     copyFile (asmFile, idata->oFile);
1598   }
1599
1600   /* copy the bit segment */
1601   fprintf (asmFile, "%s", iComments2);
1602   fprintf (asmFile, "; bit data\n");
1603   fprintf (asmFile, "%s", iComments2);
1604   copyFile (asmFile, bit->oFile);
1605
1606   /* if external stack then reserve space of it */
1607   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1608     {
1609       fprintf (asmFile, "%s", iComments2);
1610       fprintf (asmFile, "; external stack \n");
1611       fprintf (asmFile, "%s", iComments2);
1612       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1613       fprintf (asmFile, "\t.ds 256\n");
1614     }
1615
1616
1617   /* copy xtern ram data */
1618   fprintf (asmFile, "%s", iComments2);
1619   fprintf (asmFile, "; external ram data\n");
1620   fprintf (asmFile, "%s", iComments2);
1621   copyFile (asmFile, xdata->oFile);
1622
1623   /* copy xternal initialized ram data */
1624   fprintf (asmFile, "%s", iComments2);
1625   fprintf (asmFile, "; external initialized ram data\n");
1626   fprintf (asmFile, "%s", iComments2);
1627   copyFile (asmFile, xidata->oFile);
1628
1629   /* copy the interrupt vector table */
1630   if (mainf && IFFUNC_HASBODY(mainf->type))
1631     {
1632       fprintf (asmFile, "%s", iComments2);
1633       fprintf (asmFile, "; interrupt vector \n");
1634       fprintf (asmFile, "%s", iComments2);
1635       copyFile (asmFile, vFile);
1636     }
1637
1638   /* copy global & static initialisations */
1639   fprintf (asmFile, "%s", iComments2);
1640   fprintf (asmFile, "; global & static initialisations\n");
1641   fprintf (asmFile, "%s", iComments2);
1642
1643   /* Everywhere we generate a reference to the static_name area,
1644    * (which is currently only here), we immediately follow it with a
1645    * definition of the post_static_name area. This guarantees that
1646    * the post_static_name area will immediately follow the static_name
1647    * area.
1648    */
1649   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1650   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1651   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1652
1653   if (mainf && IFFUNC_HASBODY(mainf->type))
1654     {
1655       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1656       /* if external stack is specified then the
1657          higher order byte of the xdatalocation is
1658          going into P2 and the lower order going into
1659          spx */
1660       if (options.useXstack)
1661         {
1662           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1663                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1664           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1665                    (unsigned int) options.xdata_loc & 0xff);
1666         }
1667
1668       /* initialise the stack pointer.  JCF: aslink takes care of the location */
1669         fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");   /* MOF */
1670
1671       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1672       fprintf (asmFile, "\tmov\ta,dpl\n");
1673       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1674       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1675       fprintf (asmFile, "__sdcc_init_data:\n");
1676
1677       // if the port can copy the XINIT segment to XISEG
1678       if (port->genXINIT) {
1679         port->genXINIT(asmFile);
1680       }
1681
1682     }
1683   copyFile (asmFile, statsg->oFile);
1684
1685   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1686     {
1687       /* This code is generated in the post-static area.
1688        * This area is guaranteed to follow the static area
1689        * by the ugly shucking and jiving about 20 lines ago.
1690        */
1691       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1692       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1693     }
1694
1695   fprintf (asmFile,
1696            "%s"
1697            "; Home\n"
1698            "%s", iComments2, iComments2);
1699   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1700   copyFile (asmFile, home->oFile);
1701
1702   /* copy over code */
1703   fprintf (asmFile, "%s", iComments2);
1704   fprintf (asmFile, "; code\n");
1705   fprintf (asmFile, "%s", iComments2);
1706   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1707   if (mainf && IFFUNC_HASBODY(mainf->type))
1708     {
1709
1710       /* entry point @ start of CSEG */
1711       fprintf (asmFile, "__sdcc_program_startup:\n");
1712
1713       /* put in the call to main */
1714       fprintf (asmFile, "\tlcall\t_main\n");
1715       if (options.mainreturn)
1716         {
1717
1718           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1719           fprintf (asmFile, "\tret\n");
1720
1721         }
1722       else
1723         {
1724
1725           fprintf (asmFile, ";\treturn from main will lock up\n");
1726           fprintf (asmFile, "\tsjmp .\n");
1727         }
1728     }
1729   copyFile (asmFile, code->oFile);
1730
1731   if (port->genAssemblerEnd) {
1732       port->genAssemblerEnd(asmFile);
1733   }
1734   fclose (asmFile);
1735
1736   rm_tmpfiles ();
1737 }
1738
1739
1740 /** Creates a temporary file with unoque file name
1741     Scans, in order:
1742     - TMP, TEMP, TMPDIR env. varibles
1743     - if Un*x system: /usr/tmp and /tmp
1744     - root directory using mkstemp() if avaliable
1745     - default location using tempnam()
1746 */
1747 static int
1748 tempfileandname(char *fname, size_t len)
1749 {
1750 #define TEMPLATE      "sdccXXXXXX"
1751 #define TEMPLATE_LEN  ((sizeof TEMPLATE) - 1)
1752
1753   const char *tmpdir = NULL;
1754   int fd;
1755
1756   if ((tmpdir = getenv ("TMP")) == NULL)
1757     if ((tmpdir = getenv ("TEMP")) == NULL)
1758       tmpdir = getenv ("TMPDIR");
1759
1760 #ifndef _WIN32
1761   {
1762     /* try with /usr/tmp and /tmp on Un*x systems */
1763     struct stat statbuf;
1764
1765     if (tmpdir == NULL) {
1766       if (stat("/usr/tmp", &statbuf) != -1)
1767         tmpdir = "/usr/tmp";
1768       else if (stat("/tmp", &statbuf) != -1)
1769         tmpdir = "/tmp";
1770     }
1771   }
1772 #endif
1773
1774 #ifdef HAVE_MKSTEMP
1775   {
1776     char fnamebuf[PATH_MAX];
1777     size_t name_len;
1778
1779     if (fname == NULL || len == 0) {
1780       fname = fnamebuf;
1781       len = sizeof fnamebuf;
1782     }
1783
1784     if (tmpdir) {
1785       name_len = strlen(tmpdir) + 1 + TEMPLATE_LEN;
1786
1787       assert(name_len < len);
1788       if (!(name_len < len))  /* in NDEBUG is defined */
1789         return -1;            /* buffer too small, temporary file can not be created */
1790
1791       sprintf(fname, "%s" DIR_SEPARATOR_STRING TEMPLATE, tmpdir);
1792     }
1793     else {
1794       name_len = TEMPLATE_LEN;
1795
1796       assert(name_len < len);
1797       if (!(name_len < len))  /* in NDEBUG is defined */
1798         return -1;            /* buffer too small, temporary file can not be created */
1799
1800       strcpy(fname, TEMPLATE);
1801     }
1802
1803     fd = mkstemp(fname);
1804   }
1805 #else
1806   {
1807     char *name = tempnam(tmpdir, "sdcc");
1808
1809     if (name == NULL) {
1810       perror("Can't create temporary file name");
1811       exit(1);
1812     }
1813
1814     assert(strlen(name) < len);
1815     if (!(strlen(name) < len))  /* in NDEBUG is defined */
1816       return -1;                /* buffer too small, temporary file can not be created */
1817
1818     strcpy(fname, name);
1819 #ifdef _WIN32
1820     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IREAD | S_IWRITE);
1821 #else
1822     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IRUSR | S_IWUSR);
1823 #endif
1824   }
1825 #endif
1826
1827   if (fd == -1) {
1828     perror("Can't create temporary file");
1829     exit(1);
1830   }
1831
1832   return fd;
1833 }
1834
1835
1836 /** Create a temporary file name
1837 */
1838 char *
1839 tempfilename(void)
1840 {
1841   int fd;
1842   static char fnamebuf[PATH_MAX];
1843
1844   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1845     fprintf(stderr, "Can't create temporary file name!");
1846     exit(1);
1847   }
1848
1849   fd = close(fd);
1850   assert(fd != -1);
1851
1852   return fnamebuf;
1853 }
1854
1855
1856 /** Create a temporary file and add it to tmpfileNameSet,
1857     so that it is removed explicitly by rm_tmpfiles()
1858     or implicitly at program extit.
1859 */
1860 FILE *
1861 tempfile(void)
1862 {
1863   int fd;
1864   char *tmp;
1865   FILE *fp;
1866   char fnamebuf[PATH_MAX];
1867
1868   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1869     fprintf(stderr, "Can't create temporary file!");
1870     exit(1);
1871   }
1872
1873   tmp = Safe_strdup(fnamebuf);
1874   if (tmp)
1875     addSetHead(&tmpfileNameSet, tmp);
1876
1877   if ((fp = fdopen(fd, "w+b")) == NULL) {
1878       perror("Can't create temporary file!");
1879       exit(1);
1880   }
1881
1882   return fp;
1883 }