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