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