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