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