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