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