Linker complaints if linked modules have conflicting options.
[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 size = 0;
788
789   /* take care of the special   case  */
790   /* array of characters can be init  */
791   /* by a string                      */
792   if (IS_CHAR (type->next)) {
793     if (!IS_LITERAL(list2val(ilist)->etype)) {
794       werror (E_CONST_EXPECTED);
795       return;
796     }
797     if (printIvalChar (type,
798                        (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
799                        oFile, SPEC_CVAL (sym->etype).v_char))
800       return;
801   }
802   /* not the special case             */
803   if (ilist->type != INIT_DEEP)
804     {
805       werror (E_INIT_STRUCT, sym->name);
806       return;
807     }
808
809   for (iloop=ilist->init.deep; iloop; iloop=iloop->next)
810     {
811       printIval (sym, type->next, iloop, oFile);
812       
813       if (++size > DCL_ELEM(type)) {
814         werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef);
815         break;
816       }
817     }
818   
819   if (DCL_ELEM(type)) {
820     // pad with zeros if needed
821     if (size<DCL_ELEM(type)) {
822       size = (DCL_ELEM(type) - size) * getSize(type->next);
823       while (size--) {
824         tfprintf (oFile, "\t!db !constbyte\n", 0);
825       }
826     }
827   } else {
828     // we have not been given a size, but we now know it
829     DCL_ELEM (type) = size;
830   }
831
832   return;
833 }
834
835 /*-----------------------------------------------------------------*/
836 /* printIvalFuncPtr - generate initial value for function pointers */
837 /*-----------------------------------------------------------------*/
838 void 
839 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
840 {
841   value *val;
842   int dLvl = 0;
843
844   val = list2val (ilist);
845
846   if (!val) {
847     // an error has been thrown allready
848     val=constVal("0");
849   }
850
851   if (IS_LITERAL(val->etype)) {
852     if (compareType(type,val->etype)==0) {
853       werror (E_INCOMPAT_TYPES);
854       printFromToType (val->type, type);
855     }
856     printIvalCharPtr (NULL, type, val, oFile);
857     return;
858   }
859
860   /* check the types   */
861   if ((dLvl = compareType (val->type, type->next)) <= 0)
862     {
863       tfprintf (oFile, "\t!dw !constword\n", 0);
864       return;
865     }
866
867   /* now generate the name */
868   if (!val->sym)
869     {
870       if (port->use_dw_for_init)
871         {
872           tfprintf (oFile, "\t!dws\n", val->name);
873         }
874       else
875         {
876           printPointerType (oFile, val->name);
877         }
878     }
879   else if (port->use_dw_for_init)
880     {
881       tfprintf (oFile, "\t!dws\n", val->sym->rname);
882     }
883   else
884     {
885       printPointerType (oFile, val->sym->rname);
886     }
887
888   return;
889 }
890
891 /*-----------------------------------------------------------------*/
892 /* printIvalCharPtr - generates initial values for character pointers */
893 /*-----------------------------------------------------------------*/
894 int 
895 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
896 {
897   int size = 0;
898
899   /* PENDING: this is _very_ mcs51 specific, including a magic
900      number...
901      It's also endin specific.
902    */
903   size = getSize (type);
904
905   if (val->name && strlen (val->name))
906     {
907       if (size == 1)            /* This appears to be Z80 specific?? */
908         {
909           tfprintf (oFile,
910                     "\t!dbs\n", val->name);
911         }
912       else if (size == FPTRSIZE)
913         {
914           if (port->use_dw_for_init)
915             {
916               tfprintf (oFile, "\t!dws\n", val->name);
917             }
918           else
919             {
920               printPointerType (oFile, val->name);
921             }
922         }
923       else if (size == GPTRSIZE)
924         {
925           int type;
926           if (IS_PTR (val->type)) {
927             type = DCL_TYPE (val->type);
928           } else {
929             type = PTR_TYPE (SPEC_OCLS (val->etype));
930           }
931           if (val->sym && val->sym->isstrlit) {
932             // this is a literal string
933             type=CPOINTER;
934           }
935           printGPointerType (oFile, val->name, sym->name, type);
936         }
937       else
938         {
939           fprintf (stderr, "*** internal error: unknown size in "
940                    "printIvalCharPtr.\n");
941         }
942     }
943   else
944     {
945       // these are literals assigned to pointers
946       switch (size)
947         {
948         case 1:
949           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
950           break;
951         case 2:
952           if (port->use_dw_for_init)
953             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
954           else
955             tfprintf (oFile, "\t.byte %s,%s\n",
956                       aopLiteral (val, 0), aopLiteral (val, 1));
957           break;
958         case 3:
959           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
960             // non-zero mcs51 generic pointer
961             werror (E_LITERAL_GENERIC);
962           }
963           fprintf (oFile, "\t.byte %s,%s,%s\n",
964                    aopLiteral (val, 0), 
965                    aopLiteral (val, 1),
966                    aopLiteral (val, 2));
967           break;
968         case 4:
969           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
970             // non-zero ds390 generic pointer
971             werror (E_LITERAL_GENERIC);
972           }
973           fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
974                    aopLiteral (val, 0), 
975                    aopLiteral (val, 1), 
976                    aopLiteral (val, 2),
977                    aopLiteral (val, 3));
978           break;
979         default:
980           assert (0);
981         }
982     }
983
984   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
985     addSet (&statsg->syms, val->sym);
986   }
987
988   return 1;
989 }
990
991 /*-----------------------------------------------------------------*/
992 /* printIvalPtr - generates initial value for pointers             */
993 /*-----------------------------------------------------------------*/
994 void 
995 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
996 {
997   value *val;
998   int size;
999
1000   /* if deep then   */
1001   if (ilist->type == INIT_DEEP)
1002     ilist = ilist->init.deep;
1003
1004   /* function pointer     */
1005   if (IS_FUNC (type->next))
1006     {
1007       printIvalFuncPtr (type, ilist, oFile);
1008       return;
1009     }
1010
1011   if (!(val = initPointer (ilist, type)))
1012     return;
1013
1014   /* if character pointer */
1015   if (IS_CHAR (type->next))
1016     if (printIvalCharPtr (sym, type, val, oFile))
1017       return;
1018
1019   /* check the type      */
1020   if (compareType (type, val->type) == 0) {
1021     werror (W_INIT_WRONG);
1022     printFromToType (val->type, type);
1023   }
1024
1025   /* if val is literal */
1026   if (IS_LITERAL (val->etype))
1027     {
1028       switch (getSize (type))
1029         {
1030         case 1:
1031           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
1032           break;
1033         case 2:
1034           if (port->use_dw_for_init)
1035             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
1036           else
1037             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1038           break;
1039         case 3: // how about '390??
1040           fprintf (oFile, "\t.byte %s,%s,#0x%d\n",
1041                    aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE);
1042         }
1043       return;
1044     }
1045
1046
1047   size = getSize (type);
1048
1049   if (size == 1)                /* Z80 specific?? */
1050     {
1051       tfprintf (oFile, "\t!dbs\n", val->name);
1052     }
1053   else if (size == FPTRSIZE)
1054     {
1055       if (port->use_dw_for_init) {
1056         tfprintf (oFile, "\t!dws\n", val->name);
1057       } else {
1058         printPointerType (oFile, val->name);
1059       }
1060     }
1061   else if (size == GPTRSIZE)
1062     {
1063       printGPointerType (oFile, val->name, sym->name,
1064                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1065                           PTR_TYPE (SPEC_OCLS (val->etype))));
1066     }
1067   return;
1068 }
1069
1070 /*-----------------------------------------------------------------*/
1071 /* printIval - generates code for initial value                    */
1072 /*-----------------------------------------------------------------*/
1073 void 
1074 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1075 {
1076   sym_link *itype;
1077   
1078   if (!ilist)
1079     return;
1080
1081   /* update line number for error msgs */
1082   lineno=sym->lineDef;
1083
1084   /* if structure then    */
1085   if (IS_STRUCT (type))
1086     {
1087       printIvalStruct (sym, type, ilist, oFile);
1088       return;
1089     }
1090
1091   /* if this is an array   */
1092   if (IS_ARRAY (type))
1093     {
1094       printIvalArray (sym, type, ilist, oFile);
1095       return;
1096     }
1097
1098   // not an aggregate, ilist must be a node
1099   if (ilist->type!=INIT_NODE) {
1100       // or a 1-element list
1101     if (ilist->init.deep->next) {
1102       werror (W_EXCESS_INITIALIZERS, "scalar", 
1103               sym->name, sym->lineDef);
1104     } else {
1105       ilist=ilist->init.deep;
1106     }
1107   }
1108
1109   // and the type must match
1110   itype=ilist->init.node->ftype;
1111
1112   if (compareType(type, itype)==0) {
1113     // special case for literal strings
1114     if (IS_ARRAY (itype) && IS_CHAR (getSpec(itype)) &&
1115         // which are really code pointers
1116         IS_PTR(type) && DCL_TYPE(type)==CPOINTER) {
1117       // no sweat
1118     } else {
1119       werror (E_TYPE_MISMATCH, "assignment", " ");
1120       printFromToType(itype, type);
1121     }
1122   }
1123
1124   /* if this is a pointer */
1125   if (IS_PTR (type))
1126     {
1127       printIvalPtr (sym, type, ilist, oFile);
1128       return;
1129     }
1130
1131   /* if type is SPECIFIER */
1132   if (IS_SPEC (type))
1133     {
1134       printIvalType (sym, type, ilist, oFile);
1135       return;
1136     }
1137 }
1138
1139 /*-----------------------------------------------------------------*/
1140 /* emitStaticSeg - emitcode for the static segment                 */
1141 /*-----------------------------------------------------------------*/
1142 void 
1143 emitStaticSeg (memmap * map, FILE * out)
1144 {
1145   symbol *sym;
1146
1147   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1148
1149   /* for all variables in this segment do */
1150   for (sym = setFirstItem (map->syms); sym;
1151        sym = setNextItem (map->syms))
1152     {
1153
1154       /* if it is "extern" then do nothing */
1155       if (IS_EXTERN (sym->etype))
1156         continue;
1157
1158       /* if it is not static add it to the public
1159          table */
1160       if (!IS_STATIC (sym->etype))
1161         {
1162           addSetHead (&publics, sym);
1163         }
1164
1165       /* print extra debug info if required */
1166       if (options.debug) {
1167
1168         if (!sym->level)
1169           {                     /* global */
1170             if (IS_STATIC (sym->etype))
1171               fprintf (out, "F%s$", moduleName);        /* scope is file */
1172             else
1173               fprintf (out, "G$");      /* scope is global */
1174           }
1175         else
1176           /* symbol is local */
1177           fprintf (out, "L%s$",
1178                    (sym->localof ? sym->localof->name : "-null-"));
1179         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1180       }
1181       
1182       /* if it has an absolute address */
1183       if (SPEC_ABSA (sym->etype))
1184         {
1185           if (options.debug)
1186             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1187           
1188           fprintf (out, "%s\t=\t0x%04x\n",
1189                    sym->rname,
1190                    SPEC_ADDR (sym->etype));
1191         }
1192       else
1193         {
1194           if (options.debug)
1195             fprintf (out, " == .\n");
1196           
1197           /* if it has an initial value */
1198           if (sym->ival)
1199             {
1200               fprintf (out, "%s:\n", sym->rname);
1201               noAlloc++;
1202               resolveIvalSym (sym->ival);
1203               printIval (sym, sym->type, sym->ival, out);
1204               noAlloc--;
1205               /* if sym is a simple string and sym->ival is a string, 
1206                  WE don't need it anymore */
1207               if (IS_ARRAY(sym->type) && IS_CHAR(sym->type->next) &&
1208                   IS_AST_SYM_VALUE(list2expr(sym->ival)) &&
1209                   list2val(sym->ival)->sym->isstrlit) {
1210                 freeStringSymbol(list2val(sym->ival)->sym);
1211               }
1212             }
1213           else {
1214               /* allocate space */
1215               int size = getSize (sym->type);
1216               
1217               if (size==0) {
1218                   werror(E_UNKNOWN_SIZE,sym->name);
1219               }
1220               fprintf (out, "%s:\n", sym->rname);
1221               /* special case for character strings */
1222               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1223                   SPEC_CVAL (sym->etype).v_char)
1224                   printChar (out,
1225                              SPEC_CVAL (sym->etype).v_char,
1226                              strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1227               else
1228                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1229             }
1230         }
1231     }
1232 }
1233
1234 /*-----------------------------------------------------------------*/
1235 /* emitMaps - emits the code for the data portion the code         */
1236 /*-----------------------------------------------------------------*/
1237 void 
1238 emitMaps (void)
1239 {
1240   inInitMode++;
1241   /* no special considerations for the following
1242      data, idata & bit & xdata */
1243   emitRegularMap (data, TRUE, TRUE);
1244   emitRegularMap (idata, TRUE, TRUE);
1245   emitRegularMap (bit, TRUE, FALSE);
1246   emitRegularMap (xdata, TRUE, TRUE);
1247   if (port->genXINIT) {
1248     emitRegularMap (xidata, TRUE, TRUE);
1249   }
1250   emitRegularMap (sfr, FALSE, FALSE);
1251   emitRegularMap (sfrbit, FALSE, FALSE);
1252   emitRegularMap (home, TRUE, FALSE);
1253   emitRegularMap (code, TRUE, FALSE);
1254
1255   emitStaticSeg (statsg, code->oFile);
1256   if (port->genXINIT) {
1257     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1258     emitStaticSeg (xinit, code->oFile);
1259   }
1260   inInitMode--;
1261 }
1262
1263 /*-----------------------------------------------------------------*/
1264 /* flushStatics - flush all currently defined statics out to file  */
1265 /*  and delete.  Temporary function                                */
1266 /*-----------------------------------------------------------------*/
1267 void 
1268 flushStatics (void)
1269 {
1270   emitStaticSeg (statsg, codeOutFile);
1271   statsg->syms = NULL;
1272 }
1273
1274 /*-----------------------------------------------------------------*/
1275 /* createInterruptVect - creates the interrupt vector              */
1276 /*-----------------------------------------------------------------*/
1277 void 
1278 createInterruptVect (FILE * vFile)
1279 {
1280   unsigned i = 0;
1281   mainf = newSymbol ("main", 0);
1282   mainf->block = 0;
1283
1284   /* only if the main function exists */
1285   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1286     {
1287       if (!options.cc_only && !noAssemble && !options.c1mode)
1288         werror (E_NO_MAIN);
1289       return;
1290     }
1291
1292   /* if the main is only a prototype ie. no body then do nothing */
1293   if (!IFFUNC_HASBODY(mainf->type))
1294     {
1295       /* if ! compile only then main function should be present */
1296       if (!options.cc_only && !noAssemble)
1297         werror (E_NO_MAIN);
1298       return;
1299     }
1300
1301   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1302   fprintf (vFile, "__interrupt_vect:\n");
1303
1304
1305   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1306     {
1307       /* "generic" interrupt table header (if port doesn't specify one).
1308        * Look suspiciously like 8051 code to me...
1309        */
1310
1311       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1312
1313
1314       /* now for the other interrupts */
1315       for (; i < maxInterrupts; i++)
1316         {
1317           if (interrupts[i])
1318             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1319           else
1320             fprintf (vFile, "\treti\n\t.ds\t7\n");
1321         }
1322     }
1323 }
1324
1325 char *iComments1 =
1326 {
1327   ";--------------------------------------------------------\n"
1328   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1329
1330 char *iComments2 =
1331 {
1332   ";--------------------------------------------------------\n"};
1333
1334
1335 /*-----------------------------------------------------------------*/
1336 /* initialComments - puts in some initial comments                 */
1337 /*-----------------------------------------------------------------*/
1338 void 
1339 initialComments (FILE * afile)
1340 {
1341   time_t t;
1342   time (&t);
1343   fprintf (afile, "%s", iComments1);
1344   fprintf (afile, "; Version " SDCC_VERSION_STR " %s\n", asctime (localtime (&t)));
1345   fprintf (afile, "%s", iComments2);
1346 }
1347
1348 /*-----------------------------------------------------------------*/
1349 /* printPublics - generates .global for publics                    */
1350 /*-----------------------------------------------------------------*/
1351 void 
1352 printPublics (FILE * afile)
1353 {
1354   symbol *sym;
1355
1356   fprintf (afile, "%s", iComments2);
1357   fprintf (afile, "; Public variables in this module\n");
1358   fprintf (afile, "%s", iComments2);
1359
1360   for (sym = setFirstItem (publics); sym;
1361        sym = setNextItem (publics))
1362     tfprintf (afile, "\t!global\n", sym->rname);
1363 }
1364
1365 /*-----------------------------------------------------------------*/
1366 /* printExterns - generates .global for externs                    */
1367 /*-----------------------------------------------------------------*/
1368 void 
1369 printExterns (FILE * afile)
1370 {
1371   symbol *sym;
1372
1373   fprintf (afile, "%s", iComments2);
1374   fprintf (afile, "; Externals used\n");
1375   fprintf (afile, "%s", iComments2);
1376
1377   for (sym = setFirstItem (externs); sym;
1378        sym = setNextItem (externs))
1379     tfprintf (afile, "\t!extern\n", sym->rname);
1380 }
1381
1382 /*-----------------------------------------------------------------*/
1383 /* emitOverlay - will emit code for the overlay stuff              */
1384 /*-----------------------------------------------------------------*/
1385 static void 
1386 emitOverlay (FILE * afile)
1387 {
1388   set *ovrset;
1389
1390   if (!elementsInSet (ovrSetSets))
1391     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1392
1393   /* for each of the sets in the overlay segment do */
1394   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1395        ovrset = setNextItem (ovrSetSets))
1396     {
1397
1398       symbol *sym;
1399
1400       if (elementsInSet (ovrset))
1401         {
1402           /* output the area informtion */
1403           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1404         }
1405
1406       for (sym = setFirstItem (ovrset); sym;
1407            sym = setNextItem (ovrset))
1408         {
1409           /* if extern then it is in the publics table: do nothing */
1410           if (IS_EXTERN (sym->etype))
1411             continue;
1412
1413           /* if allocation required check is needed
1414              then check if the symbol really requires
1415              allocation only for local variables */
1416           if (!IS_AGGREGATE (sym->type) &&
1417               !(sym->_isparm && !IS_REGPARM (sym->etype))
1418               && !sym->allocreq && sym->level)
1419             continue;
1420
1421           /* if global variable & not static or extern
1422              and addPublics allowed then add it to the public set */
1423           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1424               && !IS_STATIC (sym->etype))
1425             {
1426               addSetHead (&publics, sym);
1427             }
1428
1429           /* if extern then do nothing or is a function
1430              then do nothing */
1431           if (IS_FUNC (sym->type))
1432             continue;
1433
1434           /* print extra debug info if required */
1435           if (options.debug)
1436             {
1437               if (!sym->level)
1438                 {               /* global */
1439                   if (IS_STATIC (sym->etype))
1440                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1441                   else
1442                     fprintf (afile, "G$");      /* scope is global */
1443                 }
1444               else
1445                 /* symbol is local */
1446                 fprintf (afile, "L%s$",
1447                          (sym->localof ? sym->localof->name : "-null-"));
1448               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1449             }
1450
1451           /* if is has an absolute address then generate
1452              an equate for this no need to allocate space */
1453           if (SPEC_ABSA (sym->etype))
1454             {
1455
1456               if (options.debug)
1457                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1458
1459               fprintf (afile, "%s\t=\t0x%04x\n",
1460                        sym->rname,
1461                        SPEC_ADDR (sym->etype));
1462             }
1463           else {
1464               int size = getSize(sym->type);
1465
1466               if (size==0) {
1467                   werror(E_UNKNOWN_SIZE,sym->name);
1468               }       
1469               if (options.debug)
1470                   fprintf (afile, "==.\n");
1471               
1472               /* allocate space */
1473               tfprintf (afile, "!labeldef\n", sym->rname);
1474               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1475           }
1476           
1477         }
1478     }
1479 }
1480
1481
1482 /*-----------------------------------------------------------------*/
1483 /* spacesToUnderscores - replace spaces with underscores        */
1484 /*-----------------------------------------------------------------*/
1485 static char *
1486 spacesToUnderscores (char *dest, const char *src, size_t len)
1487 {
1488   int i;
1489   char *p;
1490
1491   assert(dest != NULL);
1492   assert(src != NULL);
1493   assert(len > 0);
1494
1495   --len;
1496   for (p = dest, i = 0; *src != '\0' && i < len; ++src, ++i) {
1497     *p++ = isspace(*src) ? '_' : *src;
1498   }
1499   *p = '\0';
1500
1501   return dest;
1502 }
1503
1504
1505 /*-----------------------------------------------------------------*/
1506 /* glue - the final glue that hold the whole thing together        */
1507 /*-----------------------------------------------------------------*/
1508 void 
1509 glue (void)
1510 {
1511   FILE *vFile;
1512   FILE *asmFile;
1513   FILE *ovrFile = tempfile ();
1514   char moduleBuf[PATH_MAX];
1515   int mcs51_like;
1516
1517   if(port->general.glue_up_main &&
1518     (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51 || TARGET_IS_DS400))
1519   {
1520       mcs51_like=1; /*So it has bits, sfr, sbits, data, idata, etc...*/
1521   }
1522   else
1523   {
1524       mcs51_like=0;
1525   }
1526
1527   addSetHead (&tmpfileSet, ovrFile);
1528   /* print the global struct definitions */
1529   if (options.debug)
1530     cdbStructBlock (0);
1531
1532   vFile = tempfile ();
1533   /* PENDING: this isnt the best place but it will do */
1534   if (port->general.glue_up_main)
1535     {
1536       /* create the interrupt vector table */
1537       createInterruptVect (vFile);
1538     }
1539
1540   addSetHead (&tmpfileSet, vFile);
1541
1542   /* emit code for the all the variables declared */
1543   emitMaps ();
1544   /* do the overlay segments */
1545   emitOverlay (ovrFile);
1546
1547   outputDebugSymbols();
1548
1549   /* now put it all together into the assembler file */
1550   /* create the assembler file name */
1551
1552   /* -o option overrides default name? */
1553   if ((noAssemble || options.c1mode) && fullDstFileName)
1554     {
1555       strncpyz (scratchFileName, fullDstFileName, PATH_MAX);
1556     }
1557   else
1558     {
1559       strncpyz (scratchFileName, dstFileName, PATH_MAX);
1560       strncatz (scratchFileName, port->assembler.file_ext, PATH_MAX);
1561     }
1562
1563   if (!(asmFile = fopen (scratchFileName, "w")))
1564     {
1565       werror (E_FILE_OPEN_ERR, scratchFileName);
1566       exit (1);
1567     }
1568
1569   /* initial comments */
1570   initialComments (asmFile);
1571
1572   /* print module name */
1573   tfprintf (asmFile, "\t!module\n",
1574     spacesToUnderscores (moduleBuf, moduleName, sizeof moduleBuf));
1575   if(mcs51_like)
1576   {
1577     fprintf (asmFile, "\t.optsdcc -m%s", port->target);
1578
1579     switch(options.model)
1580     {
1581         case MODEL_SMALL:   fprintf (asmFile, " --model-small");   break;
1582         case MODEL_COMPACT: fprintf (asmFile, " --model-compact"); break;
1583         case MODEL_MEDIUM:  fprintf (asmFile, " --model-medium");  break;
1584         case MODEL_LARGE:   fprintf (asmFile, " --model-large");   break;
1585         case MODEL_FLAT24:  fprintf (asmFile, " --model-flat24");  break;
1586         case MODEL_PAGE0:   fprintf (asmFile, " --model-page0");   break;
1587         default: break;
1588     }
1589     if(options.stackAuto)      fprintf (asmFile, " --stack-auto");
1590     if(options.useXstack)      fprintf (asmFile, " --xstack");
1591     if(options.intlong_rent)   fprintf (asmFile, " --int-long-rent");
1592     if(options.float_rent)     fprintf (asmFile, " --float-rent");
1593     if(options.noRegParams)    fprintf (asmFile, " --no-reg-params");
1594     if(options.parms_in_bank1) fprintf (asmFile, " --parms-in-bank1");
1595     fprintf (asmFile, "\n");
1596   }
1597   else if(TARGET_IS_Z80 || TARGET_IS_GBZ80 )
1598   {
1599     fprintf (asmFile, "\t.optsdcc -m%s\n", port->target);
1600   }
1601
1602   tfprintf (asmFile, "\t!fileprelude\n");
1603
1604   /* Let the port generate any global directives, etc. */
1605   if (port->genAssemblerPreamble)
1606     {
1607       port->genAssemblerPreamble (asmFile);
1608     }
1609
1610   /* print the global variables in this module */
1611   printPublics (asmFile);
1612   if (port->assembler.externGlobal)
1613     printExterns (asmFile);
1614
1615   if(mcs51_like)
1616   {
1617       /* copy the sfr segment */
1618       fprintf (asmFile, "%s", iComments2);
1619       fprintf (asmFile, "; special function registers\n");
1620       fprintf (asmFile, "%s", iComments2);
1621       copyFile (asmFile, sfr->oFile);
1622
1623       /* copy the sbit segment */
1624       fprintf (asmFile, "%s", iComments2);
1625       fprintf (asmFile, "; special function bits \n");
1626       fprintf (asmFile, "%s", iComments2);
1627       copyFile (asmFile, sfrbit->oFile);
1628   
1629       /*JCF: Create the areas for the register banks*/
1630           if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1631           {
1632                  fprintf (asmFile, "%s", iComments2);
1633                  fprintf (asmFile, "; overlayable register banks \n");
1634                  fprintf (asmFile, "%s", iComments2);
1635                  if(RegBankUsed[0])
1636                         fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1637                  if(RegBankUsed[1]||options.parms_in_bank1)
1638                         fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1639                  if(RegBankUsed[2])
1640                         fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1641                  if(RegBankUsed[3])
1642                         fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1643           }
1644   }
1645
1646   /* copy the data segment */
1647   fprintf (asmFile, "%s", iComments2);
1648   fprintf (asmFile, "; %s ram data\n", mcs51_like?"internal":"");
1649   fprintf (asmFile, "%s", iComments2);
1650   copyFile (asmFile, data->oFile);
1651
1652
1653   /* create the overlay segments */
1654   if (overlay) {
1655     fprintf (asmFile, "%s", iComments2);
1656     fprintf (asmFile, "; overlayable items in %s ram \n", mcs51_like?"internal":"");
1657     fprintf (asmFile, "%s", iComments2);
1658     copyFile (asmFile, ovrFile);
1659   }
1660
1661   /* create the stack segment MOF */
1662   if (mainf && IFFUNC_HASBODY(mainf->type))
1663     {
1664       fprintf (asmFile, "%s", iComments2);
1665       fprintf (asmFile, "; Stack segment in internal ram \n");
1666       fprintf (asmFile, "%s", iComments2);
1667       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1668                "__start__stack:\n\t.ds\t1\n\n");
1669     }
1670
1671   /* create the idata segment */
1672   if ( (idata) && (mcs51_like) ) {
1673     fprintf (asmFile, "%s", iComments2);
1674     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1675     fprintf (asmFile, "%s", iComments2);
1676     copyFile (asmFile, idata->oFile);
1677   }
1678
1679   /* copy the bit segment */
1680   if (mcs51_like) {
1681     fprintf (asmFile, "%s", iComments2);
1682     fprintf (asmFile, "; bit data\n");
1683     fprintf (asmFile, "%s", iComments2);
1684     copyFile (asmFile, bit->oFile);
1685   }
1686
1687   /* if external stack then reserve space of it */
1688   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1689     {
1690       fprintf (asmFile, "%s", iComments2);
1691       fprintf (asmFile, "; external stack \n");
1692       fprintf (asmFile, "%s", iComments2);
1693       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1694       fprintf (asmFile, "\t.ds 256\n");
1695     }
1696
1697
1698   /* copy xtern ram data */
1699   if (mcs51_like) {
1700     fprintf (asmFile, "%s", iComments2);
1701     fprintf (asmFile, "; external ram data\n");
1702     fprintf (asmFile, "%s", iComments2);
1703     copyFile (asmFile, xdata->oFile);
1704   }
1705
1706   /* copy xternal initialized ram data */
1707   fprintf (asmFile, "%s", iComments2);
1708   fprintf (asmFile, "; external initialized ram data\n");
1709   fprintf (asmFile, "%s", iComments2);
1710   copyFile (asmFile, xidata->oFile);
1711
1712   /* If the port wants to generate any extra areas, let it do so. */
1713   if (port->extraAreas.genExtraAreaDeclaration)
1714   {
1715       port->extraAreas.genExtraAreaDeclaration(asmFile, 
1716                                                mainf && IFFUNC_HASBODY(mainf->type));
1717   }
1718     
1719   /* copy the interrupt vector table */
1720   if (mainf && IFFUNC_HASBODY(mainf->type))
1721     {
1722       fprintf (asmFile, "%s", iComments2);
1723       fprintf (asmFile, "; interrupt vector \n");
1724       fprintf (asmFile, "%s", iComments2);
1725       copyFile (asmFile, vFile);
1726     }
1727
1728   /* copy global & static initialisations */
1729   fprintf (asmFile, "%s", iComments2);
1730   fprintf (asmFile, "; global & static initialisations\n");
1731   fprintf (asmFile, "%s", iComments2);
1732
1733   /* Everywhere we generate a reference to the static_name area,
1734    * (which is currently only here), we immediately follow it with a
1735    * definition of the post_static_name area. This guarantees that
1736    * the post_static_name area will immediately follow the static_name
1737    * area.
1738    */
1739   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1740   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1741   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1742
1743   if (mainf && IFFUNC_HASBODY(mainf->type))
1744     {
1745       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1746       /* if external stack is specified then the
1747          higher order byte of the xdatalocation is
1748          going into P2 and the lower order going into
1749          spx */
1750       if (options.useXstack)
1751         {
1752           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1753                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1754           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1755                    (unsigned int) options.xdata_loc & 0xff);
1756         }
1757
1758         // This should probably be a port option, but I'm being lazy.
1759         // on the 400, the firmware boot loader gives us a valid stack
1760         // (see '400 data sheet pg. 85 (TINI400 ROM Initialization code)
1761         if (!TARGET_IS_DS400)
1762         {
1763             /* initialise the stack pointer.  JCF: aslink takes care of the location */
1764             fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");       /* MOF */
1765         }
1766
1767       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1768       fprintf (asmFile, "\tmov\ta,dpl\n");
1769       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1770       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1771       fprintf (asmFile, "__sdcc_init_data:\n");
1772
1773       // if the port can copy the XINIT segment to XISEG
1774       if (port->genXINIT) {
1775         port->genXINIT(asmFile);
1776       }
1777
1778     }
1779   copyFile (asmFile, statsg->oFile);
1780
1781   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1782     {
1783       /* This code is generated in the post-static area.
1784        * This area is guaranteed to follow the static area
1785        * by the ugly shucking and jiving about 20 lines ago.
1786        */
1787       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1788       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1789     }
1790
1791   fprintf (asmFile,
1792            "%s"
1793            "; Home\n"
1794            "%s", iComments2, iComments2);
1795   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1796   copyFile (asmFile, home->oFile);
1797
1798   /* copy over code */
1799   fprintf (asmFile, "%s", iComments2);
1800   fprintf (asmFile, "; code\n");
1801   fprintf (asmFile, "%s", iComments2);
1802   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1803   if (mainf && IFFUNC_HASBODY(mainf->type))
1804     {
1805
1806       /* entry point @ start of CSEG */
1807       fprintf (asmFile, "__sdcc_program_startup:\n");
1808
1809       /* put in the call to main */
1810       fprintf (asmFile, "\tlcall\t_main\n");
1811       if (options.mainreturn)
1812         {
1813
1814           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1815           fprintf (asmFile, "\tret\n");
1816
1817         }
1818       else
1819         {
1820
1821           fprintf (asmFile, ";\treturn from main will lock up\n");
1822           fprintf (asmFile, "\tsjmp .\n");
1823         }
1824     }
1825   copyFile (asmFile, code->oFile);
1826
1827   if (port->genAssemblerEnd) {
1828       port->genAssemblerEnd(asmFile);
1829   }
1830   fclose (asmFile);
1831
1832   rm_tmpfiles ();
1833 }
1834
1835
1836 /** Creates a temporary file with unoque file name
1837     Scans, in order:
1838     - TMP, TEMP, TMPDIR env. varibles
1839     - if Un*x system: /usr/tmp and /tmp
1840     - root directory using mkstemp() if avaliable
1841     - default location using tempnam()
1842 */
1843 static int
1844 tempfileandname(char *fname, size_t len)
1845 {
1846 #define TEMPLATE      "sdccXXXXXX"
1847 #define TEMPLATE_LEN  ((sizeof TEMPLATE) - 1)
1848
1849   const char *tmpdir = NULL;
1850   int fd;
1851
1852   if ((tmpdir = getenv ("TMP")) == NULL)
1853     if ((tmpdir = getenv ("TEMP")) == NULL)
1854       tmpdir = getenv ("TMPDIR");
1855
1856 #if defined(_WIN32)
1857   {
1858     static int warning_emitted;
1859
1860     if (tmpdir == NULL)
1861       {
1862         tmpdir = "c:\\";
1863         if (!warning_emitted)
1864           {
1865             fprintf (stderr, "TMP not defined in environment, using %s for temporary files\n.", tmpdir);
1866             warning_emitted = 1;
1867           }
1868       }
1869   }
1870 #else
1871   {
1872     /* try with /usr/tmp and /tmp on Un*x systems */
1873     struct stat statbuf;
1874
1875     if (tmpdir == NULL) {
1876       if (stat("/usr/tmp", &statbuf) != -1)
1877         tmpdir = "/usr/tmp";
1878       else if (stat("/tmp", &statbuf) != -1)
1879         tmpdir = "/tmp";
1880     }
1881   }
1882 #endif
1883
1884 #ifdef HAVE_MKSTEMP
1885   {
1886     char fnamebuf[PATH_MAX];
1887     size_t name_len;
1888
1889     if (fname == NULL || len == 0) {
1890       fname = fnamebuf;
1891       len = sizeof fnamebuf;
1892     }
1893
1894     if (tmpdir) {
1895       name_len = strlen(tmpdir) + 1 + TEMPLATE_LEN;
1896
1897       assert(name_len < len);
1898       if (!(name_len < len))  /* in NDEBUG is defined */
1899         return -1;            /* buffer too small, temporary file can not be created */
1900
1901       sprintf(fname, "%s" DIR_SEPARATOR_STRING TEMPLATE, tmpdir);
1902     }
1903     else {
1904       name_len = TEMPLATE_LEN;
1905
1906       assert(name_len < len);
1907       if (!(name_len < len))  /* in NDEBUG is defined */
1908         return -1;            /* buffer too small, temporary file can not be created */
1909
1910       strcpy(fname, TEMPLATE);
1911     }
1912
1913     fd = mkstemp(fname);
1914   }
1915 #else
1916   {
1917     char *name = tempnam(tmpdir, "sdcc");
1918
1919     if (name == NULL) {
1920       perror("Can't create temporary file name");
1921       exit(1);
1922     }
1923
1924     assert(strlen(name) < len);
1925     if (!(strlen(name) < len))  /* in NDEBUG is defined */
1926       return -1;                /* buffer too small, temporary file can not be created */
1927
1928     strcpy(fname, name);
1929 #ifdef _WIN32
1930     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IREAD | S_IWRITE);
1931 #else
1932     fd = open(name, O_CREAT | O_EXCL | O_RDWR, S_IRUSR | S_IWUSR);
1933 #endif
1934   }
1935 #endif
1936
1937   if (fd == -1) {
1938     perror("Can't create temporary file");
1939     exit(1);
1940   }
1941
1942   return fd;
1943 }
1944
1945
1946 /** Create a temporary file name
1947 */
1948 char *
1949 tempfilename(void)
1950 {
1951   int fd;
1952   static char fnamebuf[PATH_MAX];
1953
1954   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1955     fprintf(stderr, "Can't create temporary file name!");
1956     exit(1);
1957   }
1958
1959   fd = close(fd);
1960   assert(fd != -1);
1961
1962   return fnamebuf;
1963 }
1964
1965
1966 /** Create a temporary file and add it to tmpfileNameSet,
1967     so that it is removed explicitly by rm_tmpfiles()
1968     or implicitly at program extit.
1969 */
1970 FILE *
1971 tempfile(void)
1972 {
1973   int fd;
1974   char *tmp;
1975   FILE *fp;
1976   char fnamebuf[PATH_MAX];
1977
1978   if ((fd = tempfileandname(fnamebuf, sizeof fnamebuf)) == -1) {
1979     fprintf(stderr, "Can't create temporary file!");
1980     exit(1);
1981   }
1982
1983   tmp = Safe_strdup(fnamebuf);
1984   if (tmp)
1985     addSetHead(&tmpfileNameSet, tmp);
1986
1987   if ((fp = fdopen(fd, "w+b")) == NULL) {
1988       perror("Can't create temporary file!");
1989       exit(1);
1990   }
1991
1992   return fp;
1993 }