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