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