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