Fixed some more intialization things
[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
29 symbol *interrupts[256];
30 /*extern char *aopLiteral (value *, int);*//* drdani Jan 30 2000 */
31 void printIval (symbol *, link *, initList *, FILE *);
32 extern int noAlloc;
33 set *publics = NULL;            /* public variables */
34 set *externs = NULL;            /* Varibles that are declared as extern */
35
36 /* TODO: this should be configurable (DS803C90 uses more than 6) */
37 int maxInterrupts = 6;
38 extern int maxRegBank ;
39 symbol *mainf;
40 extern char *VersionString;
41 extern FILE *codeOutFile;
42 set *tmpfileSet = NULL; /* set of tmp file created by the compiler */
43 set *tmpfileNameSet = NULL; /* All are unlinked at close. */
44 /*-----------------------------------------------------------------*/
45 /* closeTmpFiles - closes all tmp files created by the compiler    */
46 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
47 /*-----------------------------------------------------------------*/
48 DEFSETFUNC(closeTmpFiles)
49 {
50     FILE *tfile = item;
51
52     if (tfile)
53         fclose(tfile);
54     
55     return 0;
56 }
57
58 /*-----------------------------------------------------------------*/
59 /* rmTmpFiles - closes all tmp files created by the compiler    */
60 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
61 /*-----------------------------------------------------------------*/
62 DEFSETFUNC(rmTmpFiles)
63 {
64     char *name = item;
65
66     if (name) {
67         unlink(name);
68         free(name);
69     }
70     return 0;
71 }
72
73 /*-----------------------------------------------------------------*/
74 /* copyFile - copies source file to destination file               */
75 /*-----------------------------------------------------------------*/
76 void copyFile (FILE * dest, FILE * src)
77 {
78     int ch;
79     
80     rewind (src);
81     while (!feof (src))
82         if ((ch = fgetc (src)) != EOF)
83             fputc (ch, dest);
84 }
85
86 char *aopLiteralLong(value *val, int offset, int size)
87 {
88     char *rs;
89     union {
90         float f;
91         unsigned char c[4];
92     } fl;
93
94     /* if it is a float then it gets tricky */
95     /* otherwise it is fairly simple */
96     if (!IS_FLOAT(val->type)) {
97         unsigned long v = floatFromVal(val);
98
99         v >>= (offset * 8);
100         switch (size) {
101         case 1:
102             tsprintf(buffer, "!immedbyte", (unsigned int)v & 0xff);
103             break;
104         case 2:
105             tsprintf(buffer, "!immedword", (unsigned int)v & 0xffff);
106             break;
107         default:
108             /* Hmm.  Too big for now. */
109             assert(0);
110         }
111         ALLOC_ATOMIC(rs,strlen(buffer)+1);
112         return strcpy (rs,buffer);
113     }
114
115     /* PENDING: For now size must be 1 */
116     assert(size == 1);
117
118     /* it is type float */
119     fl.f = (float) floatFromVal(val);
120 #ifdef _BIG_ENDIAN
121     tsprintf(buffer, "!immedbyte", fl.c[3-offset]);
122 #else
123     tsprintf(buffer, "!immedbyte", fl.c[offset]);
124 #endif
125     ALLOC_ATOMIC(rs,strlen(buffer)+1);
126     return strcpy (rs,buffer);
127 }
128
129 /*-----------------------------------------------------------------*/
130 /* aopLiteral - string from a literal value                        */
131 /*-----------------------------------------------------------------*/
132 char *aopLiteral (value *val, int offset)
133 {
134     return aopLiteralLong(val, offset, 1);
135 }
136
137 /*-----------------------------------------------------------------*/
138 /* emitRegularMap - emit code for maps with no special cases       */
139 /*-----------------------------------------------------------------*/
140 static void emitRegularMap (memmap * map, bool addPublics, bool arFlag)
141 {
142     symbol *sym;
143     
144     if (addPublics) {
145         /* PENDING: special case here - should remove */
146         if (!strcmp(map->sname, DATA_NAME))
147             tfprintf(map->oFile, "\t!areadata\n", map->sname);
148         else
149             tfprintf(map->oFile, "\t!area\n", map->sname);
150     }
151     
152     /* print the area name */
153     for (sym = setFirstItem (map->syms); sym;
154          sym = setNextItem (map->syms))  {
155         
156         /* if extern then add it into the extern list */
157         if (IS_EXTERN (sym->etype)) {
158             addSetHead (&externs, sym);
159             continue;
160         }
161         
162         /* if allocation required check is needed
163            then check if the symbol really requires
164            allocation only for local variables */
165         if (arFlag && !IS_AGGREGATE(sym->type) &&
166             !(sym->_isparm && !IS_REGPARM(sym->etype)) && 
167               !sym->allocreq && sym->level)
168             continue ;
169         
170         /* if global variable & not static or extern 
171            and addPublics allowed then add it to the public set */
172         if ((sym->level == 0 || 
173              (sym->_isparm && !IS_REGPARM(sym->etype))) &&
174             addPublics &&
175             !IS_STATIC (sym->etype))
176             addSetHead (&publics, sym);
177         
178         /* if extern then do nothing or is a function 
179            then do nothing */
180         if (IS_FUNC (sym->type))
181             continue;
182         
183         /* print extra debug info if required */
184         if ((options.debug || sym->level == 0) && !options.nodebug) {
185
186             cdbSymbol(sym,cdbFile,FALSE,FALSE);
187
188             if (!sym->level) /* global */
189                 if (IS_STATIC(sym->etype))
190                     fprintf(map->oFile,"F%s$",moduleName); /* scope is file */
191                 else
192                     fprintf(map->oFile,"G$"); /* scope is global */
193             else
194                 /* symbol is local */
195                 fprintf(map->oFile,"L%s$",(sym->localof ? sym->localof->name : "-null-"));
196             fprintf(map->oFile,"%s$%d$%d",sym->name,sym->level,sym->block);
197         }
198
199         /* if is has an absolute address then generate
200            an equate for this no need to allocate space */
201         if (SPEC_ABSA (sym->etype)) {
202             if ((options.debug || sym->level == 0) && !options.nodebug)
203                 fprintf (map->oFile," == 0x%04x\n",SPEC_ADDR (sym->etype));         
204
205             fprintf (map->oFile, "%s\t=\t0x%04x\n",
206                      sym->rname,
207                      SPEC_ADDR (sym->etype));
208         }
209         else {
210             /* allocate space */
211             if ((options.debug || sym->level == 0) && !options.nodebug)
212                 fprintf(map->oFile,"==.\n");
213             if (IS_STATIC(sym->etype))
214                 tfprintf(map->oFile, "!slabeldef\n", sym->rname);
215             else
216                 tfprintf(map->oFile, "!labeldef\n", sym->rname);
217             tfprintf(map->oFile, "\t!ds\n", (unsigned int)getSize (sym->type) & 0xffff);
218         }
219         
220         /* if it has a initial value then do it only if
221            it is a global variable */
222         if (sym->ival && sym->level == 0) {
223             ast *ival = NULL;
224             
225             if (IS_AGGREGATE (sym->type))
226                 ival = initAggregates (sym, sym->ival, NULL);
227             else
228                 ival = newNode ('=', newAst (EX_VALUE, symbolVal (sym)),
229                                 decorateType (resolveSymbols (list2expr (sym->ival))));
230             codeOutFile = statsg->oFile;
231             eBBlockFromiCode (iCodeFromAst (ival));
232             sym->ival = NULL;
233         }
234     }
235 }
236
237
238 /*-----------------------------------------------------------------*/
239 /* initPointer - pointer initialization code massaging             */
240 /*-----------------------------------------------------------------*/
241 value *initPointer (initList *ilist)
242 {
243     value *val;
244     ast *expr = list2expr(ilist);
245
246     if (!expr) 
247         goto wrong;             
248         
249     /* try it the oldway first */
250     if ((val = constExprValue(expr,FALSE)))
251         return val;
252
253     /* no then we have to do these cludgy checks */
254     /* pointers can be initialized with address of
255        a variable or address of an array element */
256     if (IS_AST_OP(expr) && expr->opval.op == '&') {
257         /* address of symbol */
258         if (IS_AST_SYM_VALUE(expr->left)) {
259             val = copyValue(AST_VALUE(expr->left));
260             val->type = newLink();
261             if (SPEC_SCLS(expr->left->etype) == S_CODE) {
262                 DCL_TYPE(val->type) = CPOINTER ;
263                 DCL_PTR_CONST(val->type) = port->mem.code_ro;
264             }
265             else
266                 if (SPEC_SCLS(expr->left->etype) == S_XDATA)
267                     DCL_TYPE(val->type) = FPOINTER;
268                 else
269                     if (SPEC_SCLS(expr->left->etype) == S_XSTACK )
270                         DCL_TYPE(val->type) = PPOINTER ;
271                     else
272                         if (SPEC_SCLS(expr->left->etype) == S_IDATA)
273                             DCL_TYPE(val->type) = IPOINTER ;
274                         else
275                             if (SPEC_SCLS(expr->left->etype) == S_EEPROM)
276                                 DCL_TYPE(val->type) = EEPPOINTER ;
277                             else
278                                 DCL_TYPE(val->type) = POINTER ;
279             val->type->next = expr->left->ftype;
280             val->etype = getSpec(val->type);
281             return val;
282         }
283
284         /* if address of indexed array */
285         if (IS_AST_OP(expr->left) && expr->left->opval.op == '[')
286             return valForArray(expr->left);     
287
288         /* if address of structure element then 
289            case 1. a.b ; */
290         if (IS_AST_OP(expr->left) && 
291             expr->left->opval.op == '.' ) {
292                 return valForStructElem(expr->left->left,
293                                         expr->left->right);
294         }
295
296         /* case 2. (&a)->b ; 
297            (&some_struct)->element */
298         if (IS_AST_OP(expr->left) &&
299             expr->left->opval.op == PTR_OP &&
300             IS_ADDRESS_OF_OP(expr->left->left))
301                 return valForStructElem(expr->left->left->left,
302                                         expr->left->right);
303
304     }
305     /* case 3. (((char *) &a) +/- constant) */
306     if (IS_AST_OP(expr) && 
307         (expr->opval.op == '+' || expr->opval.op == '-') &&
308         IS_AST_OP(expr->left) && expr->left->opval.op == CAST &&
309         IS_AST_OP(expr->left->right) && 
310         expr->left->right->opval.op == '&' &&
311         IS_AST_LIT_VALUE(expr->right)) {
312         
313         return valForCastAggr(expr->left->right->left,
314                               expr->left->left->opval.lnk,
315                               expr->right,expr->opval.op);
316         
317     }
318
319  wrong:    
320     werror(E_INIT_WRONG);
321     return NULL;
322     
323 }
324
325 /*-----------------------------------------------------------------*/
326 /* printChar - formats and prints a characater string with DB      */
327 /*-----------------------------------------------------------------*/
328 void printChar (FILE * ofile, char *s, int plen)
329 {
330     int i;
331     int len = strlen (s);
332     int pplen = 0;
333     char buf[100];
334     char *p = buf;
335
336     while (len && pplen < plen) {
337         i = 60;
338         while (i && *s && pplen < plen) {
339             if (*s < ' ' || *s == '\"') {
340                 *p = '\0';
341                 if (p != buf) 
342                     tfprintf(ofile, "\t!ascii\n", buf);
343                 tfprintf(ofile, "\t!db\n", *s);
344                 p = buf;
345             }
346             else {
347                 *p = *s;
348                 p++;
349             }
350             s++;
351             pplen++;
352             i--;
353         }
354         if (p != buf) {
355             *p = '\0';
356             tfprintf(ofile, "\t!ascii\n", buf);
357         }
358         
359         if (len > 60)
360             len -= 60;
361         else
362             len = 0;
363     }
364     tfprintf(ofile, "\t!db\n", 0);
365 }
366
367 /*-----------------------------------------------------------------*/
368 /* printIvalType - generates ival for int/char                     */
369 /*-----------------------------------------------------------------*/
370 void printIvalType (link * type, initList * ilist, FILE * oFile)
371 {
372     value *val;
373     
374     /* if initList is deep */
375     if (ilist->type == INIT_DEEP)
376         ilist = ilist->init.deep;
377     
378     val = list2val (ilist);
379     switch (getSize (type)) {
380     case 1:
381         if (!val)
382             tfprintf(oFile, "\t!db\n", 0);
383         else
384             tfprintf(oFile, "\t!dbs\n",
385                      aopLiteral (val, 0));
386         break;
387
388     case 2:
389         fprintf(oFile, "\t.byte %s,%s\n", aopLiteral(val, 0),aopLiteral(val, 1));
390         break;
391     case 4:
392         if (!val) {
393             tfprintf (oFile, "\t!dw\n", 0);
394             tfprintf (oFile, "\t!dw\n", 0);
395         }
396         else {
397             fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
398                      aopLiteral (val, 0), aopLiteral (val, 1),
399                      aopLiteral (val, 2), aopLiteral (val, 3));
400         }
401         break;
402     }
403 }
404
405 /*-----------------------------------------------------------------*/
406 /* printIvalStruct - generates initial value for structures        */
407 /*-----------------------------------------------------------------*/
408 void printIvalStruct (symbol * sym,link * type,
409                       initList * ilist, FILE * oFile)
410 {
411     symbol *sflds;
412     initList *iloop;
413     
414     sflds = SPEC_STRUCT (type)->fields;
415     if (ilist->type != INIT_DEEP) {
416         werror (E_INIT_STRUCT, sym->name);
417         return;
418     }
419     
420     iloop = ilist->init.deep;
421     
422     for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL))
423         printIval (sflds, sflds->type, iloop, oFile);
424     
425     return;
426 }
427
428 /*-----------------------------------------------------------------*/
429 /* printIvalChar - generates initital value for character array    */
430 /*-----------------------------------------------------------------*/
431 int printIvalChar (link * type, initList * ilist, FILE * oFile, char *s)
432 {
433     value *val;
434     int remain;
435     
436     if (!s) {
437         
438         val = list2val (ilist);
439         /* if the value is a character string  */
440         if (IS_ARRAY (val->type) && IS_CHAR (val->etype)) {
441             if (!DCL_ELEM (type))
442                 DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1;
443             
444             /* if size mismatch  */
445 /*          if (DCL_ELEM (type) < ((int) strlen (SPEC_CVAL (val->etype).v_char) + 1)) */
446 /*              werror (E_ARRAY_BOUND); */
447             
448             printChar (oFile, SPEC_CVAL (val->etype).v_char,DCL_ELEM(type));
449             
450             if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) -1))>0)
451                 while (remain--)
452                     tfprintf (oFile, "\t!db\n", 0);
453             
454             return 1;
455         }
456         else
457             return 0;
458     }
459     else
460         printChar (oFile, s,strlen(s)+1);
461     return 1;
462 }
463
464 /*-----------------------------------------------------------------*/
465 /* printIvalArray - generates code for array initialization        */
466 /*-----------------------------------------------------------------*/
467 void printIvalArray (symbol * sym, link * type, initList * ilist,
468                      FILE * oFile)
469 {
470     initList *iloop;
471     int lcnt = 0, size = 0;
472     
473     /* take care of the special   case  */
474     /* array of characters can be init  */
475     /* by a string                      */
476     if (IS_CHAR (type->next))
477         if (printIvalChar (type,
478                            (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
479                            oFile, SPEC_CVAL (sym->etype).v_char))
480             return;
481     
482     /* not the special case             */
483     if (ilist->type != INIT_DEEP) {
484         werror (E_INIT_STRUCT, sym->name);
485         return;
486     }
487     
488     iloop = ilist->init.deep;
489     lcnt = DCL_ELEM (type);
490     
491     for (;;) {
492         size++;
493         printIval (sym, type->next, iloop, oFile);
494         iloop = (iloop ? iloop->next : NULL);
495         
496         
497         /* if not array limits given & we */
498         /* are out of initialisers then   */
499         if (!DCL_ELEM (type) && !iloop)
500             break;
501         
502         /* no of elements given and we    */
503         /* have generated for all of them */
504         if (!--lcnt)
505             break;
506     }
507     
508     /* if we have not been given a size  */
509     if (!DCL_ELEM (type))
510         DCL_ELEM (type) = size;
511     
512     return;
513 }
514
515 /*-----------------------------------------------------------------*/
516 /* printIvalFuncPtr - generate initial value for function pointers */
517 /*-----------------------------------------------------------------*/
518 void printIvalFuncPtr (link * type, initList * ilist, FILE * oFile)
519 {
520     value *val;
521     int dLvl = 0;
522     
523     val = list2val (ilist);
524     /* check the types   */
525     if ((dLvl = checkType (val->type, type->next)) <= 0) {
526         tfprintf(oFile, "\t!dw\n", 0);
527         return;
528     }
529     
530     /* now generate the name */
531     if (!val->sym) {
532         if (port->use_dw_for_init)
533             tfprintf(oFile, "\t!dw %s\n", val->name);
534         else  
535             fprintf(oFile, "\t.byte %s,(%s >> 8)\n", val->name,val->name);
536     }
537     else
538         if (port->use_dw_for_init)
539             tfprintf(oFile, "\t!dws\n", val->sym->rname);
540         else 
541             fprintf(oFile, "\t.byte %s,(%s >> 8)\n", val->sym->rname,val->sym->rname);
542     
543     return;
544 }
545
546 /*-----------------------------------------------------------------*/
547 /* printIvalCharPtr - generates initial values for character pointers */
548 /*-----------------------------------------------------------------*/
549 int printIvalCharPtr (symbol * sym, link * type, value * val, FILE * oFile)
550 {
551     int size = 0;
552     
553     /* PENDING: this is _very_ mcs51 specific, including a magic
554        number... 
555        It's also endin specific.
556     */
557     size = getSize (type);
558
559     if (val->name && strlen(val->name)) {
560         switch (size) {
561         case 1:
562             tfprintf(oFile,
563                     "\t!dbs\n", val->name) ;
564             break;
565         case 2:
566             if (port->use_dw_for_init)
567                 tfprintf(oFile, "\t!dws\n", val->name);
568             else
569                 fprintf(oFile, "\t.byte %s,(%s >> 8)\n", val->name, val->name);
570             break;
571             /* PENDING: probably just 3 */
572         default:
573             /* PENDING: 0x02 or 0x%02x, CDATA? */
574             fprintf (oFile,
575                      "\t.byte %s,(%s >> 8),#0x%02x\n",
576                      val->name, val->name, (IS_PTR(val->type) ? DCL_TYPE(val->type) :
577                                             PTR_TYPE(SPEC_OCLS(val->etype))));
578         }
579     }
580     else {
581         switch (size) {
582         case 1:
583             tfprintf(oFile, "\t!dbs\n", aopLiteral(val, 0));
584             break;
585         case 2:
586             tfprintf(oFile, "\t.byte %s,%s\n", 
587                     aopLiteral(val, 0),aopLiteral(val, 1));
588             break;
589         case 3:
590             /* PENDING: 0x02 or 0x%02x, CDATA? */
591             fprintf(oFile, "\t.byte %s,%s,#0x02\n",
592                     aopLiteral (val, 0), aopLiteral (val, 1));
593             break;
594         default:
595             assert(0);
596         }
597     }
598
599
600     if (val->sym && val->sym->isstrlit)
601         addSet (&statsg->syms, val->sym);
602     
603     return 1;
604 }
605
606 /*-----------------------------------------------------------------*/
607 /* printIvalPtr - generates initial value for pointers             */
608 /*-----------------------------------------------------------------*/
609 void printIvalPtr (symbol * sym, link * type, initList * ilist, FILE * oFile)
610 {
611     value *val;
612     
613     /* if deep then   */
614     if (ilist->type == INIT_DEEP)
615         ilist = ilist->init.deep;
616     
617     /* function pointer     */
618     if (IS_FUNC (type->next)) {
619         printIvalFuncPtr (type, ilist, oFile);
620         return;
621     }
622     
623     if (!(val = initPointer (ilist)))
624         return ;
625
626     /* if character pointer */
627     if (IS_CHAR (type->next))
628         if (printIvalCharPtr (sym, type, val, oFile))
629             return;
630     
631     /* check the type      */
632     if (checkType (type, val->type) != 1)
633         werror (E_INIT_WRONG);
634     
635     /* if val is literal */
636     if (IS_LITERAL (val->etype)) {
637         switch (getSize (type)) {
638         case 1:
639             tfprintf(oFile, "\t!db\n", (unsigned int)floatFromVal(val) & 0xff);
640             break;
641         case 2:
642             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral(val, 0),aopLiteral(val, 1));
643             break;
644         case 3:
645             fprintf (oFile, "\t.byte %s,%s,#0x02\n",
646                      aopLiteral (val, 0), aopLiteral (val, 1));
647         }
648         return;
649     }
650     
651     
652     switch (getSize (type)) {
653     case 1:
654         tfprintf (oFile, "\t!dbs\n", val->name);
655         break;
656     case 2:
657         tfprintf (oFile, "\t!dws\n", val->name);
658         break;
659         
660     case 3:
661         fprintf (oFile, "\t.byte %s,(%s >> 8),#0x%02x\n",
662                  val->name, val->name,(IS_PTR(val->type) ? DCL_TYPE(val->type) :
663                                             PTR_TYPE(SPEC_OCLS(val->etype))));
664     }
665     return;
666 }
667
668 /*-----------------------------------------------------------------*/
669 /* printIval - generates code for initial value                    */
670 /*-----------------------------------------------------------------*/
671 void printIval (symbol * sym, link * type, initList * ilist, FILE * oFile)
672 {
673     if (!ilist)
674         return;    
675     
676     /* if structure then    */
677     if (IS_STRUCT (type)) {
678         printIvalStruct (sym, type, ilist, oFile);
679         return;
680     }
681     
682     /* if this is a pointer */
683     if (IS_PTR (type)) {
684         printIvalPtr (sym, type, ilist, oFile);
685         return;
686     }
687     
688     /* if this is an array   */
689     if (IS_ARRAY (type)) {
690         printIvalArray (sym, type, ilist, oFile);
691         return;
692     }
693     
694     /* if type is SPECIFIER */
695     if (IS_SPEC (type)) {
696         printIvalType (type, ilist, oFile);
697         return;
698     }
699 }
700
701 /*-----------------------------------------------------------------*/
702 /* emitStaticSeg - emitcode for the static segment                 */
703 /*-----------------------------------------------------------------*/
704 void emitStaticSeg (memmap * map)
705 {
706     symbol *sym;
707     
708     /*     fprintf(map->oFile,"\t.area\t%s\n",map->sname); */
709     
710     
711     /* for all variables in this segment do */
712     for (sym = setFirstItem (map->syms); sym;
713          sym = setNextItem (map->syms)) {
714         
715         /* if it is "extern" then do nothing */
716         if (IS_EXTERN (sym->etype))
717             continue;
718         
719         /* if it is not static add it to the public
720            table */
721         if (!IS_STATIC (sym->etype))
722             addSetHead (&publics, sym);
723
724         /* print extra debug info if required */
725         if ((options.debug || sym->level == 0) && !options.nodebug) {
726
727             cdbSymbol(sym,cdbFile,FALSE,FALSE);
728
729             if (!sym->level) { /* global */
730                 if (IS_STATIC(sym->etype))
731                     fprintf(code->oFile,"F%s$",moduleName); /* scope is file */
732                 else
733                     fprintf(code->oFile,"G$"); /* scope is global */
734             }
735             else
736                 /* symbol is local */
737                 fprintf(code->oFile,"L%s$",
738                         (sym->localof ? sym->localof->name : "-null-"));
739             fprintf(code->oFile,"%s$%d$%d",sym->name,sym->level,sym->block);
740         }
741         
742         /* if it has an absolute address */
743         if (SPEC_ABSA (sym->etype)) {
744             if ((options.debug || sym->level == 0) && !options.nodebug)
745                 fprintf(code->oFile," == 0x%04x\n", SPEC_ADDR (sym->etype));
746
747             fprintf (code->oFile, "%s\t=\t0x%04x\n",
748                      sym->rname,
749                      SPEC_ADDR (sym->etype));
750         }
751         else {
752             if ((options.debug || sym->level == 0) && !options.nodebug)
753                 fprintf(code->oFile," == .\n"); 
754
755             /* if it has an initial value */
756             if (sym->ival) {
757                 fprintf (code->oFile, "%s:\n", sym->rname);
758                 noAlloc++;
759                 resolveIvalSym (sym->ival);
760                 printIval (sym, sym->type, sym->ival, code->oFile);
761                 noAlloc--;
762             }
763             else {
764                 /* allocate space */
765                 fprintf (code->oFile, "%s:\n", sym->rname);
766                 /* special case for character strings */
767                 if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
768                     SPEC_CVAL (sym->etype).v_char)
769                     printChar (code->oFile,
770                                SPEC_CVAL (sym->etype).v_char,
771                                strlen(SPEC_CVAL (sym->etype).v_char)+1);
772                 else 
773                     tfprintf(code->oFile, "\t!ds\n", (unsigned int)getSize (sym->type)& 0xffff);
774             }
775         }
776     }
777 }
778
779 /*-----------------------------------------------------------------*/
780 /* emitMaps - emits the code for the data portion the code         */
781 /*-----------------------------------------------------------------*/
782 void emitMaps ()
783 {
784     /* no special considerations for the following
785        data, idata & bit & xdata */
786     emitRegularMap (data, TRUE, TRUE);
787     emitRegularMap (idata, TRUE,TRUE);
788     emitRegularMap (bit, TRUE,FALSE);
789     emitRegularMap (xdata, TRUE,TRUE);
790     emitRegularMap (sfr, FALSE,FALSE);
791     emitRegularMap (sfrbit, FALSE,FALSE);
792     emitRegularMap (code, TRUE,FALSE);
793     emitStaticSeg (statsg);
794 }
795
796 /*-----------------------------------------------------------------*/
797 /* createInterruptVect - creates the interrupt vector              */
798 /*-----------------------------------------------------------------*/
799 void createInterruptVect (FILE * vFile)
800 {
801     int i = 0;
802     mainf = newSymbol ("main", 0);
803     mainf->block = 0;
804     
805     /* only if the main function exists */
806     if (!(mainf = findSymWithLevel (SymbolTab, mainf))) {
807         if (!options.cc_only)
808             werror(E_NO_MAIN);
809         return;
810     }
811     
812     /* if the main is only a prototype ie. no body then do nothing */
813     if (!mainf->fbody) {
814         /* if ! compile only then main function should be present */
815         if (!options.cc_only)
816             werror(E_NO_MAIN);
817         return;
818     }
819     
820     tfprintf(vFile, "\t!areacode\n", CODE_NAME);
821     fprintf (vFile, "__interrupt_vect:\n");
822
823     
824     if (!port->genIVT || ! (port->genIVT(vFile, interrupts, maxInterrupts)))
825     {
826         /* "generic" interrupt table header (if port doesn't specify one).
827          *
828          * Look suspiciously like 8051 code to me...
829          */
830     
831         fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
832     
833     
834         /* now for the other interrupts */
835         for (; i < maxInterrupts; i++) {
836                 if (interrupts[i])
837                         fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
838                 else
839                         fprintf (vFile, "\treti\n\t.ds\t7\n");
840         }
841     }
842 }
843
844 char *iComments1 =
845 {
846     ";--------------------------------------------------------\n"
847     "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
848
849 char *iComments2 =
850 {
851     ";--------------------------------------------------------\n"};
852
853
854 /*-----------------------------------------------------------------*/
855 /* initialComments - puts in some initial comments                 */
856 /*-----------------------------------------------------------------*/
857 void initialComments (FILE * afile)
858 {
859     time_t t;
860     time(&t);
861     fprintf (afile, "%s", iComments1);
862     fprintf (afile, "; Version %s %s\n", VersionString,asctime(localtime(&t)));
863     fprintf (afile, "%s", iComments2);
864 }
865
866 /*-----------------------------------------------------------------*/
867 /* printPublics - generates .global for publics                    */
868 /*-----------------------------------------------------------------*/
869 void printPublics (FILE * afile)
870 {
871     symbol *sym;
872     
873     fprintf (afile, "%s", iComments2);
874     fprintf (afile, "; Public variables in this module\n");
875     fprintf (afile, "%s", iComments2);
876     
877     for (sym = setFirstItem (publics); sym;
878          sym = setNextItem (publics))
879         tfprintf(afile, "\t!global\n", sym->rname);
880 }
881
882 /*-----------------------------------------------------------------*/
883 /* printExterns - generates .global for externs                    */
884 /*-----------------------------------------------------------------*/
885 void printExterns (FILE * afile)
886 {
887     symbol *sym;
888     
889     fprintf (afile, "%s", iComments2);
890     fprintf (afile, "; Externals used\n");
891     fprintf (afile, "%s", iComments2);
892     
893     for (sym = setFirstItem (externs); sym;
894          sym = setNextItem (externs))
895         tfprintf(afile, "\t!global\n", sym->rname);
896 }
897
898 /*-----------------------------------------------------------------*/
899 /* emitOverlay - will emit code for the overlay stuff              */
900 /*-----------------------------------------------------------------*/
901 static void emitOverlay(FILE *afile)
902 {
903     set *ovrset;
904     
905     if (!elementsInSet(ovrSetSets))
906         tfprintf(afile,"\t!area\n", port->mem.overlay_name);
907
908     /* for each of the sets in the overlay segment do */
909     for (ovrset = setFirstItem(ovrSetSets); ovrset;
910          ovrset = setNextItem(ovrSetSets)) {
911
912         symbol *sym ;
913
914         if (elementsInSet(ovrset)) {
915             /* this dummy area is used to fool the assembler
916                otherwise the assembler will append each of these
917                declarations into one chunk and will not overlay 
918                sad but true */
919             fprintf(afile,"\t.area _DUMMY\n");
920             /* output the area informtion */
921             fprintf(afile,"\t.area\t%s\n", port->mem.overlay_name); /* MOF */
922         }
923         
924         for (sym = setFirstItem(ovrset); sym;
925              sym = setNextItem(ovrset)) {
926
927             /* if extern then add it to the publics tabledo nothing */
928             if (IS_EXTERN (sym->etype))
929                 continue;
930             
931             /* if allocation required check is needed
932                then check if the symbol really requires
933                allocation only for local variables */
934             if (!IS_AGGREGATE(sym->type) &&
935                 !(sym->_isparm && !IS_REGPARM(sym->etype))
936                 && !sym->allocreq && sym->level)
937                 continue ;
938             
939             /* if global variable & not static or extern 
940                and addPublics allowed then add it to the public set */
941             if ((sym->_isparm && !IS_REGPARM(sym->etype))
942                 && !IS_STATIC (sym->etype))
943                 addSetHead (&publics, sym);
944             
945             /* if extern then do nothing or is a function 
946                then do nothing */
947             if (IS_FUNC (sym->type))
948                 continue;
949
950             /* print extra debug info if required */
951             if ((options.debug || sym->level == 0) && !options.nodebug) {
952                 
953                 cdbSymbol(sym,cdbFile,FALSE,FALSE);
954                 
955                 if (!sym->level) { /* global */
956                     if (IS_STATIC(sym->etype))
957                         fprintf(afile,"F%s$",moduleName); /* scope is file */
958                     else
959                         fprintf(afile,"G$"); /* scope is global */
960                 }
961                 else
962                     /* symbol is local */
963                     fprintf(afile,"L%s$",
964                             (sym->localof ? sym->localof->name : "-null-"));
965                 fprintf(afile,"%s$%d$%d",sym->name,sym->level,sym->block);
966             }
967             
968             /* if is has an absolute address then generate
969                an equate for this no need to allocate space */
970             if (SPEC_ABSA (sym->etype)) {
971                 
972                 if ((options.debug || sym->level == 0) && !options.nodebug)
973                     fprintf (afile," == 0x%04x\n",SPEC_ADDR (sym->etype));          
974
975                 fprintf (afile, "%s\t=\t0x%04x\n",
976                          sym->rname,
977                          SPEC_ADDR (sym->etype));
978             }
979             else {
980                 if ((options.debug || sym->level == 0) && !options.nodebug)
981                     fprintf(afile,"==.\n");
982         
983                 /* allocate space */
984                 tfprintf(afile, "!labeldef\n", sym->rname);
985                 tfprintf(afile, "\t!ds\n", (unsigned int)getSize (sym->type) & 0xffff);
986             }
987             
988         }
989     }
990 }
991
992 /*-----------------------------------------------------------------*/
993 /* glue - the final glue that hold the whole thing together        */
994 /*-----------------------------------------------------------------*/
995 void glue ()
996 {
997     FILE *vFile;
998     FILE *asmFile;
999     FILE *ovrFile = tempfile();
1000     
1001     addSetHead(&tmpfileSet,ovrFile);
1002     /* print the global struct definitions */
1003     if (options.debug)
1004         cdbStructBlock (0,cdbFile);
1005
1006     vFile = tempfile();
1007     /* PENDING: this isnt the best place but it will do */
1008     if (port->general.glue_up_main) {
1009         /* create the interrupt vector table */
1010         createInterruptVect (vFile);
1011     }
1012
1013     addSetHead(&tmpfileSet,vFile);
1014     
1015     /* emit code for the all the variables declared */
1016     emitMaps ();
1017     /* do the overlay segments */
1018     emitOverlay(ovrFile);
1019
1020     /* now put it all together into the assembler file */
1021     /* create the assembler file name */
1022     
1023     if (!options.c1mode) {
1024         sprintf (buffer, srcFileName);
1025         strcat (buffer, ".asm");
1026     }
1027     else {
1028         strcpy(buffer, options.out_name);
1029     }
1030
1031     if (!(asmFile = fopen (buffer, "w"))) {
1032         werror (E_FILE_OPEN_ERR, buffer);
1033         exit (1);
1034     }
1035     
1036     /* initial comments */
1037     initialComments (asmFile);
1038     
1039     /* print module name */
1040     tfprintf(asmFile, "\t!module\n", moduleName);
1041     tfprintf(asmFile, "\t!fileprelude\n");
1042
1043     /* Let the port generate any global directives, etc. */
1044     if (port->genAssemblerPreamble)
1045     {
1046         port->genAssemblerPreamble(asmFile);
1047     }
1048     
1049     /* print the global variables in this module */
1050     printPublics (asmFile);
1051     printExterns (asmFile);
1052
1053     /* copy the sfr segment */
1054     fprintf (asmFile, "%s", iComments2);
1055     fprintf (asmFile, "; special function registers\n");
1056     fprintf (asmFile, "%s", iComments2);
1057     copyFile (asmFile, sfr->oFile);
1058     
1059     /* copy the sbit segment */
1060     fprintf (asmFile, "%s", iComments2);
1061     fprintf (asmFile, "; special function bits \n");
1062     fprintf (asmFile, "%s", iComments2);
1063     copyFile (asmFile, sfrbit->oFile);
1064     
1065     /* copy the data segment */
1066     fprintf (asmFile, "%s", iComments2);
1067     fprintf (asmFile, "; internal ram data\n");
1068     fprintf (asmFile, "%s", iComments2);
1069     copyFile (asmFile, data->oFile);
1070
1071
1072     /* create the overlay segments */
1073     fprintf (asmFile, "%s", iComments2);
1074     fprintf (asmFile, "; overlayable items in internal ram \n");
1075     fprintf (asmFile, "%s", iComments2);    
1076     copyFile (asmFile, ovrFile);
1077
1078     /* create the stack segment MOF */
1079     if (mainf && mainf->fbody) {
1080         fprintf (asmFile, "%s", iComments2);
1081         fprintf (asmFile, "; Stack segment in internal ram \n");
1082         fprintf (asmFile, "%s", iComments2);
1083         fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1084                  "__start__stack:\n\t.ds\t1\n\n");
1085     }
1086
1087     /* create the idata segment */
1088     fprintf (asmFile, "%s", iComments2);
1089     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1090     fprintf (asmFile, "%s", iComments2);
1091     copyFile (asmFile, idata->oFile);
1092     
1093     /* copy the bit segment */
1094     fprintf (asmFile, "%s", iComments2);
1095     fprintf (asmFile, "; bit data\n");
1096     fprintf (asmFile, "%s", iComments2);
1097     copyFile (asmFile, bit->oFile);
1098
1099     /* if external stack then reserve space of it */
1100     if (mainf && mainf->fbody && options.useXstack ) {
1101         fprintf (asmFile, "%s", iComments2);
1102         fprintf (asmFile, "; external stack \n");
1103         fprintf (asmFile, "%s", iComments2);
1104         fprintf (asmFile,"\t.area XSEG (XDATA)\n"); /* MOF */
1105         fprintf (asmFile,"\t.ds 256\n");
1106     }
1107         
1108         
1109     /* copy xtern ram data */
1110     fprintf (asmFile, "%s", iComments2);
1111     fprintf (asmFile, "; external ram data\n");
1112     fprintf (asmFile, "%s", iComments2);
1113     copyFile (asmFile, xdata->oFile);
1114     
1115     /* copy the interrupt vector table */
1116     if (mainf && mainf->fbody) {
1117         fprintf (asmFile, "%s", iComments2);
1118         fprintf (asmFile, "; interrupt vector \n");
1119         fprintf (asmFile, "%s", iComments2);
1120         copyFile (asmFile, vFile);
1121     }
1122     
1123     /* copy global & static initialisations */
1124     fprintf (asmFile, "%s", iComments2);
1125     fprintf (asmFile, "; global & static initialisations\n");
1126     fprintf (asmFile, "%s", iComments2);
1127     
1128     /* Everywhere we generate a reference to the static_name area, 
1129      * (which is currently only here), we immediately follow it with a 
1130      * definition of the post_static_name area. This guarantees that
1131      * the post_static_name area will immediately follow the static_name
1132      * area.
1133      */
1134     tfprintf(asmFile, "\t!area\n", port->mem.static_name); /* MOF */
1135     tfprintf(asmFile, "\t!area\n", port->mem.post_static_name);
1136     tfprintf(asmFile, "\t!area\n", port->mem.static_name);
1137     
1138     if (mainf && mainf->fbody) {
1139         fprintf (asmFile,"__sdcc_gsinit_startup:\n");
1140         /* if external stack is specified then the
1141            higher order byte of the xdatalocation is
1142            going into P2 and the lower order going into
1143            spx */
1144         if (options.useXstack) {
1145             fprintf(asmFile,"\tmov\tP2,#0x%02x\n",
1146                     (((unsigned int)options.xdata_loc) >> 8) & 0xff);
1147             fprintf(asmFile,"\tmov\t_spx,#0x%02x\n",
1148                     (unsigned int)options.xdata_loc & 0xff);
1149         }
1150
1151         /* initialise the stack pointer */
1152         /* if the user specified a value then use it */
1153         if (options.stack_loc) 
1154             fprintf(asmFile,"\tmov\tsp,#%d\n",options.stack_loc);
1155         else 
1156             /* no: we have to compute it */
1157             if (!options.stackOnData && maxRegBank <= 3)
1158                 fprintf(asmFile,"\tmov\tsp,#%d\n",((maxRegBank + 1) * 8) -1); 
1159             else
1160                 fprintf(asmFile,"\tmov\tsp,#__start__stack\n"); /* MOF */
1161
1162         fprintf (asmFile,"\tlcall\t__sdcc_external_startup\n");
1163         fprintf (asmFile,"\tmov\ta,dpl\n");
1164         fprintf (asmFile,"\tjz\t__sdcc_init_data\n");
1165         fprintf (asmFile,"\tljmp\t__sdcc_program_startup\n");
1166         fprintf (asmFile,"__sdcc_init_data:\n");
1167         
1168     }
1169     copyFile (asmFile, statsg->oFile);
1170
1171     if (port->general.glue_up_main && mainf && mainf->fbody)
1172     {
1173         /* This code is generated in the post-static area.
1174          * This area is guaranteed to follow the static area
1175          * by the ugly shucking and jiving about 20 lines ago.
1176          */
1177         tfprintf(asmFile, "\t!area\n", port->mem.post_static_name);
1178         fprintf (asmFile,"\tljmp\t__sdcc_program_startup\n");
1179     }
1180         
1181     /* copy over code */
1182     fprintf (asmFile, "%s", iComments2);
1183     fprintf (asmFile, "; code\n");
1184     fprintf (asmFile, "%s", iComments2);
1185     tfprintf(asmFile, "\t!areacode\n", CODE_NAME);
1186     if (mainf && mainf->fbody) {
1187         
1188         /* entry point @ start of CSEG */
1189         fprintf (asmFile,"__sdcc_program_startup:\n");
1190         
1191         /* put in the call to main */
1192         fprintf(asmFile,"\tlcall\t_main\n");
1193         if (options.mainreturn) {
1194
1195             fprintf(asmFile,";\treturn from main ; will return to caller\n");
1196             fprintf(asmFile,"\tret\n");
1197
1198         } else {
1199                    
1200             fprintf(asmFile,";\treturn from main will lock up\n");
1201             fprintf(asmFile,"\tsjmp     .\n");
1202         }
1203     }
1204     copyFile (asmFile, code->oFile);
1205     
1206     fclose (asmFile);
1207     applyToSet(tmpfileSet,closeTmpFiles);
1208     applyToSet(tmpfileNameSet, rmTmpFiles);
1209 }
1210
1211 /** Creates a temporary file a'la tmpfile which avoids the bugs
1212     in cygwin wrt c:\tmp.
1213     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1214 */
1215 FILE *tempfile(void)
1216 {
1217     const char *tmpdir = NULL;
1218     if (getenv("TMP"))
1219         tmpdir = getenv("TMP");
1220     else if (getenv("TEMP"))
1221         tmpdir = getenv("TEMP");
1222     else if (getenv("TMPDIR"))
1223         tmpdir = getenv("TMPDIR");
1224     if (tmpdir) {
1225         char *name = tempnam(tmpdir, "sdcc");
1226         if (name) {
1227             FILE *fp = fopen(name, "w+b");
1228             if (fp)
1229                 addSetHead(&tmpfileNameSet, name);
1230             return fp;
1231         }
1232         return NULL;
1233     }
1234     return tmpfile();
1235 }
1236
1237 char *gc_strdup(const char *s)
1238 {
1239     char *ret;
1240     ALLOC_ATOMIC(ret, strlen(s)+1);
1241     strcpy(ret, s);
1242     return ret;
1243 }