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