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