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