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