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