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