Disabled "WARNING: function 'main' undefined" when -S option is used.
[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_CHECK));
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 /* printIvalChar - generates initital value for character array    */
279 /*-----------------------------------------------------------------*/
280 static int 
281 printIvalChar (sym_link * type, initList * ilist, pBlock *pb, char *s)
282 {
283         value *val;
284         int remain;
285         
286         if(!pb)
287                 return 0;
288         
289         //fprintf(stderr, "%s\n",__FUNCTION__);
290         if (!s)
291         {
292                 
293                 val = list2val (ilist);
294                 /* if the value is a character string  */
295                 if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
296                 {
297                         if (!DCL_ELEM (type))
298                                 DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1;
299                         
300                         //printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type));
301                         //fprintf(stderr, "%s omitting call to printChar\n",__FUNCTION__);
302                         addpCode2pBlock(pb,newpCodeCharP(";omitting call to printChar"));
303                         
304                         if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) - 1)) > 0)
305                                 while (remain--)
306                                         //tfprintf (oFile, "\t!db !constbyte\n", 0);
307                                         addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(0)));
308                                 return 1;
309                 }
310                 else
311                         return 0;
312         }
313         else {
314                 //printChar (oFile, s, strlen (s) + 1);
315                 
316                 for(remain=0; remain<(int)strlen(s); remain++) {
317                         addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(s[remain])));
318                         //fprintf(stderr,"0x%02x ",s[remain]);
319                 }
320                 //fprintf(stderr,"\n");
321         }
322         return 1;
323 }
324
325 /*-----------------------------------------------------------------*/
326 /* printIvalArray - generates code for array initialization        */
327 /*-----------------------------------------------------------------*/
328 static void 
329 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
330                                 pBlock *pb)
331 {
332         initList *iloop;
333         int lcnt = 0, size = 0;
334         
335         if(!pb)
336                 return;
337         
338         /* take care of the special   case  */
339         /* array of characters can be init  */
340         /* by a string                      */
341         if (IS_CHAR (type->next)) {
342                 //fprintf(stderr,"%s:%d - is_char\n",__FUNCTION__,__LINE__);
343                 if (!IS_LITERAL(list2val(ilist)->etype)) {
344                         werror (W_INIT_WRONG);
345                         return;
346                 }
347                 if (printIvalChar (type,
348                         (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
349                         pb, SPEC_CVAL (sym->etype).v_char))
350                         return;
351         }
352         /* not the special case             */
353         if (ilist->type != INIT_DEEP)
354         {
355                 werror (E_INIT_STRUCT, sym->name);
356                 return;
357         }
358         
359         iloop = ilist->init.deep;
360         lcnt = DCL_ELEM (type);
361         
362         for (;;)
363         {
364                 //fprintf(stderr,"%s:%d - is_char\n",__FUNCTION__,__LINE__);
365                 size++;
366                 printIval (sym, type->next, iloop, pb);
367                 iloop = (iloop ? iloop->next : NULL);
368                 
369                 
370                 /* if not array limits given & we */
371                 /* are out of initialisers then   */
372                 if (!DCL_ELEM (type) && !iloop)
373                         break;
374                 
375                 /* no of elements given and we    */
376                 /* have generated for all of them */
377                 if (!--lcnt) {
378                         /* if initializers left */
379                         if (iloop) {
380                                 werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef);
381                         }
382                         break;
383                 }
384         }
385         
386         /* if we have not been given a size  */
387         if (!DCL_ELEM (type))
388                 DCL_ELEM (type) = size;
389         
390         return;
391 }
392
393 /*-----------------------------------------------------------------*/
394 /* printIval - generates code for initial value                    */
395 /*-----------------------------------------------------------------*/
396 static void 
397 printIval (symbol * sym, sym_link * type, initList * ilist, pBlock *pb)
398 {
399         if (!ilist || !pb)
400                 return;
401         
402         /* if structure then    */
403         if (IS_STRUCT (type))
404         {
405                 //fprintf(stderr,"%s struct\n",__FUNCTION__);
406                 //printIvalStruct (sym, type, ilist, oFile);
407                 return;
408         }
409         
410         /* if this is a pointer */
411         if (IS_PTR (type))
412         {
413                 //fprintf(stderr,"%s pointer\n",__FUNCTION__);
414                 //printIvalPtr (sym, type, ilist, oFile);
415                 return;
416         }
417         
418         /* if this is an array   */
419         if (IS_ARRAY (type))
420         {
421                 //fprintf(stderr,"%s array\n",__FUNCTION__);
422                 printIvalArray (sym, type, ilist, pb);
423                 return;
424         }
425         
426         /* if type is SPECIFIER */
427         if (IS_SPEC (type))
428         {
429                 //fprintf(stderr,"%s spec\n",__FUNCTION__);
430                 printIvalType (sym, type, ilist, pb);
431                 return;
432         }
433 }
434
435 extern void pCodeConstString(char *name, char *value);
436 /*-----------------------------------------------------------------*/
437 /* emitStaticSeg - emitcode for the static segment                 */
438 /*-----------------------------------------------------------------*/
439 static void
440 pic14emitStaticSeg (memmap * map)
441 {
442         symbol *sym;
443         
444         fprintf (map->oFile, ";\t.area\t%s\n", map->sname);
445         
446         //fprintf(stderr, "%s\n",__FUNCTION__);
447         
448         /* for all variables in this segment do */
449         for (sym = setFirstItem (map->syms); sym;
450         sym = setNextItem (map->syms))
451         {
452                 /* if extern then add it into the extern list */
453                 if (IS_EXTERN (sym->etype)) {
454                         addSetHead (&externs, sym);
455                         continue;
456                 }
457                 
458                 /* if it is not static add it to the public
459                 table */
460                 if (!IS_STATIC (sym->etype))
461                         addSetHead (&publics, sym);
462                 
463                 /* print extra debug info if required */
464                 if (options.debug || sym->level == 0)
465                 {
466                         if (!sym->level)
467                         {                       /* global */
468                                 if (IS_STATIC (sym->etype))
469                                         fprintf (code->oFile, "F%s_", moduleName);      /* scope is file */
470                                 else
471                                         fprintf (code->oFile, "G_");    /* scope is global */
472                         }
473                         else
474                                 /* symbol is local */
475                                 fprintf (code->oFile, "L%s_",
476                                 (sym->localof ? sym->localof->name : "-null-"));
477                         fprintf (code->oFile, "%s_%d_%d", sym->name, sym->level, sym->block);
478                         
479                 }
480                 
481                 /* if it has an absolute address */
482                 if (SPEC_ABSA (sym->etype))
483                 {
484                         if (options.debug || sym->level == 0)
485                                 fprintf (code->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
486                         
487                         fprintf (code->oFile, "%s\t=\t0x%04x\n",
488                                 sym->rname,
489                                 SPEC_ADDR (sym->etype));
490                 }
491                 else
492                 {
493                         if (options.debug || sym->level == 0)
494                                 fprintf (code->oFile, " == .\n");
495                         
496                         /* if it has an initial value */
497                         if (sym->ival)
498                         {
499                                 pBlock *pb;
500                                 
501                                 fprintf (code->oFile, "%s:\n", sym->rname);
502                                 noAlloc++;
503                                 resolveIvalSym (sym->ival, sym->type);
504                                 //printIval (sym, sym->type, sym->ival, code->oFile);
505                                 pb = newpCodeChain(NULL, 'P',newpCodeCharP("; Starting pCode block for Ival"));
506                                 addpBlock(pb);
507                                 addpCode2pBlock(pb,newpCodeLabel(sym->rname,-1));
508                                 
509                                 printIval (sym, sym->type, sym->ival, pb);
510                                 noAlloc--;
511                         }
512                         else
513                         {
514                                 
515                                 /* allocate space */
516                                 fprintf (code->oFile, "%s:\n", sym->rname);
517                                 /* special case for character strings */
518                                 if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
519                                         SPEC_CVAL (sym->etype).v_char)
520                                         pCodeConstString(sym->rname , SPEC_CVAL (sym->etype).v_char);
521                                         /*printChar (code->oFile,
522                                         SPEC_CVAL (sym->etype).v_char,
523                                 strlen (SPEC_CVAL (sym->etype).v_char) + 1);*/
524                                 else
525                                         fprintf (code->oFile, "\t.ds\t0x%04x\n", (unsigned int) getSize (sym->type) & 0xffff);
526                         }
527                 }
528         }
529         
530 }
531
532
533 /*-----------------------------------------------------------------*/
534 /* emitMaps - emits the code for the data portion the code         */
535 /*-----------------------------------------------------------------*/
536 static void
537 pic14emitMaps ()
538 {
539 /* no special considerations for the following
540         data, idata & bit & xdata */
541         pic14emitRegularMap (data, TRUE, TRUE);
542         pic14emitRegularMap (idata, TRUE, TRUE);
543         pic14emitRegularMap (bit, TRUE, FALSE);
544         pic14emitRegularMap (xdata, TRUE, TRUE);
545         pic14emitRegularMap (sfr, FALSE, FALSE);
546         pic14emitRegularMap (sfrbit, FALSE, FALSE);
547         pic14emitRegularMap (code, TRUE, FALSE);
548         pic14emitStaticSeg (statsg);
549 }
550
551 /*-----------------------------------------------------------------*/
552 /* createInterruptVect - creates the interrupt vector              */
553 /*-----------------------------------------------------------------*/
554 static void
555 pic14createInterruptVect (FILE * vFile)
556 {
557         mainf = newSymbol ("main", 0);
558         mainf->block = 0;
559         
560         /* only if the main function exists */
561         if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
562         {
563                 struct options *op = &options;
564                 if (!(op->cc_only || noAssemble))
565                         //      werror (E_NO_MAIN);
566                         fprintf(stderr,"WARNING: function 'main' undefined\n");
567                 return;
568         }
569         
570         /* if the main is only a prototype ie. no body then do nothing */
571         if (!IFFUNC_HASBODY(mainf->type))
572         {
573                 /* if ! compile only then main function should be present */
574                 if (!(options.cc_only || noAssemble))
575                         //      werror (E_NO_MAIN);
576                         fprintf(stderr,"WARNING: function 'main' undefined\n");
577                 return;
578         }
579         
580         fprintf (vFile, "%s", iComments2);
581         fprintf (vFile, "; config word \n");
582         fprintf (vFile, "%s", iComments2);
583         fprintf (vFile, "\t__config 0x%x\n", getConfigWord(0x2007));
584         
585         fprintf (vFile, "%s", iComments2);
586         fprintf (vFile, "; reset vector \n");
587         fprintf (vFile, "%s", iComments2);
588         fprintf (vFile, "STARTUP\t%s\n", CODE_NAME); // Lkr file should place section STARTUP at address 0x0
589         fprintf (vFile, "\tnop\n"); /* first location for used by incircuit debugger */
590         fprintf (vFile, "\tgoto\t__sdcc_gsinit_startup\n");
591 }
592
593
594 /*-----------------------------------------------------------------*/
595 /* initialComments - puts in some initial comments                 */
596 /*-----------------------------------------------------------------*/
597 static void
598 pic14initialComments (FILE * afile)
599 {
600         initialComments (afile);
601         fprintf (afile, "; PIC port for the 14-bit core\n");
602         fprintf (afile, iComments2);
603         
604 }
605
606 /*-----------------------------------------------------------------*/
607 /* printExterns - generates extern for external variables          */
608 /*-----------------------------------------------------------------*/
609 static void
610 pic14printExterns (FILE * afile)
611 {
612         symbol *sym;
613         
614         fprintf (afile, "%s", iComments2);
615         fprintf (afile, "; extern variables in this module\n");
616         fprintf (afile, "%s", iComments2);
617         
618         for (sym = setFirstItem (externs); sym;
619         sym = setNextItem (externs))
620                 fprintf (afile, "\textern %s\n", sym->rname);
621 }
622
623 /*-----------------------------------------------------------------*/
624 /* printPublics - generates .global for publics                    */
625 /*-----------------------------------------------------------------*/
626 static void
627 pic14printPublics (FILE * afile)
628 {
629         symbol *sym;
630         
631         fprintf (afile, "%s", iComments2);
632         fprintf (afile, "; publics variables in this module\n");
633         fprintf (afile, "%s", iComments2);
634         
635         for (sym = setFirstItem (publics); sym;
636         sym = setNextItem (publics)) {
637                 
638                 if(!IS_BITFIELD(sym->type) && ((IS_FUNC(sym->type) || sym->allocreq))) {
639                         if (!IS_BITVAR(sym->type))
640                                 fprintf (afile, "\tglobal %s\n", sym->rname);
641                 } else {
642                         /* Absolute variables are defines in the asm file as equates and thus can not be made global. */
643                         if (!SPEC_ABSA (sym->etype))
644                                 fprintf (afile, "\tglobal %s\n", sym->rname);
645                 }
646         }
647 }
648
649 /*-----------------------------------------------------------------*/
650 /* emitOverlay - will emit code for the overlay stuff              */
651 /*-----------------------------------------------------------------*/
652 static void
653 pic14emitOverlay (FILE * afile)
654 {
655         set *ovrset;
656         
657         /*  if (!elementsInSet (ovrSetSets))*/
658         
659         /* the hack below, fixes translates for devices which
660         * only have udata_shr memory */
661         fprintf (afile, "%s\t%s\n",
662                 (elementsInSet(ovrSetSets)?"":";"),
663                 port->mem.overlay_name);
664         
665         /* for each of the sets in the overlay segment do */
666         for (ovrset = setFirstItem (ovrSetSets); ovrset;
667         ovrset = setNextItem (ovrSetSets))
668         {
669                 
670                 symbol *sym;
671                 
672                 if (elementsInSet (ovrset))
673                 {
674                 /* this dummy area is used to fool the assembler
675                 otherwise the assembler will append each of these
676                 declarations into one chunk and will not overlay
677                         sad but true */
678                         
679                         /* I don't think this applies to us. We are using gpasm.  CRF */
680                         
681                         fprintf (afile, ";\t.area _DUMMY\n");
682                         /* output the area informtion */
683                         fprintf (afile, ";\t.area\t%s\n", port->mem.overlay_name);      /* MOF */
684                 }
685                 
686                 for (sym = setFirstItem (ovrset); sym;
687                 sym = setNextItem (ovrset))
688                 {
689                         
690                         /* if extern then do nothing */
691                         if (IS_EXTERN (sym->etype))
692                                 continue;
693                         
694                                 /* if allocation required check is needed
695                                 then check if the symbol really requires
696                         allocation only for local variables */
697                         if (!IS_AGGREGATE (sym->type) &&
698                                 !(sym->_isparm && !IS_REGPARM (sym->etype))
699                                 && !sym->allocreq && sym->level)
700                                 continue;
701                         
702                                 /* if global variable & not static or extern
703                         and addPublics allowed then add it to the public set */
704                         if ((sym->_isparm && !IS_REGPARM (sym->etype))
705                                 && !IS_STATIC (sym->etype))
706                                 addSetHead (&publics, sym);
707                         
708                                 /* if extern then do nothing or is a function
709                         then do nothing */
710                         if (IS_FUNC (sym->type))
711                                 continue;
712                         
713                         /* print extra debug info if required */
714                         if (options.debug || sym->level == 0)
715                         {
716                                 if (!sym->level)
717                                 {               /* global */
718                                         if (IS_STATIC (sym->etype))
719                                                 fprintf (afile, "F%s_", moduleName);    /* scope is file */
720                                         else
721                                                 fprintf (afile, "G_");  /* scope is global */
722                                 }
723                                 else
724                                         /* symbol is local */
725                                         fprintf (afile, "L%s_",
726                                         (sym->localof ? sym->localof->name : "-null-"));
727                                 fprintf (afile, "%s_%d_%d", sym->name, sym->level, sym->block);
728                         }
729                         
730                         /* if is has an absolute address then generate
731                         an equate for this no need to allocate space */
732                         if (SPEC_ABSA (sym->etype))
733                         {
734                                 
735                                 if (options.debug || sym->level == 0)
736                                         fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
737                                 
738                                 fprintf (afile, "%s\t=\t0x%04x\n",
739                                         sym->rname,
740                                         SPEC_ADDR (sym->etype));
741                         }
742                         else
743                         {
744                                 if (options.debug || sym->level == 0)
745                                         fprintf (afile, "==.\n");
746                                 
747                                 /* allocate space */
748                                 fprintf (afile, "%s:\n", sym->rname);
749                                 fprintf (afile, "\t.ds\t0x%04x\n", (unsigned int) getSize (sym->type) & 0xffff);
750                         }
751                         
752                 }
753         }
754 }
755
756
757 /*-----------------------------------------------------------------*/
758 /* glue - the final glue that hold the whole thing together        */
759 /*-----------------------------------------------------------------*/
760 void
761 picglue ()
762 {
763         char udata_name[80];
764         FILE *vFile;
765         FILE *asmFile;
766         FILE *ovrFile = tempfile();
767         
768         addSetHead(&tmpfileSet,ovrFile);
769         pCodeInitRegisters();
770         
771         if (mainf && IFFUNC_HASBODY(mainf->type)) {
772                 
773                 pBlock *pb = newpCodeChain(NULL,'X',newpCodeCharP("; Starting pCode block"));
774                 addpBlock(pb);
775                 
776                 /* entry point @ start of CSEG */
777                 addpCode2pBlock(pb,newpCodeLabel("__sdcc_program_startup",-1));
778                 /* put in the call to main */
779                 addpCode2pBlock(pb,newpCode(POC_CALL,newpCodeOp("_main",PO_STR)));
780                 
781                 if (options.mainreturn) {
782                         
783                         addpCode2pBlock(pb,newpCodeCharP(";\treturn from main will return to caller\n"));
784                         addpCode2pBlock(pb,newpCode(POC_RETURN,NULL));
785                         
786                 } else {
787                         
788                         addpCode2pBlock(pb,newpCodeCharP(";\treturn from main will lock up\n"));
789                         addpCode2pBlock(pb,newpCode(POC_GOTO,newpCodeOp("$",PO_STR)));
790                         
791                 }
792         }
793         
794         
795         /* At this point we've got all the code in the form of pCode structures */
796         /* Now it needs to be rearranged into the order it should be placed in the */
797         /* code space */
798         
799         movepBlock2Head('P');              // Last
800         movepBlock2Head(code->dbName);
801         movepBlock2Head('X');
802         movepBlock2Head(statsg->dbName);   // First
803         
804         
805         /* print the global struct definitions */
806         if (options.debug)
807                 cdbStructBlock (0);
808         
809         vFile = tempfile();
810         
811         addSetHead(&tmpfileSet,vFile);
812         
813         /* emit code for the all the variables declared */
814         pic14emitMaps ();
815         /* do the overlay segments */
816         pic14emitOverlay(ovrFile);
817         
818         /* PENDING: this isnt the best place but it will do */
819         if (port->general.glue_up_main) {
820                 /* create the interrupt vector table */
821                 pic14createInterruptVect (vFile);
822         }
823         
824         AnalyzepCode('*');
825         
826         ReuseReg(); // ReuseReg where call tree permits
827         
828         InlinepCode();
829         
830         AnalyzepCode('*');
831         
832         pcode_test();
833         
834         
835         /* now put it all together into the assembler file */
836         /* create the assembler file name */
837         
838         if ((noAssemble || options.c1mode) && fullDstFileName)
839         {
840                 sprintf (buffer, fullDstFileName);
841         }
842         else
843         {
844                 sprintf (buffer, dstFileName);
845                 strcat (buffer, ".asm");
846         }
847         
848         if (!(asmFile = fopen (buffer, "w"))) {
849                 werror (E_FILE_OPEN_ERR, buffer);
850                 exit (1);
851         }
852         
853         /* initial comments */
854         pic14initialComments (asmFile);
855         
856         /* print module name */
857         fprintf (asmFile, ";\t.module %s\n", moduleName);
858         
859         /* Let the port generate any global directives, etc. */
860         if (port->genAssemblerPreamble)
861         {
862                 port->genAssemblerPreamble(asmFile);
863         }
864         
865         /* print the extern variables in this module */
866         pic14printExterns (asmFile);
867         
868         /* print the global variables in this module */
869         pic14printPublics (asmFile);
870         
871         /* copy the sfr segment */
872         fprintf (asmFile, "%s", iComments2);
873         fprintf (asmFile, "; special function registers\n");
874         fprintf (asmFile, "%s", iComments2);
875         copyFile (asmFile, sfr->oFile);
876         
877         
878         if (udata_section_name) {
879                 sprintf(udata_name,"%s",udata_section_name);
880         } else {
881                 sprintf(udata_name,"data_%s",moduleName);
882         }
883         fprintf (asmFile, "%s", iComments2);
884         fprintf (asmFile, "; udata\n");
885         fprintf (asmFile, "%s", iComments2);
886         fprintf (asmFile, "%s\tudata\n", udata_name);
887         copyFile (asmFile, data->oFile);
888         
889         /* Put all variables into a cblock */
890         AnalyzeBanking();
891         writeUsedRegs(asmFile);
892         
893         /* create the overlay segments */
894         fprintf (asmFile, "%s", iComments2);
895         fprintf (asmFile, "; overlayable items in internal ram \n");
896         fprintf (asmFile, "%s", iComments2);    
897         copyFile (asmFile, ovrFile);
898         
899 #if 0
900         
901         /* create the stack segment MOF */
902         if (mainf && IFFUNC_HASBODY(mainf->type)) {
903                 fprintf (asmFile, "%s", iComments2);
904                 fprintf (asmFile, "; Stack segment in internal ram \n");
905                 fprintf (asmFile, "%s", iComments2);    
906                 fprintf (asmFile, ";\t.area\tSSEG\t(DATA)\n"
907                         ";__start__stack:\n;\t.ds\t1\n\n");
908         }
909         
910         /* create the idata segment */
911         fprintf (asmFile, "%s", iComments2);
912         fprintf (asmFile, "; indirectly addressable internal ram data\n");
913         fprintf (asmFile, "%s", iComments2);
914         copyFile (asmFile, idata->oFile);
915         
916         /* if external stack then reserve space of it */
917         if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack ) {
918                 fprintf (asmFile, "%s", iComments2);
919                 fprintf (asmFile, "; external stack \n");
920                 fprintf (asmFile, "%s", iComments2);
921                 fprintf (asmFile,";\t.area XSEG (XDATA)\n"); /* MOF */
922                 fprintf (asmFile,";\t.ds 256\n");
923         }
924         
925         /* copy xtern ram data */
926         fprintf (asmFile, "%s", iComments2);
927         fprintf (asmFile, "; external ram data\n");
928         fprintf (asmFile, "%s", iComments2);
929         copyFile (asmFile, xdata->oFile);
930         
931 #endif
932         
933         /* copy the bit segment */
934         fprintf (asmFile, "%s", iComments2);
935         fprintf (asmFile, "; bit data\n");
936         fprintf (asmFile, "%s", iComments2);
937         copyFile (asmFile, bit->oFile);
938         
939         /* copy the interrupt vector table */
940         if (mainf && IFFUNC_HASBODY(mainf->type)) {
941                 copyFile (asmFile, vFile);
942                 
943                 fprintf (asmFile, "%s", iComments2);
944                 fprintf (asmFile, "; interrupt and initialization code\n");
945                 fprintf (asmFile, "%s", iComments2);
946                 fprintf (asmFile, "code_init\t%s\t0x4\n", CODE_NAME); // Note - for mplink may have to enlarge section vectors in .lnk file
947                 
948                 /* interrupt service routine */
949                 fprintf (asmFile, "__sdcc_interrupt:\n");
950                 copypCode(asmFile, 'I');
951                 
952                 /* initialize data memory */
953                 fprintf (asmFile,"__sdcc_gsinit_startup:\n");
954                 /* FIXME: This is temporary.  The idata section should be used.  If 
955                 not, we could add a special feature to the linker.  This will 
956                 work in the mean time.  Put all initalized data in main.c */
957                 copypCode(asmFile, statsg->dbName);
958                 fprintf (asmFile,"\tpagesel _main\n");
959                 fprintf (asmFile,"\tgoto _main\n");
960         }
961         
962 #if 0    
963         
964         /* copy global & static initialisations */
965         fprintf (asmFile, "%s", iComments2);
966         fprintf (asmFile, "; global & static initialisations\n");
967         fprintf (asmFile, "%s", iComments2);
968         copypCode(asmFile, statsg->dbName);
969         
970 #endif
971         
972         /* copy over code */
973         fprintf (asmFile, "%s", iComments2);
974         fprintf (asmFile, "; code\n");
975         fprintf (asmFile, "%s", iComments2);
976         fprintf (asmFile, "code_%s\t%s\n", moduleName, port->mem.code_name);
977         
978         /* unknown */
979         copypCode(asmFile, 'X');
980         
981         /* _main function */
982         copypCode(asmFile, 'M');
983         
984         /* other functions */
985         copypCode(asmFile, code->dbName);
986         
987         /* unknown */
988         copypCode(asmFile, 'P');
989         
990         fprintf (asmFile,"\tend\n");
991         
992         fclose (asmFile);
993         
994         rm_tmpfiles();
995 }