* Re-added .dw for words, but now port dependent.
[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  wrong:    
306     werror(E_INIT_WRONG);
307     return NULL;
308     
309 }
310
311 /*-----------------------------------------------------------------*/
312 /* printChar - formats and prints a characater string with DB      */
313 /*-----------------------------------------------------------------*/
314 void printChar (FILE * ofile, char *s, int plen)
315 {
316     int i;
317     int len = strlen (s);
318     int pplen = 0;
319     char buf[100];
320     char *p = buf;
321
322     while (len && pplen < plen) {
323         i = 60;
324         while (i && *s && pplen < plen) {
325             if (*s < ' ' || *s == '\"') {
326                 *p = '\0';
327                 if (p != buf) 
328                     tfprintf(ofile, "\t!ascii\n", buf);
329                 tfprintf(ofile, "\t!db\n", *s);
330                 p = buf;
331             }
332             else {
333                 *p = *s;
334                 p++;
335             }
336             s++;
337             pplen++;
338             i--;
339         }
340         if (p != buf) {
341             *p = '\0';
342             tfprintf(ofile, "\t!ascii\n", buf);
343         }
344         
345         if (len > 60)
346             len -= 60;
347         else
348             len = 0;
349     }
350     tfprintf(ofile, "\t!db\n", 0);
351 }
352
353 /*-----------------------------------------------------------------*/
354 /* printIvalType - generates ival for int/char                     */
355 /*-----------------------------------------------------------------*/
356 void printIvalType (link * type, initList * ilist, FILE * oFile)
357 {
358     value *val;
359     
360     /* if initList is deep */
361     if (ilist->type == INIT_DEEP)
362         ilist = ilist->init.deep;
363     
364     val = list2val (ilist);
365     switch (getSize (type)) {
366     case 1:
367         if (!val)
368             tfprintf(oFile, "\t!db\n", 0);
369         else
370             tfprintf(oFile, "\t!dbs\n",
371                      aopLiteral (val, 0));
372         break;
373
374     case 2:
375         fprintf(oFile, "\t.byte %s,%s\n", aopLiteral(val, 0),aopLiteral(val, 1));
376         break;
377     case 4:
378         if (!val) {
379             tfprintf (oFile, "\t!dw\n", 0);
380             tfprintf (oFile, "\t!dw\n", 0);
381         }
382         else {
383             fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
384                      aopLiteral (val, 0), aopLiteral (val, 1),
385                      aopLiteral (val, 2), aopLiteral (val, 3));
386         }
387         break;
388     }
389 }
390
391 /*-----------------------------------------------------------------*/
392 /* printIvalStruct - generates initial value for structures        */
393 /*-----------------------------------------------------------------*/
394 void printIvalStruct (symbol * sym,link * type,
395                       initList * ilist, FILE * oFile)
396 {
397     symbol *sflds;
398     initList *iloop;
399     
400     sflds = SPEC_STRUCT (type)->fields;
401     if (ilist->type != INIT_DEEP) {
402         werror (E_INIT_STRUCT, sym->name);
403         return;
404     }
405     
406     iloop = ilist->init.deep;
407     
408     for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL))
409         printIval (sflds, sflds->type, iloop, oFile);
410     
411     return;
412 }
413
414 /*-----------------------------------------------------------------*/
415 /* printIvalChar - generates initital value for character array    */
416 /*-----------------------------------------------------------------*/
417 int printIvalChar (link * type, initList * ilist, FILE * oFile, char *s)
418 {
419     value *val;
420     int remain;
421     
422     if (!s) {
423         
424         val = list2val (ilist);
425         /* if the value is a character string  */
426         if (IS_ARRAY (val->type) && IS_CHAR (val->etype)) {
427             if (!DCL_ELEM (type))
428                 DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1;
429             
430             /* if size mismatch  */
431 /*          if (DCL_ELEM (type) < ((int) strlen (SPEC_CVAL (val->etype).v_char) + 1)) */
432 /*              werror (E_ARRAY_BOUND); */
433             
434             printChar (oFile, SPEC_CVAL (val->etype).v_char,DCL_ELEM(type));
435             
436             if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) -1))>0)
437                 while (remain--)
438                     tfprintf (oFile, "\t!db\n", 0);
439             
440             return 1;
441         }
442         else
443             return 0;
444     }
445     else
446         printChar (oFile, s,strlen(s)+1);
447     return 1;
448 }
449
450 /*-----------------------------------------------------------------*/
451 /* printIvalArray - generates code for array initialization        */
452 /*-----------------------------------------------------------------*/
453 void printIvalArray (symbol * sym, link * type, initList * ilist,
454                      FILE * oFile)
455 {
456     initList *iloop;
457     int lcnt = 0, size = 0;
458     
459     /* take care of the special   case  */
460     /* array of characters can be init  */
461     /* by a string                      */
462     if (IS_CHAR (type->next))
463         if (printIvalChar (type,
464                            (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
465                            oFile, SPEC_CVAL (sym->etype).v_char))
466             return;
467     
468     /* not the special case             */
469     if (ilist->type != INIT_DEEP) {
470         werror (E_INIT_STRUCT, sym->name);
471         return;
472     }
473     
474     iloop = ilist->init.deep;
475     lcnt = DCL_ELEM (type);
476     
477     for (;;) {
478         size++;
479         printIval (sym, type->next, iloop, oFile);
480         iloop = (iloop ? iloop->next : NULL);
481         
482         
483         /* if not array limits given & we */
484         /* are out of initialisers then   */
485         if (!DCL_ELEM (type) && !iloop)
486             break;
487         
488         /* no of elements given and we    */
489         /* have generated for all of them */
490         if (!--lcnt)
491             break;
492     }
493     
494     /* if we have not been given a size  */
495     if (!DCL_ELEM (type))
496         DCL_ELEM (type) = size;
497     
498     return;
499 }
500
501 /*-----------------------------------------------------------------*/
502 /* printIvalFuncPtr - generate initial value for function pointers */
503 /*-----------------------------------------------------------------*/
504 void printIvalFuncPtr (link * type, initList * ilist, FILE * oFile)
505 {
506     value *val;
507     int dLvl = 0;
508     
509     val = list2val (ilist);
510     /* check the types   */
511     if ((dLvl = checkType (val->type, type->next)) <= 0) {
512         tfprintf(oFile, "\t!dw\n", 0);
513         return;
514     }
515     
516     /* now generate the name */
517     if (!val->sym) {
518         if (port->use_dw_for_init)
519             tfprintf(oFile, "\t!dw %s\n", val->name);
520         else  
521             fprintf(oFile, "\t.byte %s,(%s >> 8)\n", val->name,val->name);
522     }
523     else
524         if (port->use_dw_for_init)
525             tfprintf(oFile, "\t!dws\n", val->sym->rname);
526         else 
527             fprintf(oFile, "\t.byte %s,(%s >> 8)\n", val->sym->rname,val->sym->rname);
528     
529     return;
530 }
531
532 /*-----------------------------------------------------------------*/
533 /* printIvalCharPtr - generates initial values for character pointers */
534 /*-----------------------------------------------------------------*/
535 int printIvalCharPtr (symbol * sym, link * type, value * val, FILE * oFile)
536 {
537     int size = 0;
538     
539     /* PENDING: this is _very_ mcs51 specific, including a magic
540        number... 
541        It's also endin specific.
542     */
543     size = getSize (type);
544
545     if (val->name && strlen(val->name)) {
546         switch (size) {
547         case 1:
548             tfprintf(oFile,
549                     "\t!dbs\n", val->name) ;
550             break;
551         case 2:
552             if (port->use_dw_for_init)
553                 tfprintf(oFile, "\t!dws\n", val->name);
554             else
555                 fprintf(oFile, "\t.byte %s,(%s >> 8)\n", val->name, val->name);
556             break;
557             /* PENDING: probably just 3 */
558         default:
559             /* PENDING: 0x02 or 0x%02x, CDATA? */
560             fprintf (oFile,
561                      "\t.byte %s,(%s >> 8),#0x%02x\n",
562                      val->name, val->name, (IS_PTR(val->type) ? DCL_TYPE(val->type) :
563                                             PTR_TYPE(SPEC_OCLS(val->etype))));
564         }
565     }
566     else {
567         switch (size) {
568         case 1:
569             tfprintf(oFile, "\t!dbs\n", aopLiteral(val, 0));
570             break;
571         case 2:
572             tfprintf(oFile, "\t.byte %s,%s\n", 
573                     aopLiteral(val, 0),aopLiteral(val, 1));
574             break;
575         case 3:
576             /* PENDING: 0x02 or 0x%02x, CDATA? */
577             fprintf(oFile, "\t.byte %s,%s,#0x02\n",
578                     aopLiteral (val, 0), aopLiteral (val, 1));
579             break;
580         default:
581             assert(0);
582         }
583     }
584
585
586     if (val->sym && val->sym->isstrlit)
587         addSet (&statsg->syms, val->sym);
588     
589     return 1;
590 }
591
592 /*-----------------------------------------------------------------*/
593 /* printIvalPtr - generates initial value for pointers             */
594 /*-----------------------------------------------------------------*/
595 void printIvalPtr (symbol * sym, link * type, initList * ilist, FILE * oFile)
596 {
597     value *val;
598     
599     /* if deep then   */
600     if (ilist->type == INIT_DEEP)
601         ilist = ilist->init.deep;
602     
603     /* function pointer     */
604     if (IS_FUNC (type->next)) {
605         printIvalFuncPtr (type, ilist, oFile);
606         return;
607     }
608     
609     if (!(val = initPointer (ilist)))
610         return ;
611
612     /* if character pointer */
613     if (IS_CHAR (type->next))
614         if (printIvalCharPtr (sym, type, val, oFile))
615             return;
616     
617     /* check the type      */
618     if (checkType (type, val->type) != 1)
619         werror (E_INIT_WRONG);
620     
621     /* if val is literal */
622     if (IS_LITERAL (val->etype)) {
623         switch (getSize (type)) {
624         case 1:
625             tfprintf(oFile, "\t!db\n", (unsigned int)floatFromVal(val) & 0xff);
626             break;
627         case 2:
628             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral(val, 0),aopLiteral(val, 1));
629             break;
630         case 3:
631             fprintf (oFile, "\t.byte %s,%s,#0x02\n",
632                      aopLiteral (val, 0), aopLiteral (val, 1));
633         }
634         return;
635     }
636     
637     
638     switch (getSize (type)) {
639     case 1:
640         tfprintf (oFile, "\t!dbs\n", val->name);
641         break;
642     case 2:
643         tfprintf (oFile, "\t!dws\n", val->name);
644         break;
645         
646     case 3:
647         fprintf (oFile, "\t.byte %s,(%s >> 8),#0x%02x\n",
648                  val->name, val->name,(IS_PTR(val->type) ? DCL_TYPE(val->type) :
649                                             PTR_TYPE(SPEC_OCLS(val->etype))));
650     }
651     return;
652 }
653
654 /*-----------------------------------------------------------------*/
655 /* printIval - generates code for initial value                    */
656 /*-----------------------------------------------------------------*/
657 void printIval (symbol * sym, link * type, initList * ilist, FILE * oFile)
658 {
659     if (!ilist)
660         return;    
661     
662     /* if structure then    */
663     if (IS_STRUCT (type)) {
664         printIvalStruct (sym, type, ilist, oFile);
665         return;
666     }
667     
668     /* if this is a pointer */
669     if (IS_PTR (type)) {
670         printIvalPtr (sym, type, ilist, oFile);
671         return;
672     }
673     
674     /* if this is an array   */
675     if (IS_ARRAY (type)) {
676         printIvalArray (sym, type, ilist, oFile);
677         return;
678     }
679     
680     /* if type is SPECIFIER */
681     if (IS_SPEC (type)) {
682         printIvalType (type, ilist, oFile);
683         return;
684     }
685 }
686
687 /*-----------------------------------------------------------------*/
688 /* emitStaticSeg - emitcode for the static segment                 */
689 /*-----------------------------------------------------------------*/
690 void emitStaticSeg (memmap * map)
691 {
692     symbol *sym;
693     
694     /*     fprintf(map->oFile,"\t.area\t%s\n",map->sname); */
695     
696     
697     /* for all variables in this segment do */
698     for (sym = setFirstItem (map->syms); sym;
699          sym = setNextItem (map->syms)) {
700         
701         /* if it is "extern" then do nothing */
702         if (IS_EXTERN (sym->etype))
703             continue;
704         
705         /* if it is not static add it to the public
706            table */
707         if (!IS_STATIC (sym->etype))
708             addSetHead (&publics, sym);
709
710         /* print extra debug info if required */
711         if ((options.debug || sym->level == 0) && !options.nodebug) {
712
713             cdbSymbol(sym,cdbFile,FALSE,FALSE);
714
715             if (!sym->level) { /* global */
716                 if (IS_STATIC(sym->etype))
717                     fprintf(code->oFile,"F%s$",moduleName); /* scope is file */
718                 else
719                     fprintf(code->oFile,"G$"); /* scope is global */
720             }
721             else
722                 /* symbol is local */
723                 fprintf(code->oFile,"L%s$",
724                         (sym->localof ? sym->localof->name : "-null-"));
725             fprintf(code->oFile,"%s$%d$%d",sym->name,sym->level,sym->block);
726         }
727         
728         /* if it has an absolute address */
729         if (SPEC_ABSA (sym->etype)) {
730             if ((options.debug || sym->level == 0) && !options.nodebug)
731                 fprintf(code->oFile," == 0x%04x\n", SPEC_ADDR (sym->etype));
732
733             fprintf (code->oFile, "%s\t=\t0x%04x\n",
734                      sym->rname,
735                      SPEC_ADDR (sym->etype));
736         }
737         else {
738             if ((options.debug || sym->level == 0) && !options.nodebug)
739                 fprintf(code->oFile," == .\n"); 
740
741             /* if it has an initial value */
742             if (sym->ival) {
743                 fprintf (code->oFile, "%s:\n", sym->rname);
744                 noAlloc++;
745                 resolveIvalSym (sym->ival);
746                 printIval (sym, sym->type, sym->ival, code->oFile);
747                 noAlloc--;
748             }
749             else {
750                 /* allocate space */
751                 fprintf (code->oFile, "%s:\n", sym->rname);
752                 /* special case for character strings */
753                 if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
754                     SPEC_CVAL (sym->etype).v_char)
755                     printChar (code->oFile,
756                                SPEC_CVAL (sym->etype).v_char,
757                                strlen(SPEC_CVAL (sym->etype).v_char)+1);
758                 else 
759                     tfprintf(code->oFile, "\t!ds\n", (unsigned int)getSize (sym->type)& 0xffff);
760             }
761         }
762     }
763 }
764
765 /*-----------------------------------------------------------------*/
766 /* emitMaps - emits the code for the data portion the code         */
767 /*-----------------------------------------------------------------*/
768 void emitMaps ()
769 {
770     /* no special considerations for the following
771        data, idata & bit & xdata */
772     emitRegularMap (data, TRUE, TRUE);
773     emitRegularMap (idata, TRUE,TRUE);
774     emitRegularMap (bit, TRUE,FALSE);
775     emitRegularMap (xdata, TRUE,TRUE);
776     emitRegularMap (sfr, FALSE,FALSE);
777     emitRegularMap (sfrbit, FALSE,FALSE);
778     emitRegularMap (code, TRUE,FALSE);
779     emitStaticSeg (statsg);
780 }
781
782 /*-----------------------------------------------------------------*/
783 /* createInterruptVect - creates the interrupt vector              */
784 /*-----------------------------------------------------------------*/
785 void createInterruptVect (FILE * vFile)
786 {
787     int i = 0;
788     mainf = newSymbol ("main", 0);
789     mainf->block = 0;
790     
791     /* only if the main function exists */
792     if (!(mainf = findSymWithLevel (SymbolTab, mainf))) {
793         if (!options.cc_only)
794             werror(E_NO_MAIN);
795         return;
796     }
797     
798     /* if the main is only a prototype ie. no body then do nothing */
799     if (!mainf->fbody) {
800         /* if ! compile only then main function should be present */
801         if (!options.cc_only)
802             werror(E_NO_MAIN);
803         return;
804     }
805     
806     tfprintf(vFile, "\t!areacode\n", CODE_NAME);
807     fprintf (vFile, "__interrupt_vect:\n");
808
809     
810     if (!port->genIVT || ! (port->genIVT(vFile, interrupts, maxInterrupts)))
811     {
812         /* "generic" interrupt table header (if port doesn't specify one).
813          *
814          * Look suspiciously like 8051 code to me...
815          */
816     
817         fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
818     
819     
820         /* now for the other interrupts */
821         for (; i < maxInterrupts; i++) {
822                 if (interrupts[i])
823                         fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
824                 else
825                         fprintf (vFile, "\treti\n\t.ds\t7\n");
826         }
827     }
828 }
829
830 char *iComments1 =
831 {
832     ";--------------------------------------------------------\n"
833     "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
834
835 char *iComments2 =
836 {
837     ";--------------------------------------------------------\n"};
838
839
840 /*-----------------------------------------------------------------*/
841 /* initialComments - puts in some initial comments                 */
842 /*-----------------------------------------------------------------*/
843 void initialComments (FILE * afile)
844 {
845     time_t t;
846     time(&t);
847     fprintf (afile, "%s", iComments1);
848     fprintf (afile, "; Version %s %s\n", VersionString,asctime(localtime(&t)));
849     fprintf (afile, "%s", iComments2);
850 }
851
852 /*-----------------------------------------------------------------*/
853 /* printPublics - generates .global for publics                    */
854 /*-----------------------------------------------------------------*/
855 void printPublics (FILE * afile)
856 {
857     symbol *sym;
858     
859     fprintf (afile, "%s", iComments2);
860     fprintf (afile, "; Public variables in this module\n");
861     fprintf (afile, "%s", iComments2);
862     
863     for (sym = setFirstItem (publics); sym;
864          sym = setNextItem (publics))
865         tfprintf(afile, "\t!global\n", sym->rname);
866 }
867
868 /*-----------------------------------------------------------------*/
869 /* printExterns - generates .global for externs                    */
870 /*-----------------------------------------------------------------*/
871 void printExterns (FILE * afile)
872 {
873     symbol *sym;
874     
875     fprintf (afile, "%s", iComments2);
876     fprintf (afile, "; Externals used\n");
877     fprintf (afile, "%s", iComments2);
878     
879     for (sym = setFirstItem (externs); sym;
880          sym = setNextItem (externs))
881         tfprintf(afile, "\t!global\n", sym->rname);
882 }
883
884 /*-----------------------------------------------------------------*/
885 /* emitOverlay - will emit code for the overlay stuff              */
886 /*-----------------------------------------------------------------*/
887 static void emitOverlay(FILE *afile)
888 {
889     set *ovrset;
890     
891     if (!elementsInSet(ovrSetSets))
892         tfprintf(afile,"\t!area\n", port->mem.overlay_name);
893
894     /* for each of the sets in the overlay segment do */
895     for (ovrset = setFirstItem(ovrSetSets); ovrset;
896          ovrset = setNextItem(ovrSetSets)) {
897
898         symbol *sym ;
899
900         if (elementsInSet(ovrset)) {
901             /* this dummy area is used to fool the assembler
902                otherwise the assembler will append each of these
903                declarations into one chunk and will not overlay 
904                sad but true */
905             fprintf(afile,"\t.area _DUMMY\n");
906             /* output the area informtion */
907             fprintf(afile,"\t.area\t%s\n", port->mem.overlay_name); /* MOF */
908         }
909         
910         for (sym = setFirstItem(ovrset); sym;
911              sym = setNextItem(ovrset)) {
912
913             /* if extern then add it to the publics tabledo nothing */
914             if (IS_EXTERN (sym->etype))
915                 continue;
916             
917             /* if allocation required check is needed
918                then check if the symbol really requires
919                allocation only for local variables */
920             if (!IS_AGGREGATE(sym->type) &&
921                 !(sym->_isparm && !IS_REGPARM(sym->etype))
922                 && !sym->allocreq && sym->level)
923                 continue ;
924             
925             /* if global variable & not static or extern 
926                and addPublics allowed then add it to the public set */
927             if ((sym->_isparm && !IS_REGPARM(sym->etype))
928                 && !IS_STATIC (sym->etype))
929                 addSetHead (&publics, sym);
930             
931             /* if extern then do nothing or is a function 
932                then do nothing */
933             if (IS_FUNC (sym->type))
934                 continue;
935
936             /* print extra debug info if required */
937             if ((options.debug || sym->level == 0) && !options.nodebug) {
938                 
939                 cdbSymbol(sym,cdbFile,FALSE,FALSE);
940                 
941                 if (!sym->level) { /* global */
942                     if (IS_STATIC(sym->etype))
943                         fprintf(afile,"F%s$",moduleName); /* scope is file */
944                     else
945                         fprintf(afile,"G$"); /* scope is global */
946                 }
947                 else
948                     /* symbol is local */
949                     fprintf(afile,"L%s$",
950                             (sym->localof ? sym->localof->name : "-null-"));
951                 fprintf(afile,"%s$%d$%d",sym->name,sym->level,sym->block);
952             }
953             
954             /* if is has an absolute address then generate
955                an equate for this no need to allocate space */
956             if (SPEC_ABSA (sym->etype)) {
957                 
958                 if ((options.debug || sym->level == 0) && !options.nodebug)
959                     fprintf (afile," == 0x%04x\n",SPEC_ADDR (sym->etype));          
960
961                 fprintf (afile, "%s\t=\t0x%04x\n",
962                          sym->rname,
963                          SPEC_ADDR (sym->etype));
964             }
965             else {
966                 if ((options.debug || sym->level == 0) && !options.nodebug)
967                     fprintf(afile,"==.\n");
968         
969                 /* allocate space */
970                 tfprintf(afile, "!labeldef\n", sym->rname);
971                 tfprintf(afile, "\t!ds\n", (unsigned int)getSize (sym->type) & 0xffff);
972             }
973             
974         }
975     }
976 }
977
978 /*-----------------------------------------------------------------*/
979 /* glue - the final glue that hold the whole thing together        */
980 /*-----------------------------------------------------------------*/
981 void glue ()
982 {
983     FILE *vFile;
984     FILE *asmFile;
985     FILE *ovrFile = tempfile();
986     
987     addSetHead(&tmpfileSet,ovrFile);
988     /* print the global struct definitions */
989     if (options.debug)
990         cdbStructBlock (0,cdbFile);
991
992     vFile = tempfile();
993     /* PENDING: this isnt the best place but it will do */
994     if (port->general.glue_up_main) {
995         /* create the interrupt vector table */
996         createInterruptVect (vFile);
997     }
998
999     addSetHead(&tmpfileSet,vFile);
1000     
1001     /* emit code for the all the variables declared */
1002     emitMaps ();
1003     /* do the overlay segments */
1004     emitOverlay(ovrFile);
1005
1006     /* now put it all together into the assembler file */
1007     /* create the assembler file name */
1008     
1009     if (!options.c1mode) {
1010         sprintf (buffer, srcFileName);
1011         strcat (buffer, ".asm");
1012     }
1013     else {
1014         strcpy(buffer, options.out_name);
1015     }
1016
1017     if (!(asmFile = fopen (buffer, "w"))) {
1018         werror (E_FILE_OPEN_ERR, buffer);
1019         exit (1);
1020     }
1021     
1022     /* initial comments */
1023     initialComments (asmFile);
1024     
1025     /* print module name */
1026     tfprintf(asmFile, "\t!module\n", moduleName);
1027     tfprintf(asmFile, "\t!fileprelude\n");
1028
1029     /* Let the port generate any global directives, etc. */
1030     if (port->genAssemblerPreamble)
1031     {
1032         port->genAssemblerPreamble(asmFile);
1033     }
1034     
1035     /* print the global variables in this module */
1036     printPublics (asmFile);
1037     printExterns (asmFile);
1038
1039     /* copy the sfr segment */
1040     fprintf (asmFile, "%s", iComments2);
1041     fprintf (asmFile, "; special function registers\n");
1042     fprintf (asmFile, "%s", iComments2);
1043     copyFile (asmFile, sfr->oFile);
1044     
1045     /* copy the sbit segment */
1046     fprintf (asmFile, "%s", iComments2);
1047     fprintf (asmFile, "; special function bits \n");
1048     fprintf (asmFile, "%s", iComments2);
1049     copyFile (asmFile, sfrbit->oFile);
1050     
1051     /* copy the data segment */
1052     fprintf (asmFile, "%s", iComments2);
1053     fprintf (asmFile, "; internal ram data\n");
1054     fprintf (asmFile, "%s", iComments2);
1055     copyFile (asmFile, data->oFile);
1056
1057
1058     /* create the overlay segments */
1059     fprintf (asmFile, "%s", iComments2);
1060     fprintf (asmFile, "; overlayable items in internal ram \n");
1061     fprintf (asmFile, "%s", iComments2);    
1062     copyFile (asmFile, ovrFile);
1063
1064     /* create the stack segment MOF */
1065     if (mainf && mainf->fbody) {
1066         fprintf (asmFile, "%s", iComments2);
1067         fprintf (asmFile, "; Stack segment in internal ram \n");
1068         fprintf (asmFile, "%s", iComments2);
1069         fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1070                  "__start__stack:\n\t.ds\t1\n\n");
1071     }
1072
1073     /* create the idata segment */
1074     fprintf (asmFile, "%s", iComments2);
1075     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1076     fprintf (asmFile, "%s", iComments2);
1077     copyFile (asmFile, idata->oFile);
1078     
1079     /* copy the bit segment */
1080     fprintf (asmFile, "%s", iComments2);
1081     fprintf (asmFile, "; bit data\n");
1082     fprintf (asmFile, "%s", iComments2);
1083     copyFile (asmFile, bit->oFile);
1084
1085     /* if external stack then reserve space of it */
1086     if (mainf && mainf->fbody && options.useXstack ) {
1087         fprintf (asmFile, "%s", iComments2);
1088         fprintf (asmFile, "; external stack \n");
1089         fprintf (asmFile, "%s", iComments2);
1090         fprintf (asmFile,"\t.area XSEG (XDATA)\n"); /* MOF */
1091         fprintf (asmFile,"\t.ds 256\n");
1092     }
1093         
1094         
1095     /* copy xtern ram data */
1096     fprintf (asmFile, "%s", iComments2);
1097     fprintf (asmFile, "; external ram data\n");
1098     fprintf (asmFile, "%s", iComments2);
1099     copyFile (asmFile, xdata->oFile);
1100     
1101     /* copy the interrupt vector table */
1102     if (mainf && mainf->fbody) {
1103         fprintf (asmFile, "%s", iComments2);
1104         fprintf (asmFile, "; interrupt vector \n");
1105         fprintf (asmFile, "%s", iComments2);
1106         copyFile (asmFile, vFile);
1107     }
1108     
1109     /* copy global & static initialisations */
1110     fprintf (asmFile, "%s", iComments2);
1111     fprintf (asmFile, "; global & static initialisations\n");
1112     fprintf (asmFile, "%s", iComments2);
1113     
1114     /* Everywhere we generate a reference to the static_name area, 
1115      * (which is currently only here), we immediately follow it with a 
1116      * definition of the post_static_name area. This guarantees that
1117      * the post_static_name area will immediately follow the static_name
1118      * area.
1119      */
1120     tfprintf(asmFile, "\t!area\n", port->mem.static_name); /* MOF */
1121     tfprintf(asmFile, "\t!area\n", port->mem.post_static_name);
1122     tfprintf(asmFile, "\t!area\n", port->mem.static_name);
1123     
1124     if (mainf && mainf->fbody) {
1125         fprintf (asmFile,"__sdcc_gsinit_startup:\n");
1126         /* if external stack is specified then the
1127            higher order byte of the xdatalocation is
1128            going into P2 and the lower order going into
1129            spx */
1130         if (options.useXstack) {
1131             fprintf(asmFile,"\tmov\tP2,#0x%02x\n",
1132                     (((unsigned int)options.xdata_loc) >> 8) & 0xff);
1133             fprintf(asmFile,"\tmov\t_spx,#0x%02x\n",
1134                     (unsigned int)options.xdata_loc & 0xff);
1135         }
1136
1137         /* initialise the stack pointer */
1138         /* if the user specified a value then use it */
1139         if (options.stack_loc) 
1140             fprintf(asmFile,"\tmov\tsp,#%d\n",options.stack_loc);
1141         else 
1142             /* no: we have to compute it */
1143             if (!options.stackOnData && maxRegBank <= 3)
1144                 fprintf(asmFile,"\tmov\tsp,#%d\n",((maxRegBank + 1) * 8) -1); 
1145             else
1146                 fprintf(asmFile,"\tmov\tsp,#__start__stack\n"); /* MOF */
1147
1148         fprintf (asmFile,"\tlcall\t__sdcc_external_startup\n");
1149         fprintf (asmFile,"\tmov\ta,dpl\n");
1150         fprintf (asmFile,"\tjz\t__sdcc_init_data\n");
1151         fprintf (asmFile,"\tljmp\t__sdcc_program_startup\n");
1152         fprintf (asmFile,"__sdcc_init_data:\n");
1153         
1154     }
1155     copyFile (asmFile, statsg->oFile);
1156
1157     if (port->general.glue_up_main && mainf && mainf->fbody)
1158     {
1159         /* This code is generated in the post-static area.
1160          * This area is guaranteed to follow the static area
1161          * by the ugly shucking and jiving about 20 lines ago.
1162          */
1163         tfprintf(asmFile, "\t!area\n", port->mem.post_static_name);
1164         fprintf (asmFile,"\tljmp\t__sdcc_program_startup\n");
1165     }
1166         
1167     /* copy over code */
1168     fprintf (asmFile, "%s", iComments2);
1169     fprintf (asmFile, "; code\n");
1170     fprintf (asmFile, "%s", iComments2);
1171     tfprintf(asmFile, "\t!areacode\n", CODE_NAME);
1172     if (mainf && mainf->fbody) {
1173         
1174         /* entry point @ start of CSEG */
1175         fprintf (asmFile,"__sdcc_program_startup:\n");
1176         
1177         /* put in the call to main */
1178         fprintf(asmFile,"\tlcall\t_main\n");
1179         if (options.mainreturn) {
1180
1181             fprintf(asmFile,";\treturn from main ; will return to caller\n");
1182             fprintf(asmFile,"\tret\n");
1183
1184         } else {
1185                    
1186             fprintf(asmFile,";\treturn from main will lock up\n");
1187             fprintf(asmFile,"\tsjmp     .\n");
1188         }
1189     }
1190     copyFile (asmFile, code->oFile);
1191     
1192     fclose (asmFile);
1193     applyToSet(tmpfileSet,closeTmpFiles);
1194     applyToSet(tmpfileNameSet, rmTmpFiles);
1195 }
1196
1197 /** Creates a temporary file a'la tmpfile which avoids the bugs
1198     in cygwin wrt c:\tmp.
1199     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1200 */
1201 FILE *tempfile(void)
1202 {
1203     const char *tmpdir = NULL;
1204     if (getenv("TMP"))
1205         tmpdir = getenv("TMP");
1206     else if (getenv("TEMP"))
1207         tmpdir = getenv("TEMP");
1208     else if (getenv("TMPDIR"))
1209         tmpdir = getenv("TMPDIR");
1210     if (tmpdir) {
1211         char *name = tempnam(tmpdir, "sdcc");
1212         if (name) {
1213             FILE *fp = fopen(name, "w+b");
1214             if (fp)
1215                 addSetHead(&tmpfileNameSet, name);
1216             return fp;
1217         }
1218         return NULL;
1219     }
1220     return tmpfile();
1221 }
1222
1223 char *gc_strdup(const char *s)
1224 {
1225     char *ret;
1226     ALLOC_ATOMIC(ret, strlen(s)+1);
1227     strcpy(ret, s);
1228     return ret;
1229 }