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