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