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