fixed bug #597940
[fw/sdcc] / src / SDCCglue.c
1 /*-------------------------------------------------------------------------
2
3   SDCCglue.c - glues everything we have done together into one file.
4                 Written By -  Sandeep Dutta . sandeep.dutta@usa.net (1998)
5
6    This program is free software; you can redistribute it and/or modify it
7    under the terms of the GNU General Public License as published by the
8    Free Software Foundation; either version 2, or (at your option) any
9    later version.
10
11    This program is distributed in the hope that it will be useful,
12    but WITHOUT ANY WARRANTY; without even the implied warranty of
13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14    GNU General Public License for more details.
15
16    You should have received a copy of the GNU General Public License
17    along with this program; if not, write to the Free Software
18    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
19
20    In other words, you are welcome to use, share and improve this program.
21    You are forbidden to forbid anyone else to use, share and improve
22    what you give them.   Help stamp out software-hoarding!
23 -------------------------------------------------------------------------*/
24
25 #include "common.h"
26 #include "asm.h"
27 #include <time.h>
28 #include "newalloc.h"
29 #include <fcntl.h>
30 #include <sys/stat.h>
31
32 #ifdef _WIN32
33 #include <io.h>
34 #else
35 #include <unistd.h>
36 #endif
37
38 symbol *interrupts[256];
39
40 void printIval (symbol *, sym_link *, initList *, FILE *);
41 set *publics = NULL;            /* public variables */
42 set *externs = NULL;            /* Varibles that are declared as extern */
43
44 /* TODO: this should be configurable (DS803C90 uses more than 6) */
45 unsigned maxInterrupts = 6;
46 int allocInfo = 1;
47 symbol *mainf;
48 set *pipeSet = NULL;            /* set of pipes */
49 set *tmpfileSet = NULL;         /* set of tmp file created by the compiler */
50 set *tmpfileNameSet = NULL;     /* All are unlinked at close. */
51
52 /*-----------------------------------------------------------------*/
53 /* closePipes - closes all pipes created by the compiler           */
54 /*-----------------------------------------------------------------*/
55 DEFSETFUNC (closePipes)
56 {
57   FILE *pfile = item;
58   int ret;
59
60   if (pfile) {
61     ret = pclose (pfile);
62     assert(ret != -1);
63   }
64
65   return 0;
66 }
67
68 /*-----------------------------------------------------------------*/
69 /* closeTmpFiles - closes all tmp files created by the compiler    */
70 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
71 /*-----------------------------------------------------------------*/
72 DEFSETFUNC (closeTmpFiles)
73 {
74   FILE *tfile = item;
75   int ret;
76
77   if (tfile) {
78     ret = fclose (tfile);
79     assert(ret == 0);
80   }
81
82   return 0;
83 }
84
85 /*-----------------------------------------------------------------*/
86 /* rmTmpFiles - unlinks all tmp files created by the compiler      */
87 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
88 /*-----------------------------------------------------------------*/
89 DEFSETFUNC (rmTmpFiles)
90 {
91   char *name = item;
92   int ret;
93
94   if (name) {
95       ret = unlink (name);
96       assert(ret == 0);
97       Safe_free (name);
98   }
99
100   return 0;
101 }
102
103 /*-----------------------------------------------------------------*/
104 /* rm_tmpfiles - close and remove temporary files and delete sets  */
105 /*-----------------------------------------------------------------*/
106 void
107 rm_tmpfiles (void)
108 {
109   /* close temporary files */
110   applyToSet (pipeSet, closePipes);
111   /* close temporary files */
112   deleteSet (&pipeSet);
113
114   applyToSet (tmpfileSet, closeTmpFiles);
115   /* remove temporary files */
116   applyToSet (tmpfileNameSet, rmTmpFiles);
117   /* delete temorary file sets */
118   deleteSet (&tmpfileSet);
119   deleteSet (&tmpfileNameSet);
120 }
121
122 /*-----------------------------------------------------------------*/
123 /* copyFile - copies source file to destination file               */
124 /*-----------------------------------------------------------------*/
125 void 
126 copyFile (FILE * dest, FILE * src)
127 {
128   int ch;
129
130   rewind (src);
131   while (!feof (src))
132     if ((ch = fgetc (src)) != EOF)
133       fputc (ch, dest);
134 }
135
136 char *
137 aopLiteralLong (value * val, int offset, int size)
138 {
139         union {
140                 float f;
141                 unsigned char c[4];
142         }
143         fl;
144
145         if (!val) {
146           // assuming we have been warned before
147           val=constVal("0");
148         }
149
150         /* if it is a float then it gets tricky */
151         /* otherwise it is fairly simple */
152         if (!IS_FLOAT (val->type)) {
153                 unsigned long v = (unsigned long) floatFromVal (val);
154
155                 v >>= (offset * 8);
156                 switch (size) {
157                 case 1:
158                         tsprintf (buffer, sizeof(buffer), 
159                                   "!immedbyte", (unsigned int) v & 0xff);
160                         break;
161                 case 2:
162                         tsprintf (buffer, sizeof(buffer), 
163                                   "!immedword", (unsigned int) v & 0xffff);
164                         break;
165                 default:
166                         /* Hmm.  Too big for now. */
167                         assert (0);
168                 }
169                 return Safe_strdup (buffer);
170         }
171
172         /* PENDING: For now size must be 1 */
173         assert (size == 1);
174
175         /* it is type float */
176         fl.f = (float) floatFromVal (val);
177 #ifdef WORDS_BIGENDIAN
178         tsprintf (buffer, sizeof(buffer), 
179                   "!immedbyte", fl.c[3 - offset]);
180 #else
181         tsprintf (buffer, sizeof(buffer), 
182                   "!immedbyte", fl.c[offset]);
183 #endif
184         return Safe_strdup (buffer);
185 }
186
187 /*-----------------------------------------------------------------*/
188 /* aopLiteral - string from a literal value                        */
189 /*-----------------------------------------------------------------*/
190 char *
191 aopLiteral (value * val, int offset)
192 {
193         return aopLiteralLong (val, offset, 1);
194 }
195
196 /*-----------------------------------------------------------------*/
197 /* emitRegularMap - emit code for maps with no special cases       */
198 /*-----------------------------------------------------------------*/
199 static void 
200 emitRegularMap (memmap * map, bool addPublics, bool arFlag)
201 {
202   symbol *sym;
203   ast *ival = NULL;
204
205   if (!map)
206     return;
207
208   if (addPublics)
209     {
210       /* PENDING: special case here - should remove */
211       if (!strcmp (map->sname, CODE_NAME))
212         tfprintf (map->oFile, "\t!areacode\n", map->sname);
213       else if (!strcmp (map->sname, DATA_NAME))
214         tfprintf (map->oFile, "\t!areadata\n", map->sname);
215       else if (!strcmp (map->sname, HOME_NAME))
216         tfprintf (map->oFile, "\t!areahome\n", map->sname);
217       else
218         tfprintf (map->oFile, "\t!area\n", map->sname);
219     }
220  
221   for (sym = setFirstItem (map->syms); sym;
222        sym = setNextItem (map->syms))
223     {
224       symbol *newSym=NULL;
225
226       /* if extern then add it into the extern list */
227       if (IS_EXTERN (sym->etype))
228         {
229           addSetHead (&externs, sym);
230           continue;
231         }
232
233       /* if allocation required check is needed
234          then check if the symbol really requires
235          allocation only for local variables */
236
237       if (arFlag && !IS_AGGREGATE (sym->type) &&
238           !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
239           !sym->allocreq && sym->level)
240         continue;
241
242       /* for bitvar locals and parameters */
243       if (!arFlag && !sym->allocreq && sym->level 
244           && !SPEC_ABSA (sym->etype)) {
245         continue;
246       }
247
248       /* if global variable & not static or extern
249          and addPublics allowed then add it to the public set */
250       if ((sym->level == 0 ||
251            (sym->_isparm && !IS_REGPARM (sym->etype))) &&
252           addPublics &&
253           !IS_STATIC (sym->etype) &&
254           (IS_FUNC(sym->type) ? (sym->used || IFFUNC_HASBODY(sym->type)) : 1))
255         {
256           addSetHead (&publics, sym);
257         }
258
259       /* if extern then do nothing or is a function
260          then do nothing */
261       if (IS_FUNC (sym->type))
262         continue;
263
264       /* print extra debug info if required */
265       if (options.debug)
266         {
267           if (!sym->level) /* global */
268             {
269               if (IS_STATIC (sym->etype))
270                 fprintf (map->oFile, "F%s$", moduleName); /* scope is file */
271               else
272                 fprintf (map->oFile, "G$");     /* scope is global */
273             }
274           else
275             {
276               /* symbol is local */
277               fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-"));
278             }
279           fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block);
280         }
281       
282       /* if it has an initial value then do it only if
283          it is a global variable */
284       if (sym->ival && sym->level == 0) {
285         if (SPEC_OCLS(sym->etype)==xidata) {
286           /* create a new "XINIT (CODE)" symbol, that will be emitted later
287              in the static seg */
288           newSym=copySymbol (sym);
289           SPEC_OCLS(newSym->etype)=xinit;
290           SNPRINTF (newSym->name, sizeof(newSym->name), "__xinit_%s", sym->name);
291           SNPRINTF (newSym->rname, sizeof(newSym->rname), "__xinit_%s", sym->rname);
292           SPEC_CONST(newSym->etype)=1;
293           SPEC_STAT(newSym->etype)=1;
294           resolveIvalSym(newSym->ival);
295
296           // add it to the "XINIT (CODE)" segment
297           addSet(&xinit->syms, newSym);
298           sym->ival=NULL;
299         } else {
300           if (IS_AGGREGATE (sym->type)) {
301             ival = initAggregates (sym, sym->ival, NULL);
302           } else {
303             if (getNelements(sym->type, sym->ival)>1) {
304               werror (W_EXCESS_INITIALIZERS, "scalar", 
305                       sym->name, sym->lineDef);
306             }
307             ival = newNode ('=', newAst_VALUE (symbolVal (sym)),
308                             decorateType (resolveSymbols (list2expr (sym->ival))));
309           }
310           codeOutFile = statsg->oFile;
311
312           if (ival) {
313             // set ival's lineno to where the symbol was defined
314             setAstLineno (ival, lineno=sym->lineDef);
315             // check if this is not a constant expression
316             if (!constExprTree(ival)) {
317               werror (E_CONST_EXPECTED, "found expression");
318               // but try to do it anyway
319             }
320             allocInfo = 0;
321             eBBlockFromiCode (iCodeFromAst (ival));
322             allocInfo = 1;
323           }
324         }         
325         sym->ival = NULL;
326       }
327
328       /* if is has an absolute address then generate
329          an equate for this no need to allocate space */
330       if (SPEC_ABSA (sym->etype))
331         {
332           char *equ="=";
333           if (options.debug) {
334             fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
335           }
336           if (TARGET_IS_XA51) {
337             if (map==sfr) {
338               equ="sfr";
339             } else if (map==bit || map==sfrbit) {
340               equ="bit";
341             }
342           }
343           fprintf (map->oFile, "%s\t%s\t0x%04x\n",
344                    sym->rname, equ,
345                    SPEC_ADDR (sym->etype));
346         }
347       else {
348         int size = getSize (sym->type);
349         if (size==0) {
350           werror(E_UNKNOWN_SIZE,sym->name);
351         }
352         /* allocate space */
353         if (options.debug) {
354           fprintf (map->oFile, "==.\n");
355         }
356         if (IS_STATIC (sym->etype))
357           tfprintf (map->oFile, "!slabeldef\n", sym->rname);
358         else
359           tfprintf (map->oFile, "!labeldef\n", sym->rname);           
360         tfprintf (map->oFile, "\t!ds\n", 
361                   (unsigned int)  size & 0xffff);
362       }
363     }
364 }
365
366 /*-----------------------------------------------------------------*/
367 /* initPointer - pointer initialization code massaging             */
368 /*-----------------------------------------------------------------*/
369 value *
370 initPointer (initList * ilist, sym_link *toType)
371 {
372         value *val;
373         ast *expr = list2expr (ilist);
374         
375         if (!expr)
376                 goto wrong;
377         
378         /* try it the oldway first */
379         if ((val = constExprValue (expr, FALSE)))
380                 return val;
381         
382         /* ( ptr + constant ) */
383         if (IS_AST_OP (expr) &&
384             (expr->opval.op == '+' || expr->opval.op == '-') &&
385             IS_AST_SYM_VALUE (expr->left) &&
386             (IS_ARRAY(expr->left->ftype) || IS_PTR(expr->left->ftype)) &&
387             compareType(toType, expr->left->ftype) &&
388             IS_AST_LIT_VALUE (expr->right)) {
389           return valForCastAggr (expr->left, expr->left->ftype,
390                                       expr->right,
391                                       expr->opval.op);
392         }
393         
394         /* (char *)&a */
395         if (IS_AST_OP(expr) && expr->opval.op==CAST &&
396             IS_AST_OP(expr->right) && expr->right->opval.op=='&') {
397           if (compareType(toType, expr->left->ftype)!=1) {
398             werror (W_INIT_WRONG);
399             printFromToType(expr->left->ftype, toType);
400           }
401           // skip the cast ???
402           expr=expr->right;
403         }
404
405         /* no then we have to do these cludgy checks */
406         /* pointers can be initialized with address of
407            a variable or address of an array element */
408         if (IS_AST_OP (expr) && expr->opval.op == '&') {
409                 /* address of symbol */
410                 if (IS_AST_SYM_VALUE (expr->left)) {
411                         val = copyValue (AST_VALUE (expr->left));
412                         val->type = newLink (DECLARATOR);
413                         if (SPEC_SCLS (expr->left->etype) == S_CODE) {
414                                 DCL_TYPE (val->type) = CPOINTER;
415                                 DCL_PTR_CONST (val->type) = port->mem.code_ro;
416                         }
417                         else if (SPEC_SCLS (expr->left->etype) == S_XDATA)
418                                 DCL_TYPE (val->type) = FPOINTER;
419                         else if (SPEC_SCLS (expr->left->etype) == S_XSTACK)
420                                 DCL_TYPE (val->type) = PPOINTER;
421                         else if (SPEC_SCLS (expr->left->etype) == S_IDATA)
422                                 DCL_TYPE (val->type) = IPOINTER;
423                         else if (SPEC_SCLS (expr->left->etype) == S_EEPROM)
424                                 DCL_TYPE (val->type) = EEPPOINTER;
425                         else
426                                 DCL_TYPE (val->type) = POINTER;
427                         val->type->next = expr->left->ftype;
428                         val->etype = getSpec (val->type);
429                         return val;
430                 }
431
432                 /* if address of indexed array */
433                 if (IS_AST_OP (expr->left) && expr->left->opval.op == '[')
434                         return valForArray (expr->left);
435
436                 /* if address of structure element then
437                    case 1. a.b ; */
438                 if (IS_AST_OP (expr->left) &&
439                     expr->left->opval.op == '.') {
440                         return valForStructElem (expr->left->left,
441                                                  expr->left->right);
442                 }
443
444                 /* case 2. (&a)->b ;
445                    (&some_struct)->element */
446                 if (IS_AST_OP (expr->left) &&
447                     expr->left->opval.op == PTR_OP &&
448                     IS_ADDRESS_OF_OP (expr->left->left)) {
449                   return valForStructElem (expr->left->left->left,
450                                            expr->left->right);
451                 }
452         }
453         /* case 3. (((char *) &a) +/- constant) */
454         if (IS_AST_OP (expr) &&
455             (expr->opval.op == '+' || expr->opval.op == '-') &&
456             IS_AST_OP (expr->left) && expr->left->opval.op == CAST &&
457             IS_AST_OP (expr->left->right) &&
458             expr->left->right->opval.op == '&' &&
459             IS_AST_LIT_VALUE (expr->right)) {
460
461                 return valForCastAggr (expr->left->right->left,
462                                        expr->left->left->opval.lnk,
463                                        expr->right, expr->opval.op);
464
465         }
466         /* case 4. (char *)(array type) */
467         if (IS_CAST_OP(expr) && IS_AST_SYM_VALUE (expr->right) &&
468             IS_ARRAY(expr->right->ftype)) {
469
470                 val = copyValue (AST_VALUE (expr->right));
471                 val->type = newLink (DECLARATOR);
472                 if (SPEC_SCLS (expr->right->etype) == S_CODE) {
473                         DCL_TYPE (val->type) = CPOINTER;
474                         DCL_PTR_CONST (val->type) = port->mem.code_ro;
475                 }
476                 else if (SPEC_SCLS (expr->right->etype) == S_XDATA)
477                         DCL_TYPE (val->type) = FPOINTER;
478                 else if (SPEC_SCLS (expr->right->etype) == S_XSTACK)
479                         DCL_TYPE (val->type) = PPOINTER;
480                 else if (SPEC_SCLS (expr->right->etype) == S_IDATA)
481                         DCL_TYPE (val->type) = IPOINTER;
482                 else if (SPEC_SCLS (expr->right->etype) == S_EEPROM)
483                         DCL_TYPE (val->type) = EEPPOINTER;
484                 else
485                         DCL_TYPE (val->type) = POINTER;
486                 val->type->next = expr->right->ftype->next;
487                 val->etype = getSpec (val->type);
488                 return val;
489         }
490  wrong:
491         werror (E_INCOMPAT_PTYPES);
492         return NULL;
493
494 }
495
496 /*-----------------------------------------------------------------*/
497 /* printChar - formats and prints a characater string with DB      */
498 /*-----------------------------------------------------------------*/
499 void 
500 printChar (FILE * ofile, char *s, int plen)
501 {
502   int i;
503   int len = strlen (s);
504   int pplen = 0;
505   char buf[100];
506   char *p = buf;
507
508   while (len && pplen < plen)
509     {
510       i = 60;
511       while (i && *s && pplen < plen)
512         {
513           if (*s < ' ' || *s == '\"' || *s=='\\')
514             {
515               *p = '\0';
516               if (p != buf)
517                 tfprintf (ofile, "\t!ascii\n", buf);
518               tfprintf (ofile, "\t!db !constbyte\n", (unsigned char)*s);
519               p = buf;
520             }
521           else
522             {
523               *p = *s;
524               p++;
525             }
526           s++;
527           pplen++;
528           i--;
529         }
530       if (p != buf)
531         {
532           *p = '\0';
533           tfprintf (ofile, "\t!ascii\n", buf);
534           p = buf;
535         }
536
537       if (len > 60)
538         len -= 60;
539       else
540         len = 0;
541     }
542   tfprintf (ofile, "\t!db !constbyte\n", 0);
543 }
544
545 /*-----------------------------------------------------------------*/
546 /* return the generic pointer high byte for a given pointer type.  */
547 /*-----------------------------------------------------------------*/
548 int 
549 pointerTypeToGPByte (const int p_type, const char *iname, const char *oname)
550 {
551   switch (p_type)
552     {
553     case IPOINTER:
554     case POINTER:
555       return GPTYPE_NEAR;
556     case GPOINTER:
557         werror (E_CANNOT_USE_GENERIC_POINTER, 
558                 iname ? iname : "<null>", 
559                 oname ? oname : "<null>");
560       exit (1);
561     case FPOINTER:
562       return GPTYPE_FAR;
563     case CPOINTER:
564       return GPTYPE_CODE;
565     case PPOINTER:
566       return GPTYPE_XSTACK;
567     default:
568       fprintf (stderr, "*** internal error: unknown pointer type %d in GPByte.\n",
569                p_type);
570       break;
571     }
572   return -1;
573 }
574
575
576 /*-----------------------------------------------------------------*/
577 /* printPointerType - generates ival for pointer type              */
578 /*-----------------------------------------------------------------*/
579 void 
580 _printPointerType (FILE * oFile, const char *name)
581 {
582   if (options.model == MODEL_FLAT24)
583     {
584       fprintf (oFile, "\t.byte %s,(%s >> 8),(%s >> 16)", name, name, name);
585     }
586   else
587     {
588       fprintf (oFile, "\t.byte %s,(%s >> 8)", name, name);
589     }
590 }
591
592 /*-----------------------------------------------------------------*/
593 /* printPointerType - generates ival for pointer type              */
594 /*-----------------------------------------------------------------*/
595 void 
596 printPointerType (FILE * oFile, const char *name)
597 {
598   _printPointerType (oFile, name);
599   fprintf (oFile, "\n");
600 }
601
602 /*-----------------------------------------------------------------*/
603 /* printGPointerType - generates ival for generic pointer type     */
604 /*-----------------------------------------------------------------*/
605 void 
606 printGPointerType (FILE * oFile, const char *iname, const char *oname,
607                    const unsigned int type)
608 {
609   _printPointerType (oFile, iname);
610   fprintf (oFile, ",#0x%02x\n", pointerTypeToGPByte (type, iname, oname));
611 }
612
613 /*-----------------------------------------------------------------*/
614 /* printIvalType - generates ival for int/char                     */
615 /*-----------------------------------------------------------------*/
616 void 
617 printIvalType (symbol *sym, sym_link * type, initList * ilist, FILE * oFile)
618 {
619         value *val;
620
621         /* if initList is deep */
622         if (ilist->type == INIT_DEEP)
623                 ilist = ilist->init.deep;
624
625         if (!(val = list2val (ilist))) {
626           // assuming a warning has been thrown
627           val=constVal("0");
628         }
629
630         if (val->type != type) {
631           val = valCastLiteral(type, floatFromVal(val));
632         }
633         
634         switch (getSize (type)) {
635         case 1:
636                 if (!val)
637                         tfprintf (oFile, "\t!db !constbyte\n", 0);
638                 else
639                         tfprintf (oFile, "\t!dbs\n",
640                                   aopLiteral (val, 0));
641                 break;
642
643         case 2:
644                 if (port->use_dw_for_init)
645                         tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
646                 else
647                         fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
648                 break;
649         case 4:
650                 if (!val) {
651                         tfprintf (oFile, "\t!dw !constword\n", 0);
652                         tfprintf (oFile, "\t!dw !constword\n", 0);
653                 }
654                 else {
655                         fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
656                                  aopLiteral (val, 0), aopLiteral (val, 1),
657                                  aopLiteral (val, 2), aopLiteral (val, 3));
658                 }
659                 break;
660         }
661 }
662
663 /*-----------------------------------------------------------------*/
664 /* printIvalBitFields - generate initializer for bitfields         */
665 /*-----------------------------------------------------------------*/
666 void printIvalBitFields(symbol **sym, initList **ilist, FILE * oFile)
667 {
668         value *val ;
669         symbol *lsym = *sym;
670         initList *lilist = *ilist ;
671         unsigned long ival = 0;
672         int size =0;
673
674         
675         do {
676                 unsigned long i;
677                 val = list2val(lilist);
678                 if (size) {
679                         if (SPEC_BLEN(lsym->etype) > 8) {
680                                 size += ((SPEC_BLEN (lsym->etype) / 8) + 
681                                          (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
682                         }
683                 } else {
684                         size = ((SPEC_BLEN (lsym->etype) / 8) + 
685                                  (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
686                 }
687                 i = (unsigned long)floatFromVal(val);
688                 i <<= SPEC_BSTR (lsym->etype);
689                 ival |= i;
690                 if (! ( lsym->next &&
691                         (IS_BITFIELD(lsym->next->type)) &&
692                         (SPEC_BSTR(lsym->next->etype)))) break;
693                 lsym = lsym->next;
694                 lilist = lilist->next;
695         } while (1);
696         switch (size) {
697         case 1:
698                 tfprintf (oFile, "\t!db !constbyte\n",ival);
699                 break;
700
701         case 2:
702                 tfprintf (oFile, "\t!dw !constword\n",ival);
703                 break;
704         case 4:
705                 tfprintf (oFile, "\t!db  !constword,!constword\n",
706                          (ival >> 8) & 0xffff, (ival & 0xffff));
707                 break;
708         }
709         *sym = lsym;
710         *ilist = lilist;
711 }
712
713 /*-----------------------------------------------------------------*/
714 /* printIvalStruct - generates initial value for structures        */
715 /*-----------------------------------------------------------------*/
716 void 
717 printIvalStruct (symbol * sym, sym_link * type,
718                  initList * ilist, FILE * oFile)
719 {
720         symbol *sflds;
721         initList *iloop;
722
723         sflds = SPEC_STRUCT (type)->fields;
724         if (ilist->type != INIT_DEEP) {
725                 werror (E_INIT_STRUCT, sym->name);
726                 return;
727         }
728
729         iloop = ilist->init.deep;
730
731         for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) {
732                 if (IS_BITFIELD(sflds->type)) {
733                         printIvalBitFields(&sflds,&iloop,oFile);
734                 } else {
735                         printIval (sym, sflds->type, iloop, oFile);
736                 }
737         }
738         if (iloop) {
739           werror (W_EXCESS_INITIALIZERS, "struct", sym->name, sym->lineDef);
740         }
741         return;
742 }
743
744 /*-----------------------------------------------------------------*/
745 /* printIvalChar - generates initital value for character array    */
746 /*-----------------------------------------------------------------*/
747 int 
748 printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s)
749 {
750   value *val;
751   int remain;
752
753   if (!s)
754     {
755
756       val = list2val (ilist);
757       /* if the value is a character string  */
758       if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
759         {
760           if (!DCL_ELEM (type))
761             DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1;
762
763           printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type));
764
765           if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) - 1)) > 0)
766             while (remain--)
767               tfprintf (oFile, "\t!db !constbyte\n", 0);
768
769           return 1;
770         }
771       else
772         return 0;
773     }
774   else
775     printChar (oFile, s, strlen (s) + 1);
776   return 1;
777 }
778
779 /*-----------------------------------------------------------------*/
780 /* printIvalArray - generates code for array initialization        */
781 /*-----------------------------------------------------------------*/
782 void
783 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
784                 FILE * oFile)
785 {
786   initList *iloop;
787   int lcnt = 0, size = 0;
788   sym_link *last_type;
789
790   /* take care of the special   case  */
791   /* array of characters can be init  */
792   /* by a string                      */
793   if (IS_CHAR (type->next)) {
794     if (!IS_LITERAL(list2val(ilist)->etype)) {
795       werror (E_CONST_EXPECTED);
796       return;
797     }
798     if (printIvalChar (type,
799                        (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
800                        oFile, SPEC_CVAL (sym->etype).v_char))
801       return;
802   }
803   /* not the special case             */
804   if (ilist->type != INIT_DEEP)
805     {
806       werror (E_INIT_STRUCT, sym->name);
807       return;
808     }
809
810   iloop = ilist->init.deep;
811   lcnt = DCL_ELEM (type);
812   for (last_type = type->next; 
813        last_type && IS_DECL(last_type) && DCL_ELEM (last_type); 
814        last_type = last_type->next) {
815     lcnt *= DCL_ELEM (last_type);
816   }
817
818   for (;;)
819     {
820       size++;
821       printIval (sym, type->next, iloop, oFile);
822       iloop = (iloop ? iloop->next : NULL);
823
824
825       /* if not array limits given & we */
826       /* are out of initialisers then   */
827       if (!DCL_ELEM (type) && !iloop)
828         break;
829
830       /* no of elements given and we    */
831       /* have generated for all of them */
832       if (!--lcnt) {
833         /* if initializers left */
834         if (iloop) {
835           werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef);
836         }
837         break;
838       }
839     }
840
841   /* if we have not been given a size  */
842   if (!DCL_ELEM (type))
843     DCL_ELEM (type) = size;
844
845   return;
846 }
847
848 /*-----------------------------------------------------------------*/
849 /* printIvalFuncPtr - generate initial value for function pointers */
850 /*-----------------------------------------------------------------*/
851 void 
852 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
853 {
854   value *val;
855   int dLvl = 0;
856
857   val = list2val (ilist);
858
859   if (!val) {
860     // an error has been thrown allready
861     val=constVal("0");
862   }
863
864   if (IS_LITERAL(val->etype)) {
865     if (compareType(type,val->etype)==0) {
866       werror (E_INCOMPAT_TYPES);
867       printFromToType (val->type, type);
868     }
869     printIvalCharPtr (NULL, type, val, oFile);
870     return;
871   }
872
873   /* check the types   */
874   if ((dLvl = compareType (val->type, type->next)) <= 0)
875     {
876       tfprintf (oFile, "\t!dw !constword\n", 0);
877       return;
878     }
879
880   /* now generate the name */
881   if (!val->sym)
882     {
883       if (port->use_dw_for_init)
884         {
885           tfprintf (oFile, "\t!dws\n", val->name);
886         }
887       else
888         {
889           printPointerType (oFile, val->name);
890         }
891     }
892   else if (port->use_dw_for_init)
893     {
894       tfprintf (oFile, "\t!dws\n", val->sym->rname);
895     }
896   else
897     {
898       printPointerType (oFile, val->sym->rname);
899     }
900
901   return;
902 }
903
904 /*-----------------------------------------------------------------*/
905 /* printIvalCharPtr - generates initial values for character pointers */
906 /*-----------------------------------------------------------------*/
907 int 
908 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
909 {
910   int size = 0;
911
912   /* PENDING: this is _very_ mcs51 specific, including a magic
913      number...
914      It's also endin specific.
915    */
916   size = getSize (type);
917
918   if (val->name && strlen (val->name))
919     {
920       if (size == 1)            /* This appears to be Z80 specific?? */
921         {
922           tfprintf (oFile,
923                     "\t!dbs\n", val->name);
924         }
925       else if (size == FPTRSIZE)
926         {
927           if (port->use_dw_for_init)
928             {
929               tfprintf (oFile, "\t!dws\n", val->name);
930             }
931           else
932             {
933               printPointerType (oFile, val->name);
934             }
935         }
936       else if (size == GPTRSIZE)
937         {
938           int type;
939           if (IS_PTR (val->type)) {
940             type = DCL_TYPE (val->type);
941           } else {
942             type = PTR_TYPE (SPEC_OCLS (val->etype));
943           }
944           if (val->sym && val->sym->isstrlit) {
945             // this is a literal string
946             type=CPOINTER;
947           }
948           printGPointerType (oFile, val->name, sym->name, type);
949         }
950       else
951         {
952           fprintf (stderr, "*** internal error: unknown size in "
953                    "printIvalCharPtr.\n");
954         }
955     }
956   else
957     {
958       // these are literals assigned to pointers
959       switch (size)
960         {
961         case 1:
962           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
963           break;
964         case 2:
965           if (port->use_dw_for_init)
966             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
967           else
968             tfprintf (oFile, "\t.byte %s,%s\n",
969                       aopLiteral (val, 0), aopLiteral (val, 1));
970           break;
971         case 3:
972           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
973             // non-zero mcs51 generic pointer
974             werror (E_LITERAL_GENERIC);
975           }
976           fprintf (oFile, "\t.byte %s,%s,%s\n",
977                    aopLiteral (val, 0), 
978                    aopLiteral (val, 1),
979                    aopLiteral (val, 2));
980           break;
981         case 4:
982           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
983             // non-zero ds390 generic pointer
984             werror (E_LITERAL_GENERIC);
985           }
986           fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
987                    aopLiteral (val, 0), 
988                    aopLiteral (val, 1), 
989                    aopLiteral (val, 2),
990                    aopLiteral (val, 3));
991           break;
992         default:
993           assert (0);
994         }
995     }
996
997   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
998     addSet (&statsg->syms, val->sym);
999   }
1000
1001   return 1;
1002 }
1003
1004 /*-----------------------------------------------------------------*/
1005 /* printIvalPtr - generates initial value for pointers             */
1006 /*-----------------------------------------------------------------*/
1007 void 
1008 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1009 {
1010   value *val;
1011   int size;
1012
1013   /* if deep then   */
1014   if (ilist->type == INIT_DEEP)
1015     ilist = ilist->init.deep;
1016
1017   /* function pointer     */
1018   if (IS_FUNC (type->next))
1019     {
1020       printIvalFuncPtr (type, ilist, oFile);
1021       return;
1022     }
1023
1024   if (!(val = initPointer (ilist, type)))
1025     return;
1026
1027   /* if character pointer */
1028   if (IS_CHAR (type->next))
1029     if (printIvalCharPtr (sym, type, val, oFile))
1030       return;
1031
1032   /* check the type      */
1033   if (compareType (type, val->type) == 0) {
1034     werror (W_INIT_WRONG);
1035     printFromToType (val->type, type);
1036   }
1037
1038   /* if val is literal */
1039   if (IS_LITERAL (val->etype))
1040     {
1041       switch (getSize (type))
1042         {
1043         case 1:
1044           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
1045           break;
1046         case 2:
1047           if (port->use_dw_for_init)
1048             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
1049           else
1050             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1051           break;
1052         case 3: // how about '390??
1053           fprintf (oFile, "\t.byte %s,%s,#0x%d\n",
1054                    aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE);
1055         }
1056       return;
1057     }
1058
1059
1060   size = getSize (type);
1061
1062   if (size == 1)                /* Z80 specific?? */
1063     {
1064       tfprintf (oFile, "\t!dbs\n", val->name);
1065     }
1066   else if (size == FPTRSIZE)
1067     {
1068       if (port->use_dw_for_init) {
1069         tfprintf (oFile, "\t!dws\n", val->name);
1070       } else {
1071         printPointerType (oFile, val->name);
1072       }
1073     }
1074   else if (size == GPTRSIZE)
1075     {
1076       printGPointerType (oFile, val->name, sym->name,
1077                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1078                           PTR_TYPE (SPEC_OCLS (val->etype))));
1079     }
1080   return;
1081 }
1082
1083 /*-----------------------------------------------------------------*/
1084 /* printIval - generates code for initial value                    */
1085 /*-----------------------------------------------------------------*/
1086 void 
1087 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1088 {
1089   value *val;
1090   
1091   if (!ilist)
1092     return;
1093
1094   /* update line number for error msgs */
1095   lineno=sym->lineDef;
1096
1097   /* if structure then    */
1098   if (IS_STRUCT (type))
1099     {
1100       printIvalStruct (sym, type, ilist, oFile);
1101       return;
1102     }
1103
1104   /* if this is an array   */
1105   if (IS_ARRAY (type))
1106     {
1107       printIvalArray (sym, type, ilist, oFile);
1108       return;
1109     }
1110
1111   // not an aggregate, ilist must be a node
1112   if (ilist->type!=INIT_NODE &&
1113       // or a 1-element list
1114       ilist->init.deep->next) {
1115     werror (W_EXCESS_INITIALIZERS, "scalar", 
1116             sym->name, sym->lineDef);
1117   }
1118
1119   // and the type must match
1120   val=list2val(ilist);
1121   if (compareType(type, val->type)==0) {
1122     // special case for literal strings
1123     if (IS_ARRAY (val->type) && IS_CHAR (val->etype) &&
1124         // which are really code pointers
1125         IS_PTR(type) && DCL_TYPE(type)==CPOINTER) {
1126       // no sweat
1127     } else {
1128       werror (E_TYPE_MISMATCH, "assignment", " ");
1129       printFromToType(list2val(ilist)->type, type);
1130     }
1131   }
1132
1133   /* if this is a pointer */
1134   if (IS_PTR (type))
1135     {
1136       printIvalPtr (sym, type, ilist, oFile);
1137       return;
1138     }
1139
1140   /* if type is SPECIFIER */
1141   if (IS_SPEC (type))
1142     {
1143       printIvalType (sym, type, ilist, oFile);
1144       return;
1145     }
1146 }
1147
1148 /*-----------------------------------------------------------------*/
1149 /* emitStaticSeg - emitcode for the static segment                 */
1150 /*-----------------------------------------------------------------*/
1151 void 
1152 emitStaticSeg (memmap * map, FILE * out)
1153 {
1154   symbol *sym;
1155
1156   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1157
1158   /* for all variables in this segment do */
1159   for (sym = setFirstItem (map->syms); sym;
1160        sym = setNextItem (map->syms))
1161     {
1162
1163       /* if it is "extern" then do nothing */
1164       if (IS_EXTERN (sym->etype))
1165         continue;
1166
1167       /* if it is not static add it to the public
1168          table */
1169       if (!IS_STATIC (sym->etype))
1170         {
1171           addSetHead (&publics, sym);
1172         }
1173
1174       /* print extra debug info if required */
1175       if (options.debug) {
1176
1177         if (!sym->level)
1178           {                     /* global */
1179             if (IS_STATIC (sym->etype))
1180               fprintf (out, "F%s$", moduleName);        /* scope is file */
1181             else
1182               fprintf (out, "G$");      /* scope is global */
1183           }
1184         else
1185           /* symbol is local */
1186           fprintf (out, "L%s$",
1187                    (sym->localof ? sym->localof->name : "-null-"));
1188         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1189       }
1190       
1191       /* if it has an absolute address */
1192       if (SPEC_ABSA (sym->etype))
1193         {
1194           if (options.debug)
1195             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1196           
1197           fprintf (out, "%s\t=\t0x%04x\n",
1198                    sym->rname,
1199                    SPEC_ADDR (sym->etype));
1200         }
1201       else
1202         {
1203           if (options.debug)
1204             fprintf (out, " == .\n");
1205           
1206           /* if it has an initial value */
1207           if (sym->ival)
1208             {
1209               fprintf (out, "%s:\n", sym->rname);
1210               noAlloc++;
1211               resolveIvalSym (sym->ival);
1212               printIval (sym, sym->type, sym->ival, out);
1213               noAlloc--;
1214               /* if sym is a simple string and sym->ival is a string, 
1215                  WE don't need it anymore */
1216               if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) &&
1217                   IS_AST_SYM_VALUE(list2expr(sym->ival)) &&
1218                   list2val(sym->ival)->sym->isstrlit) {
1219                 freeStringSymbol(list2val(sym->ival)->sym);
1220               }
1221             }
1222           else {
1223               /* allocate space */
1224               int size = getSize (sym->type);
1225               
1226               if (size==0) {
1227                   werror(E_UNKNOWN_SIZE,sym->name);
1228               }
1229               fprintf (out, "%s:\n", sym->rname);
1230               /* special case for character strings */
1231               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1232                   SPEC_CVAL (sym->etype).v_char)
1233                   printChar (out,
1234                              SPEC_CVAL (sym->etype).v_char,
1235                              strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1236               else
1237                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1238             }
1239         }
1240     }
1241 }
1242
1243 /*-----------------------------------------------------------------*/
1244 /* emitMaps - emits the code for the data portion the code         */
1245 /*-----------------------------------------------------------------*/
1246 void 
1247 emitMaps (void)
1248 {
1249   inInitMode++;
1250   /* no special considerations for the following
1251      data, idata & bit & xdata */
1252   emitRegularMap (data, TRUE, TRUE);
1253   emitRegularMap (idata, TRUE, TRUE);
1254   emitRegularMap (bit, TRUE, FALSE);
1255   emitRegularMap (xdata, TRUE, TRUE);
1256   if (port->genXINIT) {
1257     emitRegularMap (xidata, TRUE, TRUE);
1258   }
1259   emitRegularMap (sfr, FALSE, FALSE);
1260   emitRegularMap (sfrbit, FALSE, FALSE);
1261   emitRegularMap (home, TRUE, FALSE);
1262   emitRegularMap (code, TRUE, FALSE);
1263
1264   emitStaticSeg (statsg, code->oFile);
1265   if (port->genXINIT) {
1266     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1267     emitStaticSeg (xinit, code->oFile);
1268   }
1269   inInitMode--;
1270 }
1271
1272 /*-----------------------------------------------------------------*/
1273 /* flushStatics - flush all currently defined statics out to file  */
1274 /*  and delete.  Temporary function                                */
1275 /*-----------------------------------------------------------------*/
1276 void 
1277 flushStatics (void)
1278 {
1279   emitStaticSeg (statsg, codeOutFile);
1280   statsg->syms = NULL;
1281 }
1282
1283 /*-----------------------------------------------------------------*/
1284 /* createInterruptVect - creates the interrupt vector              */
1285 /*-----------------------------------------------------------------*/
1286 void 
1287 createInterruptVect (FILE * vFile)
1288 {
1289   unsigned i = 0;
1290   mainf = newSymbol ("main", 0);
1291   mainf->block = 0;
1292
1293   /* only if the main function exists */
1294   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1295     {
1296       if (!options.cc_only && !noAssemble && !options.c1mode)
1297         werror (E_NO_MAIN);
1298       return;
1299     }
1300
1301   /* if the main is only a prototype ie. no body then do nothing */
1302   if (!IFFUNC_HASBODY(mainf->type))
1303     {
1304       /* if ! compile only then main function should be present */
1305       if (!options.cc_only && !noAssemble)
1306         werror (E_NO_MAIN);
1307       return;
1308     }
1309
1310   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1311   fprintf (vFile, "__interrupt_vect:\n");
1312
1313
1314   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1315     {
1316       /* "generic" interrupt table header (if port doesn't specify one).
1317        * Look suspiciously like 8051 code to me...
1318        */
1319
1320       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1321
1322
1323       /* now for the other interrupts */
1324       for (; i < maxInterrupts; i++)
1325         {
1326           if (interrupts[i])
1327             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1328           else
1329             fprintf (vFile, "\treti\n\t.ds\t7\n");
1330         }
1331     }
1332 }
1333
1334 char *iComments1 =
1335 {
1336   ";--------------------------------------------------------\n"
1337   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1338
1339 char *iComments2 =
1340 {
1341   ";--------------------------------------------------------\n"};
1342
1343
1344 /*-----------------------------------------------------------------*/
1345 /* initialComments - puts in some initial comments                 */
1346 /*-----------------------------------------------------------------*/
1347 void 
1348 initialComments (FILE * afile)
1349 {
1350   time_t t;
1351   time (&t);
1352   fprintf (afile, "%s", iComments1);
1353   fprintf (afile, "; Version " SDCC_VERSION_STR " %s\n", asctime (localtime (&t)));
1354   fprintf (afile, "%s", iComments2);
1355 }
1356
1357 /*-----------------------------------------------------------------*/
1358 /* printPublics - generates .global for publics                    */
1359 /*-----------------------------------------------------------------*/
1360 void 
1361 printPublics (FILE * afile)
1362 {
1363   symbol *sym;
1364
1365   fprintf (afile, "%s", iComments2);
1366   fprintf (afile, "; Public variables in this module\n");
1367   fprintf (afile, "%s", iComments2);
1368
1369   for (sym = setFirstItem (publics); sym;
1370        sym = setNextItem (publics))
1371     tfprintf (afile, "\t!global\n", sym->rname);
1372 }
1373
1374 /*-----------------------------------------------------------------*/
1375 /* printExterns - generates .global for externs                    */
1376 /*-----------------------------------------------------------------*/
1377 void 
1378 printExterns (FILE * afile)
1379 {
1380   symbol *sym;
1381
1382   fprintf (afile, "%s", iComments2);
1383   fprintf (afile, "; Externals used\n");
1384   fprintf (afile, "%s", iComments2);
1385
1386   for (sym = setFirstItem (externs); sym;
1387        sym = setNextItem (externs))
1388     tfprintf (afile, "\t!extern\n", sym->rname);
1389 }
1390
1391 /*-----------------------------------------------------------------*/
1392 /* emitOverlay - will emit code for the overlay stuff              */
1393 /*-----------------------------------------------------------------*/
1394 static void 
1395 emitOverlay (FILE * afile)
1396 {
1397   set *ovrset;
1398
1399   if (!elementsInSet (ovrSetSets))
1400     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1401
1402   /* for each of the sets in the overlay segment do */
1403   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1404        ovrset = setNextItem (ovrSetSets))
1405     {
1406
1407       symbol *sym;
1408
1409       if (elementsInSet (ovrset))
1410         {
1411           /* output the area informtion */
1412           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1413         }
1414
1415       for (sym = setFirstItem (ovrset); sym;
1416            sym = setNextItem (ovrset))
1417         {
1418           /* if extern then it is in the publics table: do nothing */
1419           if (IS_EXTERN (sym->etype))
1420             continue;
1421
1422           /* if allocation required check is needed
1423              then check if the symbol really requires
1424              allocation only for local variables */
1425           if (!IS_AGGREGATE (sym->type) &&
1426               !(sym->_isparm && !IS_REGPARM (sym->etype))
1427               && !sym->allocreq && sym->level)
1428             continue;
1429
1430           /* if global variable & not static or extern
1431              and addPublics allowed then add it to the public set */
1432           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1433               && !IS_STATIC (sym->etype))
1434             {
1435               addSetHead (&publics, sym);
1436             }
1437
1438           /* if extern then do nothing or is a function
1439              then do nothing */
1440           if (IS_FUNC (sym->type))
1441             continue;
1442
1443           /* print extra debug info if required */
1444           if (options.debug)
1445             {
1446               if (!sym->level)
1447                 {               /* global */
1448                   if (IS_STATIC (sym->etype))
1449                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1450                   else
1451                     fprintf (afile, "G$");      /* scope is global */
1452                 }
1453               else
1454                 /* symbol is local */
1455                 fprintf (afile, "L%s$",
1456                          (sym->localof ? sym->localof->name : "-null-"));
1457               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1458             }
1459
1460           /* if is has an absolute address then generate
1461              an equate for this no need to allocate space */
1462           if (SPEC_ABSA (sym->etype))
1463             {
1464
1465               if (options.debug)
1466                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1467
1468               fprintf (afile, "%s\t=\t0x%04x\n",
1469                        sym->rname,
1470                        SPEC_ADDR (sym->etype));
1471             }
1472           else {
1473               int size = getSize(sym->type);
1474
1475               if (size==0) {
1476                   werror(E_UNKNOWN_SIZE,sym->name);
1477               }       
1478               if (options.debug)
1479                   fprintf (afile, "==.\n");
1480               
1481               /* allocate space */
1482               tfprintf (afile, "!labeldef\n", sym->rname);
1483               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1484           }
1485           
1486         }
1487     }
1488 }
1489
1490
1491 /*-----------------------------------------------------------------*/
1492 /* spacesToUnderscores - replace spaces with underscores        */
1493 /*-----------------------------------------------------------------*/
1494 static char *
1495 spacesToUnderscores (char *dest, const char *src, size_t len)
1496 {
1497   int i;
1498   char *p;
1499
1500   assert(dest != NULL);
1501   assert(src != NULL);
1502   assert(len > 0);
1503
1504   --len;
1505   for (p = dest, i = 0; *src != '\0' && i < len; ++src, ++i) {
1506     *p++ = isspace(*src) ? '_' : *src;
1507   }
1508   *p = '\0';
1509
1510   return dest;
1511 }
1512
1513
1514 /*-----------------------------------------------------------------*/
1515 /* glue - the final glue that hold the whole thing together        */
1516 /*-----------------------------------------------------------------*/
1517 void 
1518 glue (void)
1519 {
1520   FILE *vFile;
1521   FILE *asmFile;
1522   FILE *ovrFile = tempfile ();
1523   char moduleBuf[PATH_MAX];
1524
1525   addSetHead (&tmpfileSet, ovrFile);
1526   /* print the global struct definitions */
1527   if (options.debug)
1528     cdbStructBlock (0);
1529
1530   vFile = tempfile ();
1531   /* PENDING: this isnt the best place but it will do */
1532   if (port->general.glue_up_main)
1533     {
1534       /* create the interrupt vector table */
1535       createInterruptVect (vFile);
1536     }
1537
1538   addSetHead (&tmpfileSet, vFile);
1539
1540   /* emit code for the all the variables declared */
1541   emitMaps ();
1542   /* do the overlay segments */
1543   emitOverlay (ovrFile);
1544
1545   outputDebugSymbols();
1546
1547   /* now put it all together into the assembler file */
1548   /* create the assembler file name */
1549
1550   /* -o option overrides default name? */
1551   if ((noAssemble || options.c1mode) && fullDstFileName)
1552     {
1553       strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1554     }
1555   else
1556     {
1557       strncpyz (scratchFileName, dstFileName, PATH_MAX);
1558       strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1559     }
1560
1561   if (!(asmFile = fopen (scratchFileName, "w")))
1562     {
1563       werror (E_FILE_OPEN_ERR, scratchFileName);
1564       exit (1);
1565     }
1566
1567   /* initial comments */
1568   initialComments (asmFile);
1569
1570   /* print module name */
1571   tfprintf (asmFile, "\t!module\n",
1572     spacesToUnderscores (moduleBuf, moduleName, sizeof moduleBuf));
1573   tfprintf (asmFile, "\t!fileprelude\n");
1574
1575   /* Let the port generate any global directives, etc. */
1576   if (port->genAssemblerPreamble)
1577     {
1578       port->genAssemblerPreamble (asmFile);
1579     }
1580
1581   /* print the global variables in this module */
1582   printPublics (asmFile);
1583   if (port->assembler.externGlobal)
1584     printExterns (asmFile);
1585
1586   /* copy the sfr segment */
1587   fprintf (asmFile, "%s", iComments2);
1588   fprintf (asmFile, "; special function registers\n");
1589   fprintf (asmFile, "%s", iComments2);
1590   copyFile (asmFile, sfr->oFile);
1591
1592   /* copy the sbit segment */
1593   fprintf (asmFile, "%s", iComments2);
1594   fprintf (asmFile, "; special function bits \n");
1595   fprintf (asmFile, "%s", iComments2);
1596   copyFile (asmFile, sfrbit->oFile);
1597   
1598   /*JCF: Create the areas for the register banks*/
1599   if(port->general.glue_up_main &&
1600      (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51 || TARGET_IS_DS400))
1601   {
1602           if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1603           {
1604                  fprintf (asmFile, "%s", iComments2);
1605                  fprintf (asmFile, "; overlayable register banks \n");
1606                  fprintf (asmFile, "%s", iComments2);
1607                  if(RegBankUsed[0])
1608                         fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1609                  if(RegBankUsed[1]||options.parms_in_bank1)
1610                         fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1611                  if(RegBankUsed[2])
1612                         fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1613                  if(RegBankUsed[3])
1614                         fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1615           }
1616   }
1617
1618   /* copy the data segment */
1619   fprintf (asmFile, "%s", iComments2);
1620   fprintf (asmFile, "; internal ram data\n");
1621   fprintf (asmFile, "%s", iComments2);
1622   copyFile (asmFile, data->oFile);
1623
1624
1625   /* create the overlay segments */
1626   if (overlay) {
1627     fprintf (asmFile, "%s", iComments2);
1628     fprintf (asmFile, "; overlayable items in internal ram \n");
1629     fprintf (asmFile, "%s", iComments2);
1630     copyFile (asmFile, ovrFile);
1631   }
1632
1633   /* create the stack segment MOF */
1634   if (mainf && IFFUNC_HASBODY(mainf->type))
1635     {
1636       fprintf (asmFile, "%s", iComments2);
1637       fprintf (asmFile, "; Stack segment in internal ram \n");
1638       fprintf (asmFile, "%s", iComments2);
1639       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1640                "__start__stack:\n\t.ds\t1\n\n");
1641     }
1642
1643   /* create the idata segment */
1644   if (idata) {
1645     fprintf (asmFile, "%s", iComments2);
1646     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1647     fprintf (asmFile, "%s", iComments2);
1648     copyFile (asmFile, idata->oFile);
1649   }
1650
1651   /* copy the bit segment */
1652   fprintf (asmFile, "%s", iComments2);
1653   fprintf (asmFile, "; bit data\n");
1654   fprintf (asmFile, "%s", iComments2);
1655   copyFile (asmFile, bit->oFile);
1656
1657   /* if external stack then reserve space of it */
1658   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1659     {
1660       fprintf (asmFile, "%s", iComments2);
1661       fprintf (asmFile, "; external stack \n");
1662       fprintf (asmFile, "%s", iComments2);
1663       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1664       fprintf (asmFile, "\t.ds 256\n");
1665     }
1666
1667
1668   /* copy xtern ram data */
1669   fprintf (asmFile, "%s", iComments2);
1670   fprintf (asmFile, "; external ram data\n");
1671   fprintf (asmFile, "%s", iComments2);
1672   copyFile (asmFile, xdata->oFile);
1673
1674   /* copy xternal initialized ram data */
1675   fprintf (asmFile, "%s", iComments2);
1676   fprintf (asmFile, "; external initialized ram data\n");
1677   fprintf (asmFile, "%s", iComments2);
1678   copyFile (asmFile, xidata->oFile);
1679
1680   /* copy the interrupt vector table */
1681   if (mainf && IFFUNC_HASBODY(mainf->type))
1682     {
1683       fprintf (asmFile, "%s", iComments2);
1684       fprintf (asmFile, "; interrupt vector \n");
1685       fprintf (asmFile, "%s", iComments2);
1686       copyFile (asmFile, vFile);
1687     }
1688
1689   /* copy global & static initialisations */
1690   fprintf (asmFile, "%s", iComments2);
1691   fprintf (asmFile, "; global & static initialisations\n");
1692   fprintf (asmFile, "%s", iComments2);
1693
1694   /* Everywhere we generate a reference to the static_name area,
1695    * (which is currently only here), we immediately follow it with a
1696    * definition of the post_static_name area. This guarantees that
1697    * the post_static_name area will immediately follow the static_name
1698    * area.
1699    */
1700   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1701   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1702   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1703
1704   if (mainf && IFFUNC_HASBODY(mainf->type))
1705     {
1706       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1707       /* if external stack is specified then the
1708          higher order byte of the xdatalocation is
1709          going into P2 and the lower order going into
1710          spx */
1711       if (options.useXstack)
1712         {
1713           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1714                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1715           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1716                    (unsigned int) options.xdata_loc & 0xff);
1717         }
1718
1719         // This should probably be a port option, but I'm being lazy.
1720         // on the 400, the firmware boot loader gives us a valid stack
1721         // (see '400 data sheet pg. 85 (TINI400 ROM Initialization code)
1722         if (!TARGET_IS_DS400)
1723         {
1724             /* initialise the stack pointer.  JCF: aslink takes care of the location */
1725             fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");       /* MOF */
1726         }
1727
1728       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1729       fprintf (asmFile, "\tmov\ta,dpl\n");
1730       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1731       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1732       fprintf (asmFile, "__sdcc_init_data:\n");
1733
1734       // if the port can copy the XINIT segment to XISEG
1735       if (port->genXINIT) {
1736         port->genXINIT(asmFile);
1737       }
1738
1739     }
1740   copyFile (asmFile, statsg->oFile);
1741
1742   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1743     {
1744       /* This code is generated in the post-static area.
1745        * This area is guaranteed to follow the static area
1746        * by the ugly shucking and jiving about 20 lines ago.
1747        */
1748       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1749       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1750     }
1751
1752   fprintf (asmFile,
1753            "%s"
1754            "; Home\n"
1755            "%s", iComments2, iComments2);
1756   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1757   copyFile (asmFile, home->oFile);
1758
1759   /* copy over code */
1760   fprintf (asmFile, "%s", iComments2);
1761   fprintf (asmFile, "; code\n");
1762   fprintf (asmFile, "%s", iComments2);
1763   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1764   if (mainf && IFFUNC_HASBODY(mainf->type))
1765     {
1766
1767       /* entry point @ start of CSEG */
1768       fprintf (asmFile, "__sdcc_program_startup:\n");
1769
1770       /* put in the call to main */
1771       fprintf (asmFile, "\tlcall\t_main\n");
1772       if (options.mainreturn)
1773         {
1774
1775           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1776           fprintf (asmFile, "\tret\n");
1777
1778         }
1779       else
1780         {
1781
1782           fprintf (asmFile, ";\treturn from main will lock up\n");
1783           fprintf (asmFile, "\tsjmp .\n");
1784         }
1785     }
1786   copyFile (asmFile, code->oFile);
1787
1788   if (port->genAssemblerEnd) {
1789       port->genAssemblerEnd(asmFile);
1790   }
1791   fclose (asmFile);
1792
1793   rm_tmpfiles ();
1794 }
1795
1796
1797 /** Creates a temporary file with unoque file name
1798     Scans, in order:
1799     - TMP, TEMP, TMPDIR env. varibles
1800     - if Un*x system: /usr/tmp and /tmp
1801     - root directory using mkstemp() if avaliable
1802     - default location using tempnam()
1803 */
1804 static int
1805 tempfileandname(char *fname, size_t len)
1806 {
1807 #define TEMPLATE      "sdccXXXXXX"
1808 #define TEMPLATE_LEN  ((sizeof TEMPLATE) - 1)
1809
1810   const char *tmpdir = NULL;
1811   int fd;
1812
1813   if ((tmpdir = getenv ("TMP")) == NULL)
1814     if ((tmpdir = getenv ("TEMP")) == NULL)
1815       tmpdir = getenv ("TMPDIR");
1816
1817 #ifndef _WIN32
1818   {
1819     /* try with /usr/tmp and /tmp on Un*x systems */
1820     struct stat statbuf;
1821
1822     if (tmpdir == NULL) {
1823       if (stat("/usr/tmp", &statbuf) != -1)
1824         tmpdir = "/usr/tmp";
1825       else if (stat("/tmp", &statbuf) != -1)
1826         tmpdir = "/tmp";
1827     }
1828   }
1829 #endif
1830
1831 #ifdef HAVE_MKSTEMP
1832   {
1833     char fnamebuf[PATH_MAX];
1834     size_t name_len;
1835
1836     if (fname == NULL || len == 0) {
1837       fname = fnamebuf;
1838       len = sizeof fnamebuf;
1839     }
1840
1841     if (tmpdir) {
1842       name_len = strlen(tmpdir) + 1 + TEMPLATE_LEN;
1843
1844       assert(name_len < len);
1845       if (!(name_len < len))  /* in NDEBUG is defined */
1846         return -1;            /* buffer too small, temporary file can not be created */
1847
1848       sprintf(fname, "%s" DIR_SEPARATOR_STRING TEMPLATE, tmpdir);
1849     }
1850     else {
1851       name_len = TEMPLATE_LEN;
1852
1853       assert(name_len < len);
1854       if (!(name_len < len))  /* in NDEBUG is defined */
1855         return -1;            /* buffer too small, temporary file can not be created */
1856
1857       strcpy(fname, TEMPLATE);
1858     }
1859
1860     fd = mkstemp(fname);
1861   }
1862 #else
1863   {
1864     char *name = tempnam(tmpdir, "sdcc");
1865
1866     if (name == NULL) {
1867       perror("Can't create temporary file name");
1868       exit(1);
1869     }
1870
1871     assert(strlen(name) < len);
1872     if (!(strlen(name) < len))  /* in NDEBUG is defined */
1873       return -1;                /* buffer too small, temporary file can not be created */
1874
1875     strcpy(fname, name);
1876 #ifdef _WIN32
1877     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IREAD | S_IWRITE);
1878 #else
1879     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IRUSR | S_IWUSR);
1880 #endif
1881   }
1882 #endif
1883
1884   if (fd == -1) {
1885     perror("Can't create temporary file");
1886     exit(1);
1887   }
1888
1889   return fd;
1890 }
1891
1892
1893 /** Create a temporary file name
1894 */
1895 char *
1896 tempfilename(void)
1897 {
1898   int fd;
1899   static char fnamebuf[PATH_MAX];
1900
1901   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1902     fprintf(stderr, "Can't create temporary file name!");
1903     exit(1);
1904   }
1905
1906   fd = close(fd);
1907   assert(fd != -1);
1908
1909   return fnamebuf;
1910 }
1911
1912
1913 /** Create a temporary file and add it to tmpfileNameSet,
1914     so that it is removed explicitly by rm_tmpfiles()
1915     or implicitly at program extit.
1916 */
1917 FILE *
1918 tempfile(void)
1919 {
1920   int fd;
1921   char *tmp;
1922   FILE *fp;
1923   char fnamebuf[PATH_MAX];
1924
1925   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1926     fprintf(stderr, "Can't create temporary file!");
1927     exit(1);
1928   }
1929
1930   tmp = Safe_strdup(fnamebuf);
1931   if (tmp)
1932     addSetHead(&tmpfileNameSet, tmp);
1933
1934   if ((fp = fdopen(fd, "w+b")) == NULL) {
1935       perror("Can't create temporary file!");
1936       exit(1);
1937   }
1938
1939   return fp;
1940 }