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