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