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