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