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