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