85d49a3a8495e55a82336710034aa7e623cb2631
[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 #include "pcode.h"
29 #include "newalloc.h"
30
31
32 #ifdef WORDS_BIGENDIAN
33 #define _ENDIAN(x)  (3-x)
34 #else
35 #define _ENDIAN(x)  (x)
36 #endif
37
38 #define BYTE_IN_LONG(x,b) ((x>>(8*_ENDIAN(b)))&0xff)
39
40 extern symbol *interrupts[256];
41 static void printIval (symbol * sym, sym_link * type, initList * ilist, pBlock *pb);
42 extern int noAlloc;
43 extern set *publics;
44 extern set *externs;
45 extern unsigned maxInterrupts;
46 extern int maxRegBank;
47 extern symbol *mainf;
48 extern char *VersionString;
49 extern FILE *codeOutFile;
50 extern set *tmpfileSet;
51 extern set *tmpfileNameSet;
52 extern char *iComments1;
53 extern char *iComments2;
54 //extern void emitStaticSeg (memmap * map);
55
56 extern DEFSETFUNC (closeTmpFiles);
57 extern DEFSETFUNC (rmTmpFiles);
58
59 extern void AnalyzeBanking (void);
60 extern void copyFile (FILE * dest, FILE * src);
61 extern void ReuseReg(void);
62 extern void InlinepCode(void);
63 extern void writeUsedRegs(FILE *);
64
65 extern void initialComments (FILE * afile);
66 extern void printPublics (FILE * afile);
67
68 extern void printChar (FILE * ofile, char *s, int plen);
69 void  pCodeInitRegisters(void);
70 int getConfigWord(int address);
71
72 char *udata_section_name=0;             // FIXME Temporary fix to change udata section name -- VR
73
74 /*-----------------------------------------------------------------*/
75 /* aopLiteral - string from a literal value                        */
76 /*-----------------------------------------------------------------*/
77 int pic14aopLiteral (value *val, int offset)
78 {
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 = (unsigned long) floatFromVal(val);
88                 
89                 return ( (v >> (offset * 8)) & 0xff);
90         }
91         
92         /* it is type float */
93         fl.f = (float) floatFromVal(val);
94 #ifdef WORDS_BIGENDIAN
95         return fl.c[3-offset];
96 #else
97         return fl.c[offset];
98 #endif
99         
100 }
101
102
103 /*-----------------------------------------------------------------*/
104 /* emitRegularMap - emit code for maps with no special cases       */
105 /*-----------------------------------------------------------------*/
106 static void
107 pic14emitRegularMap (memmap * map, bool addPublics, bool arFlag)
108 {
109         symbol *sym;
110         int bitvars = 0;;
111         
112         /* print the area name */
113         if (addPublics)
114                 fprintf (map->oFile, ";\t.area\t%s\n", map->sname);
115         
116         for (sym = setFirstItem (map->syms); sym;
117         sym = setNextItem (map->syms)) {
118                 
119                 //printf("%s\n",sym->name);
120                 
121                 /* if extern then add it into the extern list */
122                 if (IS_EXTERN (sym->etype)) {
123                         addSetHead (&externs, sym);
124                         continue;
125                 }
126                 
127                 /* if allocation required check is needed
128                 then check if the symbol really requires
129                 allocation only for local variables */
130                 if (arFlag && !IS_AGGREGATE (sym->type) &&
131                         !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
132                         !sym->allocreq && sym->level)
133                         continue;
134                 
135                         /* if global variable & not static or extern
136                 and addPublics allowed then add it to the public set */
137                 if ((sym->level == 0 ||
138                         (sym->_isparm && !IS_REGPARM (sym->etype))) &&
139                         addPublics &&
140                         !IS_STATIC (sym->etype))
141                         addSetHead (&publics, sym);
142                 
143                 // PIC code allocates its own registers - so ignore parameter variable generated by processFuncArgs()
144                 if (sym->_isparm)
145                         continue;
146                         /* if extern then do nothing or is a function
147                 then do nothing */
148                 if (IS_FUNC (sym->type))
149                         continue;
150 #if 0
151                 /* print extra debug info if required */
152                 if (options.debug || sym->level == 0)
153                 {
154                         if (!sym->level)        /* global */
155                                 if (IS_STATIC (sym->etype))
156                                         fprintf (map->oFile, "F%s_", moduleName);               /* scope is file */
157                                 else
158                                         fprintf (map->oFile, "G_");     /* scope is global */
159                                 else
160                                         /* symbol is local */
161                                         fprintf (map->oFile, "L%s_", (sym->localof ? sym->localof->name : "-null-"));
162                                 fprintf (map->oFile, "%s_%d_%d", sym->name, sym->level, sym->block);
163                 }
164 #endif
165                 
166                 /* if it has an absolute address then generate
167                 an equate for this no need to allocate space */
168                 if (SPEC_ABSA (sym->etype))
169                 {
170                         //if (options.debug || sym->level == 0)
171                         //fprintf (map->oFile,"; == 0x%04x\n",SPEC_ADDR (sym->etype));
172                         
173                         fprintf (map->oFile, "%s\tEQU\t0x%04x\n",
174                                 sym->rname,
175                                 SPEC_ADDR (sym->etype));
176                 }
177                 else
178                 {
179                         /* allocate space */
180                         
181                         /* If this is a bit variable, then allocate storage after 8 bits have been declared */
182                         /* unlike the 8051, the pic does not have a separate bit area. So we emulate bit ram */
183                         /* by grouping the bits together into groups of 8 and storing them in the normal ram. */
184                         if (IS_BITVAR (sym->etype))
185                         {
186                                 bitvars++;
187                         }
188                         else
189                         {
190                                 fprintf (map->oFile, "%s\tres\t%d\n", sym->rname,getSize (sym->type) & 0xffff);
191                                 /*
192                                 {
193                                 int i, size;
194                                 
195                                   if ((size = (unsigned int) getSize (sym->type) & 0xffff) > 1)
196                                   {
197                                   for (i = 1; i < size; i++)
198                                   fprintf (map->oFile, "\t%s_%d\n", sym->rname, i);
199                                   }
200                                   }
201                                 */
202                         }
203                         //fprintf (map->oFile, "\t.ds\t0x%04x\n", (unsigned int)getSize (sym->type) & 0xffff);
204                 }
205                 
206                 /* if it has a initial value then do it only if
207                 it is a global variable */
208                 if (sym->ival && sym->level == 0) {
209                         ast *ival = NULL;
210                         
211                         if (IS_AGGREGATE (sym->type))
212                                 ival = initAggregates (sym, sym->ival, NULL);
213                         else
214                                 ival = newNode ('=', newAst_VALUE(symbolVal (sym)),
215                                 decorateType (resolveSymbols (list2expr (sym->ival)), RESULT_TYPE_NONE));
216                         codeOutFile = statsg->oFile;
217                         GcurMemmap = statsg;
218                         eBBlockFromiCode (iCodeFromAst (ival));
219                         sym->ival = NULL;
220                 }
221         }
222 }
223
224
225 /*-----------------------------------------------------------------*/
226 /* printIvalType - generates ival for int/char                     */
227 /*-----------------------------------------------------------------*/
228 static void 
229 printIvalType (symbol *sym, sym_link * type, initList * ilist, pBlock *pb)
230 {
231         value *val;
232         unsigned long ulval;
233         
234         //fprintf(stderr, "%s\n",__FUNCTION__);
235         
236         /* if initList is deep */
237         if (ilist->type == INIT_DEEP)
238                 ilist = ilist->init.deep;
239         
240         if (!IS_AGGREGATE(sym->type) && getNelements(type, ilist)>1) {
241                 werror (W_EXCESS_INITIALIZERS, "scalar", sym->name, sym->lineDef);
242         }
243         
244         if (!(val = list2val (ilist))) {
245                 // assuming a warning has been thrown
246                 val=constVal("0");
247         }
248         
249         if (val->type != type) {
250                 val = valCastLiteral(type, floatFromVal(val));
251         }
252         
253         if(val) 
254                 ulval = (unsigned long) floatFromVal (val);
255         else
256                 ulval =0;
257         
258         switch (getSize (type)) {
259         case 1:
260                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,0))));
261                 break;
262                 
263         case 2:
264                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,0))));
265                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,1))));
266                 break;
267                 
268         case 4:
269                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,0))));
270                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,1))));
271                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,2))));
272                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,3))));
273                 break;
274         }
275 }
276
277 /*-----------------------------------------------------------------*/
278 /* printIvalBitFields - generate initializer for bitfields         */
279 /*-----------------------------------------------------------------*/
280 static void printIvalBitFields(symbol **sym, initList **ilist, pBlock *pb ) 
281 {
282         value *val ;
283         symbol *lsym = *sym;
284         initList *lilist = *ilist ;
285         unsigned long ival = 0;
286         int size =0;
287         
288         
289         do {
290                 unsigned long i;
291                 val = list2val(lilist);
292                 if (size) {
293                         if (SPEC_BLEN(lsym->etype) > 8) {
294                                 size += ((SPEC_BLEN (lsym->etype) / 8) + 
295                                         (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
296                         }
297                 } else {
298                         size = ((SPEC_BLEN (lsym->etype) / 8) + 
299                                 (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
300                 }
301                 i = (unsigned long)floatFromVal(val);
302                 i <<= SPEC_BSTR (lsym->etype);
303                 ival |= i;
304                 if (! ( lsym->next &&
305                         (IS_BITFIELD(lsym->next->type)) &&
306                         (SPEC_BSTR(lsym->next->etype)))) break;
307                 lsym = lsym->next;
308                 lilist = lilist->next;
309         } while (1);
310         switch (size) {
311         case 1:
312                 //tfprintf (oFile, "\t!db !constbyte\n",ival);
313                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(ival)));
314                 break;
315                 
316         case 2:
317                 //tfprintf (oFile, "\t!dw !constword\n",ival);
318                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(ival>>8)));
319                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(ival)));
320                 break;
321         case 4:
322                 //tfprintf (oFile, "\t!db  !constword,!constword\n",(ival >> 8) & 0xffff, (ival & 0xffff));
323                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(ival>>24)));
324                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(ival>>16)));
325                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(ival>>8)));
326                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(ival)));
327                 break;
328         }
329         *sym = lsym;
330         *ilist = lilist;
331 }
332
333 /*-----------------------------------------------------------------*/
334 /* printIvalStruct - generates initial value for structures        */
335 /*-----------------------------------------------------------------*/
336 static void printIvalStruct (symbol * sym, sym_link * type, initList * ilist, pBlock *pb)
337 {
338         symbol *sflds;
339         initList *iloop = NULL;
340         
341         sflds = SPEC_STRUCT (type)->fields;
342         
343         if (ilist) {
344                 if (ilist->type != INIT_DEEP) {
345                         werrorfl (sym->fileDef, sym->lineDef, E_INIT_STRUCT, sym->name);
346                         return;
347                 }
348                 
349                 iloop = ilist->init.deep;
350         }
351         
352         for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) {
353                 if (IS_BITFIELD(sflds->type)) {
354                         printIvalBitFields(&sflds,&iloop,pb);
355                 } else {
356                         printIval (sym, sflds->type, iloop, pb);
357                 }
358         }
359         if (iloop) {
360                 werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "struct", sym->name);
361         }
362         return;
363 }
364
365 /*-----------------------------------------------------------------*/
366 /* printIvalChar - generates initital value for character array    */
367 /*-----------------------------------------------------------------*/
368 static int 
369 printIvalChar (sym_link * type, initList * ilist, pBlock *pb, char *s)
370 {
371         value *val;
372         int remain, ilen;
373         
374         if(!pb)
375                 return 0;
376         
377         //fprintf(stderr, "%s\n",__FUNCTION__);
378         if (!s)
379         {
380                 
381                 val = list2val (ilist);
382
383                 /* if the value is a character string  */
384                 if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
385                 {
386                         ilen = DCL_ELEM(val->type);
387
388                         if (!DCL_ELEM (type))
389                                 DCL_ELEM (type) = ilen;
390                 
391                         /* emit string constant */
392                         for (remain = 0; remain < ilen; remain++) {
393                                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(SPEC_CVAL(val->etype).v_char[remain])));
394                         }
395                         
396                         /* fill array up to desired size */
397                         if ((remain = (DCL_ELEM (type) - ilen)) > 0)
398                                 while (remain--)
399                                         //tfprintf (oFile, "\t!db !constbyte\n", 0);
400                                         addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(0)));
401                                 return 1;
402                 }
403                 else
404                         return 0;
405         }
406         else {
407                 //printChar (oFile, s, strlen (s) + 1);
408                 
409                 for(remain=0; remain<(int)strlen(s); remain++) {
410                         addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(s[remain])));
411                         //fprintf(stderr,"0x%02x ",s[remain]);
412                 }
413                 //fprintf(stderr,"\n");
414         }
415         return 1;
416 }
417
418 /*-----------------------------------------------------------------*/
419 /* printIvalArray - generates code for array initialization        */
420 /*-----------------------------------------------------------------*/
421 static void 
422 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
423                                 pBlock *pb)
424 {
425         initList *iloop;
426         unsigned size = 0;
427         
428         if(!pb)
429                 return;
430         if (ilist) {
431                 /* take care of the special   case  */
432                 /* array of characters can be init  */
433                 /* by a string                      */
434                 if (IS_CHAR (type->next)) {
435                         //fprintf(stderr,"%s:%d - is_char\n",__FUNCTION__,__LINE__);
436                         if (!IS_LITERAL(list2val(ilist)->etype)) {
437                                 werror (W_INIT_WRONG);
438                                 return;
439                         }
440                         if (printIvalChar (type,
441                                 (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
442                                 pb, SPEC_CVAL (sym->etype).v_char))
443                                 return;
444                 }
445                 /* not the special case */
446                 if (ilist->type != INIT_DEEP) {
447                         werrorfl (ilist->filename, ilist->lineno, E_INIT_STRUCT, sym->name);
448                         return;
449                 }
450
451                 for (iloop=ilist->init.deep; iloop; iloop=iloop->next) {
452                         if ((++size > DCL_ELEM(type)) && DCL_ELEM(type)) {
453                                 werrorfl (sym->fileDef, sym->lineDef, W_EXCESS_INITIALIZERS, "array", sym->name);
454                                 break;
455                         }
456                         printIval (sym, type->next, iloop, pb);
457                 }
458         }
459
460         if (DCL_ELEM(type)) {
461                 // pad with zeros if needed
462                 if (size<DCL_ELEM(type)) {
463                         size = (DCL_ELEM(type) - size) * getSize(type->next);
464                         while (size--) {
465                                 //tfprintf (oFile, "\t!db !constbyte\n", 0);
466                                 addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(0)));
467                         }
468                 }
469         } else {
470                 // we have not been given a size, but we now know it
471                 DCL_ELEM (type) = size;
472         }
473
474         return;
475 }
476
477 /*-----------------------------------------------------------------*/
478 /* printIval - generates code for initial value                    */
479 /*-----------------------------------------------------------------*/
480 static void 
481 printIval (symbol * sym, sym_link * type, initList * ilist, pBlock *pb)
482 {
483         if (!ilist || !pb)
484                 return;
485         
486         /* if structure then    */
487         if (IS_STRUCT (type))
488         {
489                 //fprintf(stderr,"%s struct\n",__FUNCTION__);
490                 printIvalStruct (sym, type, ilist, pb);
491                 return;
492         }
493         
494         /* if this is a pointer */
495         if (IS_PTR (type))
496         {
497                 //fprintf(stderr,"%s pointer\n",__FUNCTION__);
498                 //printIvalPtr (sym, type, ilist, oFile);
499                 return;
500         }
501         
502         /* if this is an array   */
503         if (IS_ARRAY (type))
504         {
505                 //fprintf(stderr,"%s array\n",__FUNCTION__);
506                 printIvalArray (sym, type, ilist, pb);
507                 return;
508         }
509         
510         /* if type is SPECIFIER */
511         if (IS_SPEC (type))
512         {
513                 //fprintf(stderr,"%s spec\n",__FUNCTION__);
514                 printIvalType (sym, type, ilist, pb);
515                 return;
516         }
517 }
518
519 extern void pCodeConstString(char *name, char *value);
520 /*-----------------------------------------------------------------*/
521 /* emitStaticSeg - emitcode for the static segment                 */
522 /*-----------------------------------------------------------------*/
523 static void
524 pic14emitStaticSeg (memmap * map)
525 {
526         symbol *sym;
527         
528         fprintf (map->oFile, ";\t.area\t%s\n", map->sname);
529         
530         //fprintf(stderr, "%s\n",__FUNCTION__);
531         
532         /* for all variables in this segment do */
533         for (sym = setFirstItem (map->syms); sym;
534         sym = setNextItem (map->syms))
535         {
536                 /* if extern then add it into the extern list */
537                 if (IS_EXTERN (sym->etype)) {
538                         addSetHead (&externs, sym);
539                         continue;
540                 }
541                 
542                 /* if it is not static add it to the public
543                 table */
544                 if (!IS_STATIC (sym->etype))
545                         addSetHead (&publics, sym);
546                 
547                 /* print extra debug info if required */
548                 if (options.debug || sym->level == 0)
549                 {
550                         if (!sym->level)
551                         {                       /* global */
552                                 if (IS_STATIC (sym->etype))
553                                         fprintf (code->oFile, "F%s_", moduleName);      /* scope is file */
554                                 else
555                                         fprintf (code->oFile, "G_");    /* scope is global */
556                         }
557                         else
558                                 /* symbol is local */
559                                 fprintf (code->oFile, "L%s_",
560                                 (sym->localof ? sym->localof->name : "-null-"));
561                         fprintf (code->oFile, "%s_%d_%d", sym->name, sym->level, sym->block);
562                         
563                 }
564                 
565                 /* if it has an absolute address */
566                 if (SPEC_ABSA (sym->etype))
567                 {
568                         if (options.debug || sym->level == 0)
569                                 fprintf (code->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
570                         
571                         fprintf (code->oFile, "%s\t=\t0x%04x\n",
572                                 sym->rname,
573                                 SPEC_ADDR (sym->etype));
574                 }
575                 else
576                 {
577                         if (options.debug || sym->level == 0)
578                                 fprintf (code->oFile, " == .\n");
579                         
580                         /* if it has an initial value */
581                         if (sym->ival)
582                         {
583                                 pBlock *pb;
584                                 
585                                 fprintf (code->oFile, "%s:\n", sym->rname);
586                                 noAlloc++;
587                                 resolveIvalSym (sym->ival, sym->type);
588                                 //printIval (sym, sym->type, sym->ival, code->oFile);
589                                 pb = newpCodeChain(NULL, 'P',newpCodeCharP("; Starting pCode block for Ival"));
590                                 addpBlock(pb);
591                                 addpCode2pBlock(pb,newpCodeLabel(sym->rname,-1));
592                                 
593                                 printIval (sym, sym->type, sym->ival, pb);
594                                 noAlloc--;
595                         }
596                         else
597                         {
598                                 
599                                 /* allocate space */
600                                 fprintf (code->oFile, "%s:\n", sym->rname);
601                                 /* special case for character strings */
602                                 if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
603                                         SPEC_CVAL (sym->etype).v_char)
604                                         pCodeConstString(sym->rname , SPEC_CVAL (sym->etype).v_char);
605                                         /*printChar (code->oFile,
606                                         SPEC_CVAL (sym->etype).v_char,
607                                 strlen (SPEC_CVAL (sym->etype).v_char) + 1);*/
608                                 else
609                                         fprintf (code->oFile, "\t.ds\t0x%04x\n", (unsigned int) getSize (sym->type) & 0xffff);
610                         }
611                 }
612         }
613         
614 }
615
616
617 /*-----------------------------------------------------------------*/
618 /* emitMaps - emits the code for the data portion the code         */
619 /*-----------------------------------------------------------------*/
620 static void
621 pic14emitMaps ()
622 {
623 /* no special considerations for the following
624         data, idata & bit & xdata */
625         pic14emitRegularMap (data, TRUE, TRUE);
626         pic14emitRegularMap (idata, TRUE, TRUE);
627         pic14emitRegularMap (bit, TRUE, FALSE);
628         pic14emitRegularMap (xdata, TRUE, TRUE);
629         pic14emitRegularMap (sfr, FALSE, FALSE);
630         pic14emitRegularMap (sfrbit, FALSE, FALSE);
631         pic14emitRegularMap (code, TRUE, FALSE);
632         pic14emitStaticSeg (statsg);
633 }
634
635 /*-----------------------------------------------------------------*/
636 /* createInterruptVect - creates the interrupt vector              */
637 /*-----------------------------------------------------------------*/
638 static void
639 pic14createInterruptVect (FILE * vFile)
640 {
641         mainf = newSymbol ("main", 0);
642         mainf->block = 0;
643         
644         /* only if the main function exists */
645         if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
646         {
647                 struct options *op = &options;
648                 if (!(op->cc_only || noAssemble))
649                         //      werror (E_NO_MAIN);
650                         fprintf(stderr,"WARNING: function 'main' undefined\n");
651                 return;
652         }
653         
654         /* if the main is only a prototype ie. no body then do nothing */
655         if (!IFFUNC_HASBODY(mainf->type))
656         {
657                 /* if ! compile only then main function should be present */
658                 if (!(options.cc_only || noAssemble))
659                         //      werror (E_NO_MAIN);
660                         fprintf(stderr,"WARNING: function 'main' undefined\n");
661                 return;
662         }
663         
664         fprintf (vFile, "%s", iComments2);
665         fprintf (vFile, "; config word \n");
666         fprintf (vFile, "%s", iComments2);
667         fprintf (vFile, "\t__config 0x%x\n", getConfigWord(0x2007));
668         
669         fprintf (vFile, "%s", iComments2);
670         fprintf (vFile, "; reset vector \n");
671         fprintf (vFile, "%s", iComments2);
672         fprintf (vFile, "STARTUP\t%s\n", CODE_NAME); // Lkr file should place section STARTUP at address 0x0
673         fprintf (vFile, "\tnop\n"); /* first location for used by incircuit debugger */
674         fprintf (vFile, "\tgoto\t__sdcc_gsinit_startup\n");
675 }
676
677
678 /*-----------------------------------------------------------------*/
679 /* initialComments - puts in some initial comments                 */
680 /*-----------------------------------------------------------------*/
681 static void
682 pic14initialComments (FILE * afile)
683 {
684         initialComments (afile);
685         fprintf (afile, "; PIC port for the 14-bit core\n");
686         fprintf (afile, iComments2);
687         
688 }
689
690 /*-----------------------------------------------------------------*/
691 /* printExterns - generates extern for external variables          */
692 /*-----------------------------------------------------------------*/
693 static void
694 pic14printExterns (FILE * afile)
695 {
696         symbol *sym;
697         
698         fprintf (afile, "%s", iComments2);
699         fprintf (afile, "; extern variables in this module\n");
700         fprintf (afile, "%s", iComments2);
701         
702         for (sym = setFirstItem (externs); sym;
703         sym = setNextItem (externs))
704                 fprintf (afile, "\textern %s\n", sym->rname);
705 }
706
707 /*-----------------------------------------------------------------*/
708 /* printPublics - generates .global for publics                    */
709 /*-----------------------------------------------------------------*/
710 static void
711 pic14printPublics (FILE * afile)
712 {
713         symbol *sym;
714         
715         fprintf (afile, "%s", iComments2);
716         fprintf (afile, "; publics variables in this module\n");
717         fprintf (afile, "%s", iComments2);
718         
719         for (sym = setFirstItem (publics); sym;
720         sym = setNextItem (publics)) {
721                 
722                 if(!IS_BITFIELD(sym->type) && ((IS_FUNC(sym->type) || sym->allocreq))) {
723                         if (!IS_BITVAR(sym->type))
724                                 fprintf (afile, "\tglobal %s\n", sym->rname);
725                 } else {
726                         /* Absolute variables are defines in the asm file as equates and thus can not be made global. */
727                         if (!SPEC_ABSA (sym->etype))
728                                 fprintf (afile, "\tglobal %s\n", sym->rname);
729                 }
730         }
731 }
732
733 /*-----------------------------------------------------------------*/
734 /* emitOverlay - will emit code for the overlay stuff              */
735 /*-----------------------------------------------------------------*/
736 static void
737 pic14emitOverlay (FILE * afile)
738 {
739         set *ovrset;
740         
741         /*  if (!elementsInSet (ovrSetSets))*/
742         
743         /* the hack below, fixes translates for devices which
744         * only have udata_shr memory */
745         fprintf (afile, "%s\t%s\n",
746                 (elementsInSet(ovrSetSets)?"":";"),
747                 port->mem.overlay_name);
748         
749         /* for each of the sets in the overlay segment do */
750         for (ovrset = setFirstItem (ovrSetSets); ovrset;
751         ovrset = setNextItem (ovrSetSets))
752         {
753                 
754                 symbol *sym;
755                 
756                 if (elementsInSet (ovrset))
757                 {
758                 /* this dummy area is used to fool the assembler
759                 otherwise the assembler will append each of these
760                 declarations into one chunk and will not overlay
761                         sad but true */
762                         
763                         /* I don't think this applies to us. We are using gpasm.  CRF */
764                         
765                         fprintf (afile, ";\t.area _DUMMY\n");
766                         /* output the area informtion */
767                         fprintf (afile, ";\t.area\t%s\n", port->mem.overlay_name);      /* MOF */
768                 }
769                 
770                 for (sym = setFirstItem (ovrset); sym;
771                 sym = setNextItem (ovrset))
772                 {
773                         
774                         /* if extern then do nothing */
775                         if (IS_EXTERN (sym->etype))
776                                 continue;
777                         
778                                 /* if allocation required check is needed
779                                 then check if the symbol really requires
780                         allocation only for local variables */
781                         if (!IS_AGGREGATE (sym->type) &&
782                                 !(sym->_isparm && !IS_REGPARM (sym->etype))
783                                 && !sym->allocreq && sym->level)
784                                 continue;
785                         
786                                 /* if global variable & not static or extern
787                         and addPublics allowed then add it to the public set */
788                         if ((sym->_isparm && !IS_REGPARM (sym->etype))
789                                 && !IS_STATIC (sym->etype))
790                                 addSetHead (&publics, sym);
791                         
792                                 /* if extern then do nothing or is a function
793                         then do nothing */
794                         if (IS_FUNC (sym->type))
795                                 continue;
796                         
797                         /* print extra debug info if required */
798                         if (options.debug || sym->level == 0)
799                         {
800                                 if (!sym->level)
801                                 {               /* global */
802                                         if (IS_STATIC (sym->etype))
803                                                 fprintf (afile, "F%s_", moduleName);    /* scope is file */
804                                         else
805                                                 fprintf (afile, "G_");  /* scope is global */
806                                 }
807                                 else
808                                         /* symbol is local */
809                                         fprintf (afile, "L%s_",
810                                         (sym->localof ? sym->localof->name : "-null-"));
811                                 fprintf (afile, "%s_%d_%d", sym->name, sym->level, sym->block);
812                         }
813                         
814                         /* if is has an absolute address then generate
815                         an equate for this no need to allocate space */
816                         if (SPEC_ABSA (sym->etype))
817                         {
818                                 
819                                 if (options.debug || sym->level == 0)
820                                         fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
821                                 
822                                 fprintf (afile, "%s\t=\t0x%04x\n",
823                                         sym->rname,
824                                         SPEC_ADDR (sym->etype));
825                         }
826                         else
827                         {
828                                 if (options.debug || sym->level == 0)
829                                         fprintf (afile, "==.\n");
830                                 
831                                 /* allocate space */
832                                 fprintf (afile, "%s:\n", sym->rname);
833                                 fprintf (afile, "\t.ds\t0x%04x\n", (unsigned int) getSize (sym->type) & 0xffff);
834                         }
835                         
836                 }
837         }
838 }
839
840
841 /*-----------------------------------------------------------------*/
842 /* glue - the final glue that hold the whole thing together        */
843 /*-----------------------------------------------------------------*/
844 void
845 picglue ()
846 {
847         char udata_name[80];
848         FILE *vFile;
849         FILE *asmFile;
850         FILE *ovrFile = tempfile();
851         
852         addSetHead(&tmpfileSet,ovrFile);
853         pCodeInitRegisters();
854         
855         if (mainf && IFFUNC_HASBODY(mainf->type)) {
856                 
857                 pBlock *pb = newpCodeChain(NULL,'X',newpCodeCharP("; Starting pCode block"));
858                 addpBlock(pb);
859                 
860                 /* entry point @ start of CSEG */
861                 addpCode2pBlock(pb,newpCodeLabel("__sdcc_program_startup",-1));
862                 /* put in the call to main */
863                 addpCode2pBlock(pb,newpCode(POC_CALL,newpCodeOp("_main",PO_STR)));
864                 
865                 if (options.mainreturn) {
866                         
867                         addpCode2pBlock(pb,newpCodeCharP(";\treturn from main will return to caller\n"));
868                         addpCode2pBlock(pb,newpCode(POC_RETURN,NULL));
869                         
870                 } else {
871                         
872                         addpCode2pBlock(pb,newpCodeCharP(";\treturn from main will lock up\n"));
873                         addpCode2pBlock(pb,newpCode(POC_GOTO,newpCodeOp("$",PO_STR)));
874                         
875                 }
876         }
877         
878         
879         /* At this point we've got all the code in the form of pCode structures */
880         /* Now it needs to be rearranged into the order it should be placed in the */
881         /* code space */
882         
883         movepBlock2Head('P');              // Last
884         movepBlock2Head(code->dbName);
885         movepBlock2Head('X');
886         movepBlock2Head(statsg->dbName);   // First
887         
888         
889         /* print the global struct definitions */
890         if (options.debug)
891                 cdbStructBlock (0);
892         
893         vFile = tempfile();
894         
895         addSetHead(&tmpfileSet,vFile);
896         
897         /* emit code for the all the variables declared */
898         pic14emitMaps ();
899         /* do the overlay segments */
900         pic14emitOverlay(ovrFile);
901         
902         /* PENDING: this isnt the best place but it will do */
903         if (port->general.glue_up_main) {
904                 /* create the interrupt vector table */
905                 pic14createInterruptVect (vFile);
906         }
907         
908         AnalyzepCode('*');
909         
910         ReuseReg(); // ReuseReg where call tree permits
911         
912         InlinepCode();
913         
914         AnalyzepCode('*');
915         
916         pcode_test();
917         
918         
919         /* now put it all together into the assembler file */
920         /* create the assembler file name */
921         
922         if ((noAssemble || options.c1mode) && fullDstFileName)
923         {
924                 sprintf (buffer, fullDstFileName);
925         }
926         else
927         {
928                 sprintf (buffer, dstFileName);
929                 strcat (buffer, ".asm");
930         }
931         
932         if (!(asmFile = fopen (buffer, "w"))) {
933                 werror (E_FILE_OPEN_ERR, buffer);
934                 exit (1);
935         }
936         
937         /* initial comments */
938         pic14initialComments (asmFile);
939         
940         /* print module name */
941         fprintf (asmFile, ";\t.module %s\n", moduleName);
942         
943         /* Let the port generate any global directives, etc. */
944         if (port->genAssemblerPreamble)
945         {
946                 port->genAssemblerPreamble(asmFile);
947         }
948         
949         /* print the extern variables in this module */
950         pic14printExterns (asmFile);
951         
952         /* print the global variables in this module */
953         pic14printPublics (asmFile);
954         
955         /* copy the sfr segment */
956         fprintf (asmFile, "%s", iComments2);
957         fprintf (asmFile, "; special function registers\n");
958         fprintf (asmFile, "%s", iComments2);
959         copyFile (asmFile, sfr->oFile);
960         
961         
962         if (udata_section_name) {
963                 sprintf(udata_name,"%s",udata_section_name);
964         } else {
965                 sprintf(udata_name,"data_%s",moduleName);
966         }
967         fprintf (asmFile, "%s", iComments2);
968         fprintf (asmFile, "; udata\n");
969         fprintf (asmFile, "%s", iComments2);
970         fprintf (asmFile, "%s\tudata\n", udata_name);
971         copyFile (asmFile, data->oFile);
972         
973         /* Put all variables into a cblock */
974         AnalyzeBanking();
975         writeUsedRegs(asmFile);
976         
977         /* create the overlay segments */
978         fprintf (asmFile, "%s", iComments2);
979         fprintf (asmFile, "; overlayable items in internal ram \n");
980         fprintf (asmFile, "%s", iComments2);    
981         copyFile (asmFile, ovrFile);
982         
983 #if 0
984         
985         /* create the stack segment MOF */
986         if (mainf && IFFUNC_HASBODY(mainf->type)) {
987                 fprintf (asmFile, "%s", iComments2);
988                 fprintf (asmFile, "; Stack segment in internal ram \n");
989                 fprintf (asmFile, "%s", iComments2);    
990                 fprintf (asmFile, ";\t.area\tSSEG\t(DATA)\n"
991                         ";__start__stack:\n;\t.ds\t1\n\n");
992         }
993         
994         /* create the idata segment */
995         fprintf (asmFile, "%s", iComments2);
996         fprintf (asmFile, "; indirectly addressable internal ram data\n");
997         fprintf (asmFile, "%s", iComments2);
998         copyFile (asmFile, idata->oFile);
999         
1000         /* if external stack then reserve space of it */
1001         if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack ) {
1002                 fprintf (asmFile, "%s", iComments2);
1003                 fprintf (asmFile, "; external stack \n");
1004                 fprintf (asmFile, "%s", iComments2);
1005                 fprintf (asmFile,";\t.area XSEG (XDATA)\n"); /* MOF */
1006                 fprintf (asmFile,";\t.ds 256\n");
1007         }
1008         
1009         /* copy xtern ram data */
1010         fprintf (asmFile, "%s", iComments2);
1011         fprintf (asmFile, "; external ram data\n");
1012         fprintf (asmFile, "%s", iComments2);
1013         copyFile (asmFile, xdata->oFile);
1014         
1015 #endif
1016         
1017         /* copy the bit segment */
1018         fprintf (asmFile, "%s", iComments2);
1019         fprintf (asmFile, "; bit data\n");
1020         fprintf (asmFile, "%s", iComments2);
1021         copyFile (asmFile, bit->oFile);
1022         
1023         /* copy the interrupt vector table */
1024         if (mainf && IFFUNC_HASBODY(mainf->type)) {
1025                 copyFile (asmFile, vFile);
1026                 
1027                 fprintf (asmFile, "%s", iComments2);
1028                 fprintf (asmFile, "; interrupt and initialization code\n");
1029                 fprintf (asmFile, "%s", iComments2);
1030                 fprintf (asmFile, "code_init\t%s\t0x4\n", CODE_NAME); // Note - for mplink may have to enlarge section vectors in .lnk file
1031                 
1032                 /* interrupt service routine */
1033                 fprintf (asmFile, "__sdcc_interrupt:\n");
1034                 copypCode(asmFile, 'I');
1035                 
1036                 /* initialize data memory */
1037                 fprintf (asmFile,"__sdcc_gsinit_startup:\n");
1038                 /* FIXME: This is temporary.  The idata section should be used.  If 
1039                 not, we could add a special feature to the linker.  This will 
1040                 work in the mean time.  Put all initalized data in main.c */
1041                 copypCode(asmFile, statsg->dbName);
1042                 fprintf (asmFile,"\tpagesel _main\n");
1043                 fprintf (asmFile,"\tgoto _main\n");
1044         }
1045         
1046 #if 0    
1047         
1048         /* copy global & static initialisations */
1049         fprintf (asmFile, "%s", iComments2);
1050         fprintf (asmFile, "; global & static initialisations\n");
1051         fprintf (asmFile, "%s", iComments2);
1052         copypCode(asmFile, statsg->dbName);
1053         
1054 #endif
1055         
1056         /* copy over code */
1057         fprintf (asmFile, "%s", iComments2);
1058         fprintf (asmFile, "; code\n");
1059         fprintf (asmFile, "%s", iComments2);
1060         fprintf (asmFile, "code_%s\t%s\n", moduleName, port->mem.code_name);
1061         
1062         /* unknown */
1063         copypCode(asmFile, 'X');
1064         
1065         /* _main function */
1066         copypCode(asmFile, 'M');
1067         
1068         /* other functions */
1069         copypCode(asmFile, code->dbName);
1070         
1071         /* unknown */
1072         copypCode(asmFile, 'P');
1073         
1074         fprintf (asmFile,"\tend\n");
1075         
1076         fclose (asmFile);
1077         
1078         rm_tmpfiles();
1079 }