6b100947609d50c93f57cd255e586c900ac944ab
[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
30 #if !defined(__BORLANDC__) && !defined(_MSC_VER)
31 #include <unistd.h>
32 #endif
33
34 symbol *interrupts[256];
35
36 void printIval (symbol *, sym_link *, initList *, FILE *);
37 set *publics = NULL;            /* public variables */
38 set *externs = NULL;            /* Varibles that are declared as extern */
39
40 /* TODO: this should be configurable (DS803C90 uses more than 6) */
41 unsigned maxInterrupts = 6;
42 int allocInfo = 1;
43 symbol *mainf;
44 extern char *VersionString;
45 set *tmpfileSet = NULL;         /* set of tmp file created by the compiler */
46 set *tmpfileNameSet = NULL;     /* All are unlinked at close. */
47
48 /*-----------------------------------------------------------------*/
49 /* closeTmpFiles - closes all tmp files created by the compiler    */
50 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
51 /*-----------------------------------------------------------------*/
52 DEFSETFUNC (closeTmpFiles)
53 {
54   FILE *tfile = item;
55
56   if (tfile)
57     fclose (tfile);
58
59   return 0;
60 }
61
62 /*-----------------------------------------------------------------*/
63 /* rmTmpFiles - unlinks all tmp files created by the compiler      */
64 /*                 because of BRAIN DEAD MS/DOS & CYGNUS Libraries */
65 /*-----------------------------------------------------------------*/
66 DEFSETFUNC (rmTmpFiles)
67 {
68   char *name = item;
69
70   if (name)
71     {
72       unlink (name);
73       Safe_free (name);
74     }
75   return 0;
76 }
77
78 /*-----------------------------------------------------------------*/
79 /* rm_tmpfiles - close and remove temporary files and delete sets  */
80 /*-----------------------------------------------------------------*/
81 void
82 rm_tmpfiles (void)
83 {
84   /* close temporary files */
85   applyToSet (tmpfileSet, closeTmpFiles);
86   /* remove temporary files */
87   applyToSet (tmpfileNameSet, rmTmpFiles);
88   /* delete temorary file sets */
89   deleteSet (&tmpfileSet);
90   deleteSet (&tmpfileNameSet);
91 }
92
93 /*-----------------------------------------------------------------*/
94 /* copyFile - copies source file to destination file               */
95 /*-----------------------------------------------------------------*/
96 void 
97 copyFile (FILE * dest, FILE * src)
98 {
99   int ch;
100
101   rewind (src);
102   while (!feof (src))
103     if ((ch = fgetc (src)) != EOF)
104       fputc (ch, dest);
105 }
106
107 char *
108 aopLiteralLong (value * val, int offset, int size)
109 {
110         char *rs;
111         union {
112                 float f;
113                 unsigned char c[4];
114         }
115         fl;
116
117         if (!val) {
118           // assuming we have been warned before
119           val=constVal("0");
120         }
121
122         /* if it is a float then it gets tricky */
123         /* otherwise it is fairly simple */
124         if (!IS_FLOAT (val->type)) {
125                 unsigned long v = (unsigned long) floatFromVal (val);
126
127                 v >>= (offset * 8);
128                 switch (size) {
129                 case 1:
130                         tsprintf (buffer, "!immedbyte", (unsigned int) v & 0xff);
131                         break;
132                 case 2:
133                         tsprintf (buffer, "!immedword", (unsigned int) v & 0xffff);
134                         break;
135                 default:
136                         /* Hmm.  Too big for now. */
137                         assert (0);
138                 }
139                 rs = Safe_calloc (1, strlen (buffer) + 1);
140                 return strcpy (rs, buffer);
141         }
142
143         /* PENDING: For now size must be 1 */
144         assert (size == 1);
145
146         /* it is type float */
147         fl.f = (float) floatFromVal (val);
148 #ifdef _BIG_ENDIAN
149         tsprintf (buffer, "!immedbyte", fl.c[3 - offset]);
150 #else
151         tsprintf (buffer, "!immedbyte", fl.c[offset]);
152 #endif
153         rs = Safe_calloc (1, strlen (buffer) + 1);
154         return strcpy (rs, buffer);
155 }
156
157 /*-----------------------------------------------------------------*/
158 /* aopLiteral - string from a literal value                        */
159 /*-----------------------------------------------------------------*/
160 char *
161 aopLiteral (value * val, int offset)
162 {
163         return aopLiteralLong (val, offset, 1);
164 }
165
166 /*-----------------------------------------------------------------*/
167 /* emitRegularMap - emit code for maps with no special cases       */
168 /*-----------------------------------------------------------------*/
169 static void 
170 emitRegularMap (memmap * map, bool addPublics, bool arFlag)
171 {
172   symbol *sym;
173   ast *ival = NULL;
174
175   if (!map)
176     return;
177
178   if (addPublics)
179     {
180       /* PENDING: special case here - should remove */
181       if (!strcmp (map->sname, CODE_NAME))
182         tfprintf (map->oFile, "\t!areacode\n", map->sname);
183       else if (!strcmp (map->sname, DATA_NAME))
184         tfprintf (map->oFile, "\t!areadata\n", map->sname);
185       else if (!strcmp (map->sname, HOME_NAME))
186         tfprintf (map->oFile, "\t!areahome\n", map->sname);
187       else
188         tfprintf (map->oFile, "\t!area\n", map->sname);
189     }
190  
191   for (sym = setFirstItem (map->syms); sym;
192        sym = setNextItem (map->syms))
193     {
194       symbol *newSym=NULL;
195
196       /* if extern then add it into the extern list */
197       if (IS_EXTERN (sym->etype))
198         {
199           addSetHead (&externs, sym);
200           continue;
201         }
202
203       /* if allocation required check is needed
204          then check if the symbol really requires
205          allocation only for local variables */
206
207       if (arFlag && !IS_AGGREGATE (sym->type) &&
208           !(sym->_isparm && !IS_REGPARM (sym->etype)) &&
209           !sym->allocreq && sym->level)
210         continue;
211
212       /* for bitvar locals and parameters */
213       if (!arFlag && !sym->allocreq && sym->level 
214           && !SPEC_ABSA (sym->etype)) {
215         continue;
216       }
217
218       /* if global variable & not static or extern
219          and addPublics allowed then add it to the public set */
220       if ((sym->level == 0 ||
221            (sym->_isparm && !IS_REGPARM (sym->etype))) &&
222           addPublics &&
223           !IS_STATIC (sym->etype) &&
224           (IS_FUNC(sym->type) ? (sym->used || IFFUNC_HASBODY(sym->type)) : 1))
225         {
226           addSetHead (&publics, sym);
227         }
228
229       /* if extern then do nothing or is a function
230          then do nothing */
231       if (IS_FUNC (sym->type))
232         continue;
233
234       /* print extra debug info if required */
235       if (options.debug) {
236         cdbSymbol (sym, cdbFile, FALSE, FALSE);
237         if (!sym->level) /* global */
238           if (IS_STATIC (sym->etype))
239             fprintf (map->oFile, "F%s$", moduleName); /* scope is file */
240           else
241             fprintf (map->oFile, "G$"); /* scope is global */
242         else
243           /* symbol is local */
244           fprintf (map->oFile, "L%s$", (sym->localof ? sym->localof->name : "-null-"));
245         fprintf (map->oFile, "%s$%d$%d", sym->name, sym->level, sym->block);
246       }
247       
248       /* if it has an initial value then do it only if
249          it is a global variable */
250       if (sym->ival && sym->level == 0) {
251         if (SPEC_OCLS(sym->etype)==xidata) {
252           // create a new "XINIT (CODE)" symbol, that will be emitted later
253           newSym=copySymbol (sym);
254           SPEC_OCLS(newSym->etype)=xinit;
255           sprintf (newSym->name, "__xinit_%s", sym->name);
256           sprintf (newSym->rname,"__xinit_%s", sym->rname);
257           SPEC_CONST(newSym->etype)=1;
258           SPEC_STAT(newSym->etype)=1;
259
260           // add it to the "XINIT (CODE)" segment
261           addSet(&xinit->syms, newSym);
262           sym->ival=NULL;
263         } else {
264           if (IS_AGGREGATE (sym->type)) {
265             ival = initAggregates (sym, sym->ival, NULL);
266           } else {
267             if (getNelements(sym->type, sym->ival)>1) {
268               werror (W_EXCESS_INITIALIZERS, "scalar", 
269                       sym->name, sym->lineDef);
270             }
271             ival = newNode ('=', newAst_VALUE (symbolVal (sym)),
272                             decorateType (resolveSymbols (list2expr (sym->ival))));
273           }
274           codeOutFile = statsg->oFile;
275
276           if (ival) {
277             // set ival's lineno to where the symbol was defined
278             setAstLineno (ival, lineno=sym->lineDef);
279             // check if this is not a constant expression
280             if (!constExprTree(ival)) {
281               werror (E_CONST_EXPECTED, "found expression");
282               // but try to do it anyway
283             }
284             allocInfo = 0;
285             eBBlockFromiCode (iCodeFromAst (ival));
286             allocInfo = 1;
287           }
288         }         
289         sym->ival = NULL;
290       }
291
292       /* if is has an absolute address then generate
293          an equate for this no need to allocate space */
294       if (SPEC_ABSA (sym->etype))
295         {
296           char *equ="=";
297           if (options.debug) {
298             fprintf (map->oFile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
299           }
300           if (TARGET_IS_XA51) {
301             if (map==sfr) {
302               equ="sfr";
303             } else if (map==bit || map==sfrbit) {
304               equ="bit";
305             }
306           }
307           fprintf (map->oFile, "%s\t%s\t0x%04x\n",
308                    sym->rname, equ,
309                    SPEC_ADDR (sym->etype));
310         }
311       else {
312         int size = getSize (sym->type);
313         if (size==0) {
314           werror(E_UNKNOWN_SIZE,sym->name);
315         }
316         /* allocate space */
317         if (options.debug) {
318           fprintf (map->oFile, "==.\n");
319         }
320         if (IS_STATIC (sym->etype))
321           tfprintf (map->oFile, "!slabeldef\n", sym->rname);
322         else
323           tfprintf (map->oFile, "!labeldef\n", sym->rname);           
324         tfprintf (map->oFile, "\t!ds\n", 
325                   (unsigned int)  size & 0xffff);
326       }
327     }
328 }
329
330 /*-----------------------------------------------------------------*/
331 /* initPointer - pointer initialization code massaging             */
332 /*-----------------------------------------------------------------*/
333 value *
334 initPointer (initList * ilist, sym_link *toType)
335 {
336         value *val;
337         ast *expr = list2expr (ilist);
338         
339         if (!expr)
340                 goto wrong;
341         
342         /* try it the oldway first */
343         if ((val = constExprValue (expr, FALSE)))
344                 return val;
345         
346         /* ( ptr + constant ) */
347         if (IS_AST_OP (expr) &&
348             (expr->opval.op == '+' || expr->opval.op == '-') &&
349             IS_AST_SYM_VALUE (expr->left) &&
350             (IS_ARRAY(expr->left->ftype) || IS_PTR(expr->left->ftype)) &&
351             compareType(toType, expr->left->ftype) &&
352             IS_AST_LIT_VALUE (expr->right)) {
353           return valForCastAggr (expr->left, expr->left->ftype,
354                                       expr->right,
355                                       expr->opval.op);
356         }
357         
358         /* (char *)&a */
359         if (IS_AST_OP(expr) && expr->opval.op==CAST &&
360             IS_AST_OP(expr->right) && expr->right->opval.op=='&') {
361           if (compareType(toType, expr->left->ftype)!=1) {
362             werror (W_INIT_WRONG);
363             printFromToType(expr->left->ftype, toType);
364           }
365           // skip the cast ???
366           expr=expr->right;
367         }
368
369         /* no then we have to do these cludgy checks */
370         /* pointers can be initialized with address of
371            a variable or address of an array element */
372         if (IS_AST_OP (expr) && expr->opval.op == '&') {
373                 /* address of symbol */
374                 if (IS_AST_SYM_VALUE (expr->left)) {
375                         val = copyValue (AST_VALUE (expr->left));
376                         val->type = newLink ();
377                         if (SPEC_SCLS (expr->left->etype) == S_CODE) {
378                                 DCL_TYPE (val->type) = CPOINTER;
379                                 DCL_PTR_CONST (val->type) = port->mem.code_ro;
380                         }
381                         else if (SPEC_SCLS (expr->left->etype) == S_XDATA)
382                                 DCL_TYPE (val->type) = FPOINTER;
383                         else if (SPEC_SCLS (expr->left->etype) == S_XSTACK)
384                                 DCL_TYPE (val->type) = PPOINTER;
385                         else if (SPEC_SCLS (expr->left->etype) == S_IDATA)
386                                 DCL_TYPE (val->type) = IPOINTER;
387                         else if (SPEC_SCLS (expr->left->etype) == S_EEPROM)
388                                 DCL_TYPE (val->type) = EEPPOINTER;
389                         else
390                                 DCL_TYPE (val->type) = POINTER;
391                         val->type->next = expr->left->ftype;
392                         val->etype = getSpec (val->type);
393                         return val;
394                 }
395
396                 /* if address of indexed array */
397                 if (IS_AST_OP (expr->left) && expr->left->opval.op == '[')
398                         return valForArray (expr->left);
399
400                 /* if address of structure element then
401                    case 1. a.b ; */
402                 if (IS_AST_OP (expr->left) &&
403                     expr->left->opval.op == '.') {
404                         return valForStructElem (expr->left->left,
405                                                  expr->left->right);
406                 }
407
408                 /* case 2. (&a)->b ;
409                    (&some_struct)->element */
410                 if (IS_AST_OP (expr->left) &&
411                     expr->left->opval.op == PTR_OP &&
412                     IS_ADDRESS_OF_OP (expr->left->left)) {
413                   return valForStructElem (expr->left->left->left,
414                                            expr->left->right);
415                 }
416         }
417         /* case 3. (((char *) &a) +/- constant) */
418         if (IS_AST_OP (expr) &&
419             (expr->opval.op == '+' || expr->opval.op == '-') &&
420             IS_AST_OP (expr->left) && expr->left->opval.op == CAST &&
421             IS_AST_OP (expr->left->right) &&
422             expr->left->right->opval.op == '&' &&
423             IS_AST_LIT_VALUE (expr->right)) {
424
425                 return valForCastAggr (expr->left->right->left,
426                                        expr->left->left->opval.lnk,
427                                        expr->right, expr->opval.op);
428
429         }
430         /* case 4. (char *)(array type) */
431         if (IS_CAST_OP(expr) && IS_AST_SYM_VALUE (expr->right) &&
432             IS_ARRAY(expr->right->ftype)) {
433
434                 val = copyValue (AST_VALUE (expr->right));
435                 val->type = newLink ();
436                 if (SPEC_SCLS (expr->right->etype) == S_CODE) {
437                         DCL_TYPE (val->type) = CPOINTER;
438                         DCL_PTR_CONST (val->type) = port->mem.code_ro;
439                 }
440                 else if (SPEC_SCLS (expr->right->etype) == S_XDATA)
441                         DCL_TYPE (val->type) = FPOINTER;
442                 else if (SPEC_SCLS (expr->right->etype) == S_XSTACK)
443                         DCL_TYPE (val->type) = PPOINTER;
444                 else if (SPEC_SCLS (expr->right->etype) == S_IDATA)
445                         DCL_TYPE (val->type) = IPOINTER;
446                 else if (SPEC_SCLS (expr->right->etype) == S_EEPROM)
447                         DCL_TYPE (val->type) = EEPPOINTER;
448                 else
449                         DCL_TYPE (val->type) = POINTER;
450                 val->type->next = expr->right->ftype->next;
451                 val->etype = getSpec (val->type);
452                 return val;
453         }
454  wrong:
455         werror (E_INCOMPAT_PTYPES);
456         return NULL;
457
458 }
459
460 /*-----------------------------------------------------------------*/
461 /* printChar - formats and prints a characater string with DB      */
462 /*-----------------------------------------------------------------*/
463 void 
464 printChar (FILE * ofile, char *s, int plen)
465 {
466   int i;
467   int len = strlen (s);
468   int pplen = 0;
469   char buf[100];
470   char *p = buf;
471
472   while (len && pplen < plen)
473     {
474       i = 60;
475       while (i && *s && pplen < plen)
476         {
477           if (*s < ' ' || *s == '\"' || *s=='\\')
478             {
479               *p = '\0';
480               if (p != buf)
481                 tfprintf (ofile, "\t!ascii\n", buf);
482               tfprintf (ofile, "\t!db !constbyte\n", (unsigned char)*s);
483               p = buf;
484             }
485           else
486             {
487               *p = *s;
488               p++;
489             }
490           s++;
491           pplen++;
492           i--;
493         }
494       if (p != buf)
495         {
496           *p = '\0';
497           tfprintf (ofile, "\t!ascii\n", buf);
498           p = buf;
499         }
500
501       if (len > 60)
502         len -= 60;
503       else
504         len = 0;
505     }
506   tfprintf (ofile, "\t!db !constbyte\n", 0);
507 }
508
509 /*-----------------------------------------------------------------*/
510 /* return the generic pointer high byte for a given pointer type.  */
511 /*-----------------------------------------------------------------*/
512 int 
513 pointerTypeToGPByte (const int p_type, const char *iname, const char *oname)
514 {
515   switch (p_type)
516     {
517     case IPOINTER:
518     case POINTER:
519       return GPTYPE_NEAR;
520     case GPOINTER:
521         werror (E_CANNOT_USE_GENERIC_POINTER, 
522                 iname ? iname : "<null>", 
523                 oname ? oname : "<null>");
524       exit (1);
525     case FPOINTER:
526       return GPTYPE_FAR;
527     case CPOINTER:
528       return GPTYPE_CODE;
529     case PPOINTER:
530       return GPTYPE_XSTACK;
531     default:
532       fprintf (stderr, "*** internal error: unknown pointer type %d in GPByte.\n",
533                p_type);
534       break;
535     }
536   return -1;
537 }
538
539
540 /*-----------------------------------------------------------------*/
541 /* printPointerType - generates ival for pointer type              */
542 /*-----------------------------------------------------------------*/
543 void 
544 _printPointerType (FILE * oFile, const char *name)
545 {
546   /* if (TARGET_IS_DS390) */
547   if (options.model == MODEL_FLAT24)
548     {
549       fprintf (oFile, "\t.byte %s,(%s >> 8),(%s >> 16)", name, name, name);
550     }
551   else
552     {
553       fprintf (oFile, "\t.byte %s,(%s >> 8)", name, name);
554     }
555 }
556
557 /*-----------------------------------------------------------------*/
558 /* printPointerType - generates ival for pointer type              */
559 /*-----------------------------------------------------------------*/
560 void 
561 printPointerType (FILE * oFile, const char *name)
562 {
563   _printPointerType (oFile, name);
564   fprintf (oFile, "\n");
565 }
566
567 /*-----------------------------------------------------------------*/
568 /* printGPointerType - generates ival for generic pointer type     */
569 /*-----------------------------------------------------------------*/
570 void 
571 printGPointerType (FILE * oFile, const char *iname, const char *oname,
572                    const unsigned int type)
573 {
574   _printPointerType (oFile, iname);
575   fprintf (oFile, ",#0x%02x\n", pointerTypeToGPByte (type, iname, oname));
576 }
577
578 /*-----------------------------------------------------------------*/
579 /* printIvalType - generates ival for int/char                     */
580 /*-----------------------------------------------------------------*/
581 void 
582 printIvalType (symbol *sym, sym_link * type, initList * ilist, FILE * oFile)
583 {
584         value *val;
585
586         /* if initList is deep */
587         if (ilist->type == INIT_DEEP)
588                 ilist = ilist->init.deep;
589
590         if (!IS_AGGREGATE(sym->type) && getNelements(type, ilist)>1) {
591           werror (W_EXCESS_INITIALIZERS, "scalar", sym->name, sym->lineDef);
592         }
593
594         if (!(val = list2val (ilist))) {
595           // assuming a warning has been thrown
596           val=constVal("0");
597         }
598
599         if (val->type != type) {
600           val = valCastLiteral(type, floatFromVal(val));
601         }
602         
603         switch (getSize (type)) {
604         case 1:
605                 if (!val)
606                         tfprintf (oFile, "\t!db !constbyte\n", 0);
607                 else
608                         tfprintf (oFile, "\t!dbs\n",
609                                   aopLiteral (val, 0));
610                 break;
611
612         case 2:
613                 if (port->use_dw_for_init)
614                         tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
615                 else
616                         fprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
617                 break;
618         case 4:
619                 if (!val) {
620                         tfprintf (oFile, "\t!dw !constword\n", 0);
621                         tfprintf (oFile, "\t!dw !constword\n", 0);
622                 }
623                 else {
624                         fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
625                                  aopLiteral (val, 0), aopLiteral (val, 1),
626                                  aopLiteral (val, 2), aopLiteral (val, 3));
627                 }
628                 break;
629         }
630 }
631
632 /*-----------------------------------------------------------------*/
633 /* printIvalBitFields - generate initializer for bitfields         */
634 /*-----------------------------------------------------------------*/
635 void printIvalBitFields(symbol **sym, initList **ilist, FILE * oFile)
636 {
637         value *val ;
638         symbol *lsym = *sym;
639         initList *lilist = *ilist ;
640         unsigned long ival = 0;
641         int size =0;
642
643         
644         do {
645                 unsigned long i;
646                 val = list2val(lilist);
647                 if (size) {
648                         if (SPEC_BLEN(lsym->etype) > 8) {
649                                 size += ((SPEC_BLEN (lsym->etype) / 8) + 
650                                          (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
651                         }
652                 } else {
653                         size = ((SPEC_BLEN (lsym->etype) / 8) + 
654                                  (SPEC_BLEN (lsym->etype) % 8 ? 1 : 0));
655                 }
656                 i = (unsigned long)floatFromVal(val);
657                 i <<= SPEC_BSTR (lsym->etype);
658                 ival |= i;
659                 if (! ( lsym->next &&
660                         (IS_BITFIELD(lsym->next->type)) &&
661                         (SPEC_BSTR(lsym->next->etype)))) break;
662                 lsym = lsym->next;
663                 lilist = lilist->next;
664         } while (1);
665         switch (size) {
666         case 1:
667                 tfprintf (oFile, "\t!db !constbyte\n",ival);
668                 break;
669
670         case 2:
671                 tfprintf (oFile, "\t!dw !constword\n",ival);
672                 break;
673         case 4:
674                 tfprintf (oFile, "\t!db  !constword,!constword\n",
675                          (ival >> 8) & 0xffff, (ival & 0xffff));
676                 break;
677         }
678         *sym = lsym;
679         *ilist = lilist;
680 }
681
682 /*-----------------------------------------------------------------*/
683 /* printIvalStruct - generates initial value for structures        */
684 /*-----------------------------------------------------------------*/
685 void 
686 printIvalStruct (symbol * sym, sym_link * type,
687                  initList * ilist, FILE * oFile)
688 {
689         symbol *sflds;
690         initList *iloop;
691
692         sflds = SPEC_STRUCT (type)->fields;
693         if (ilist->type != INIT_DEEP) {
694                 werror (E_INIT_STRUCT, sym->name);
695                 return;
696         }
697
698         iloop = ilist->init.deep;
699
700         for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) {
701                 if (IS_BITFIELD(sflds->type)) {
702                         printIvalBitFields(&sflds,&iloop,oFile);
703                 } else {
704                         printIval (sym, sflds->type, iloop, oFile);
705                 }
706         }
707         if (iloop) {
708           werror (W_EXCESS_INITIALIZERS, "struct", sym->name, sym->lineDef);
709         }
710         return;
711 }
712
713 /*-----------------------------------------------------------------*/
714 /* printIvalChar - generates initital value for character array    */
715 /*-----------------------------------------------------------------*/
716 int 
717 printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s)
718 {
719   value *val;
720   int remain;
721
722   if (!s)
723     {
724
725       val = list2val (ilist);
726       /* if the value is a character string  */
727       if (IS_ARRAY (val->type) && IS_CHAR (val->etype))
728         {
729           if (!DCL_ELEM (type))
730             DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1;
731
732           printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type));
733
734           if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) - 1)) > 0)
735             while (remain--)
736               tfprintf (oFile, "\t!db !constbyte\n", 0);
737
738           return 1;
739         }
740       else
741         return 0;
742     }
743   else
744     printChar (oFile, s, strlen (s) + 1);
745   return 1;
746 }
747
748 /*-----------------------------------------------------------------*/
749 /* printIvalArray - generates code for array initialization        */
750 /*-----------------------------------------------------------------*/
751 void
752 printIvalArray (symbol * sym, sym_link * type, initList * ilist,
753                 FILE * oFile)
754 {
755   initList *iloop;
756   int lcnt = 0, size = 0;
757   sym_link *last_type;
758
759   /* take care of the special   case  */
760   /* array of characters can be init  */
761   /* by a string                      */
762   if (IS_CHAR (type->next)) {
763     if (!IS_LITERAL(list2val(ilist)->etype)) {
764       werror (E_CONST_EXPECTED);
765       return;
766     }
767     if (printIvalChar (type,
768                        (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
769                        oFile, SPEC_CVAL (sym->etype).v_char))
770       return;
771   }
772   /* not the special case             */
773   if (ilist->type != INIT_DEEP)
774     {
775       werror (E_INIT_STRUCT, sym->name);
776       return;
777     }
778
779   iloop = ilist->init.deep;
780   lcnt = DCL_ELEM (type);
781   for (last_type = type->next; last_type && DCL_ELEM (last_type); last_type = last_type->next)
782     lcnt *= DCL_ELEM (last_type);
783
784   for (;;)
785     {
786       size++;
787       printIval (sym, type->next, iloop, oFile);
788       iloop = (iloop ? iloop->next : NULL);
789
790
791       /* if not array limits given & we */
792       /* are out of initialisers then   */
793       if (!DCL_ELEM (type) && !iloop)
794         break;
795
796       /* no of elements given and we    */
797       /* have generated for all of them */
798       if (!--lcnt) {
799         /* if initializers left */
800         if (iloop) {
801           werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef);
802         }
803         break;
804       }
805     }
806
807   /* if we have not been given a size  */
808   if (!DCL_ELEM (type))
809     DCL_ELEM (type) = size;
810
811   return;
812 }
813
814 /*-----------------------------------------------------------------*/
815 /* printIvalFuncPtr - generate initial value for function pointers */
816 /*-----------------------------------------------------------------*/
817 void 
818 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
819 {
820   value *val;
821   int dLvl = 0;
822
823   val = list2val (ilist);
824
825   if (!val) {
826     // an error has been thrown allready
827     val=constVal("0");
828   }
829
830   if (IS_LITERAL(val->etype)) {
831     if (compareType(type,val->etype)==0) {
832       werror (E_INCOMPAT_TYPES);
833       printFromToType (val->type, type);
834     }
835     printIvalCharPtr (NULL, type, val, oFile);
836     return;
837   }
838
839   /* check the types   */
840   if ((dLvl = compareType (val->type, type->next)) <= 0)
841     {
842       tfprintf (oFile, "\t!dw !constword\n", 0);
843       return;
844     }
845
846   /* now generate the name */
847   if (!val->sym)
848     {
849       if (port->use_dw_for_init)
850         {
851           tfprintf (oFile, "\t!dws\n", val->name);
852         }
853       else
854         {
855           printPointerType (oFile, val->name);
856         }
857     }
858   else if (port->use_dw_for_init)
859     {
860       tfprintf (oFile, "\t!dws\n", val->sym->rname);
861     }
862   else
863     {
864       printPointerType (oFile, val->sym->rname);
865     }
866
867   return;
868 }
869
870 /*-----------------------------------------------------------------*/
871 /* printIvalCharPtr - generates initial values for character pointers */
872 /*-----------------------------------------------------------------*/
873 int 
874 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
875 {
876   int size = 0;
877
878   /* PENDING: this is _very_ mcs51 specific, including a magic
879      number...
880      It's also endin specific.
881    */
882   size = getSize (type);
883
884   if (val->name && strlen (val->name))
885     {
886       if (size == 1)            /* This appears to be Z80 specific?? */
887         {
888           tfprintf (oFile,
889                     "\t!dbs\n", val->name);
890         }
891       else if (size == FPTRSIZE)
892         {
893           if (port->use_dw_for_init)
894             {
895               tfprintf (oFile, "\t!dws\n", val->name);
896             }
897           else
898             {
899               printPointerType (oFile, val->name);
900             }
901         }
902       else if (size == GPTRSIZE)
903         {
904           int type;
905           if (IS_PTR (val->type)) {
906             type = DCL_TYPE (val->type);
907           } else {
908             type = PTR_TYPE (SPEC_OCLS (val->etype));
909           }
910           if (val->sym && val->sym->isstrlit) {
911             // this is a literal string
912             type=CPOINTER;
913           }
914           printGPointerType (oFile, val->name, sym->name, type);
915         }
916       else
917         {
918           fprintf (stderr, "*** internal error: unknown size in "
919                    "printIvalCharPtr.\n");
920         }
921     }
922   else
923     {
924       // these are literals assigned to pointers
925       switch (size)
926         {
927         case 1:
928           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
929           break;
930         case 2:
931           if (port->use_dw_for_init)
932             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
933           else
934             tfprintf (oFile, "\t.byte %s,%s\n",
935                       aopLiteral (val, 0), aopLiteral (val, 1));
936           break;
937         case 3:
938           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
939             // non-zero mcs51 generic pointer
940             werror (E_LITERAL_GENERIC);
941           }
942           fprintf (oFile, "\t.byte %s,%s,%s\n",
943                    aopLiteral (val, 0), 
944                    aopLiteral (val, 1),
945                    aopLiteral (val, 2));
946           break;
947         case 4:
948           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
949             // non-zero ds390 generic pointer
950             werror (E_LITERAL_GENERIC);
951           }
952           fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
953                    aopLiteral (val, 0), 
954                    aopLiteral (val, 1), 
955                    aopLiteral (val, 2),
956                    aopLiteral (val, 3));
957           break;
958         default:
959           assert (0);
960         }
961     }
962
963   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
964     addSet (&statsg->syms, val->sym);
965   }
966
967   return 1;
968 }
969
970 /*-----------------------------------------------------------------*/
971 /* printIvalPtr - generates initial value for pointers             */
972 /*-----------------------------------------------------------------*/
973 void 
974 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
975 {
976   value *val;
977   int size;
978
979   /* if deep then   */
980   if (ilist->type == INIT_DEEP)
981     ilist = ilist->init.deep;
982
983   /* function pointer     */
984   if (IS_FUNC (type->next))
985     {
986       printIvalFuncPtr (type, ilist, oFile);
987       return;
988     }
989
990   if (!(val = initPointer (ilist, type)))
991     return;
992
993   /* if character pointer */
994   if (IS_CHAR (type->next))
995     if (printIvalCharPtr (sym, type, val, oFile))
996       return;
997
998   /* check the type      */
999   if (compareType (type, val->type) == 0) {
1000     werror (W_INIT_WRONG);
1001     printFromToType (val->type, type);
1002   }
1003
1004   /* if val is literal */
1005   if (IS_LITERAL (val->etype))
1006     {
1007       switch (getSize (type))
1008         {
1009         case 1:
1010           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
1011           break;
1012         case 2:
1013           if (port->use_dw_for_init)
1014             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
1015           else
1016             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1017           break;
1018         case 3: // how about '390??
1019           fprintf (oFile, "\t.byte %s,%s,#0x%d\n",
1020                    aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE);
1021         }
1022       return;
1023     }
1024
1025
1026   size = getSize (type);
1027
1028   if (size == 1)                /* Z80 specific?? */
1029     {
1030       tfprintf (oFile, "\t!dbs\n", val->name);
1031     }
1032   else if (size == FPTRSIZE)
1033     {
1034       if (port->use_dw_for_init) {
1035         tfprintf (oFile, "\t!dws\n", val->name);
1036       } else {
1037         printPointerType (oFile, val->name);
1038       }
1039     }
1040   else if (size == GPTRSIZE)
1041     {
1042       printGPointerType (oFile, val->name, sym->name,
1043                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1044                           PTR_TYPE (SPEC_OCLS (val->etype))));
1045     }
1046   return;
1047 }
1048
1049 /*-----------------------------------------------------------------*/
1050 /* printIval - generates code for initial value                    */
1051 /*-----------------------------------------------------------------*/
1052 void 
1053 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1054 {
1055   if (!ilist)
1056     return;
1057
1058   /* update line number for error msgs */
1059   lineno=sym->lineDef;
1060
1061   /* if structure then    */
1062   if (IS_STRUCT (type))
1063     {
1064       printIvalStruct (sym, type, ilist, oFile);
1065       return;
1066     }
1067
1068   /* if this is a pointer */
1069   if (IS_PTR (type))
1070     {
1071       printIvalPtr (sym, type, ilist, oFile);
1072       return;
1073     }
1074
1075   /* if this is an array   */
1076   if (IS_ARRAY (type))
1077     {
1078       printIvalArray (sym, type, ilist, oFile);
1079       return;
1080     }
1081
1082   /* if type is SPECIFIER */
1083   if (IS_SPEC (type))
1084     {
1085       printIvalType (sym, type, ilist, oFile);
1086       return;
1087     }
1088 }
1089
1090 /*-----------------------------------------------------------------*/
1091 /* emitStaticSeg - emitcode for the static segment                 */
1092 /*-----------------------------------------------------------------*/
1093 void 
1094 emitStaticSeg (memmap * map, FILE * out)
1095 {
1096   symbol *sym;
1097
1098   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1099
1100   /* for all variables in this segment do */
1101   for (sym = setFirstItem (map->syms); sym;
1102        sym = setNextItem (map->syms))
1103     {
1104
1105       /* if it is "extern" then do nothing */
1106       if (IS_EXTERN (sym->etype))
1107         continue;
1108
1109       /* if it is not static add it to the public
1110          table */
1111       if (!IS_STATIC (sym->etype))
1112         {
1113           addSetHead (&publics, sym);
1114         }
1115
1116       /* print extra debug info if required */
1117       if (options.debug) {
1118         cdbSymbol (sym, cdbFile, FALSE, FALSE);
1119         if (!sym->level)
1120           {                     /* global */
1121             if (IS_STATIC (sym->etype))
1122               fprintf (out, "F%s$", moduleName);        /* scope is file */
1123             else
1124               fprintf (out, "G$");      /* scope is global */
1125           }
1126         else
1127           /* symbol is local */
1128           fprintf (out, "L%s$",
1129                    (sym->localof ? sym->localof->name : "-null-"));
1130         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1131       }
1132       
1133       /* if it has an absolute address */
1134       if (SPEC_ABSA (sym->etype))
1135         {
1136           if (options.debug)
1137             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1138           
1139           fprintf (out, "%s\t=\t0x%04x\n",
1140                    sym->rname,
1141                    SPEC_ADDR (sym->etype));
1142         }
1143       else
1144         {
1145           if (options.debug)
1146             fprintf (out, " == .\n");
1147           
1148           /* if it has an initial value */
1149           if (sym->ival)
1150             {
1151               fprintf (out, "%s:\n", sym->rname);
1152               noAlloc++;
1153               resolveIvalSym (sym->ival);
1154               printIval (sym, sym->type, sym->ival, out);
1155               noAlloc--;
1156             }
1157           else {
1158               /* allocate space */
1159               int size = getSize (sym->type);
1160               
1161               if (size==0) {
1162                   werror(E_UNKNOWN_SIZE,sym->name);
1163               }
1164               fprintf (out, "%s:\n", sym->rname);
1165               /* special case for character strings */
1166               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1167                   SPEC_CVAL (sym->etype).v_char)
1168                   printChar (out,
1169                              SPEC_CVAL (sym->etype).v_char,
1170                              strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1171               else
1172                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1173             }
1174         }
1175     }
1176 }
1177
1178 /*-----------------------------------------------------------------*/
1179 /* emitMaps - emits the code for the data portion the code         */
1180 /*-----------------------------------------------------------------*/
1181 void 
1182 emitMaps (void)
1183 {
1184   inInitMode++;
1185   /* no special considerations for the following
1186      data, idata & bit & xdata */
1187   emitRegularMap (data, TRUE, TRUE);
1188   emitRegularMap (idata, TRUE, TRUE);
1189   emitRegularMap (bit, TRUE, FALSE);
1190   emitRegularMap (xdata, TRUE, TRUE);
1191   if (port->genXINIT) {
1192     emitRegularMap (xidata, TRUE, TRUE);
1193   }
1194   emitRegularMap (sfr, FALSE, FALSE);
1195   emitRegularMap (sfrbit, FALSE, FALSE);
1196   emitRegularMap (home, TRUE, FALSE);
1197   emitRegularMap (code, TRUE, FALSE);
1198
1199   emitStaticSeg (statsg, code->oFile);
1200   if (port->genXINIT) {
1201     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1202     emitStaticSeg (xinit, code->oFile);
1203   }
1204   inInitMode--;
1205 }
1206
1207 /*-----------------------------------------------------------------*/
1208 /* flushStatics - flush all currently defined statics out to file  */
1209 /*  and delete.  Temporary function                                */
1210 /*-----------------------------------------------------------------*/
1211 void 
1212 flushStatics (void)
1213 {
1214   emitStaticSeg (statsg, codeOutFile);
1215   statsg->syms = NULL;
1216 }
1217
1218 /*-----------------------------------------------------------------*/
1219 /* createInterruptVect - creates the interrupt vector              */
1220 /*-----------------------------------------------------------------*/
1221 void 
1222 createInterruptVect (FILE * vFile)
1223 {
1224   unsigned i = 0;
1225   mainf = newSymbol ("main", 0);
1226   mainf->block = 0;
1227
1228   /* only if the main function exists */
1229   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1230     {
1231       if (!options.cc_only && !noAssemble && !options.c1mode)
1232         werror (E_NO_MAIN);
1233       return;
1234     }
1235
1236   /* if the main is only a prototype ie. no body then do nothing */
1237   if (!IFFUNC_HASBODY(mainf->type))
1238     {
1239       /* if ! compile only then main function should be present */
1240       if (!options.cc_only && !noAssemble)
1241         werror (E_NO_MAIN);
1242       return;
1243     }
1244
1245   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1246   fprintf (vFile, "__interrupt_vect:\n");
1247
1248
1249   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1250     {
1251       /* "generic" interrupt table header (if port doesn't specify one).
1252        * Look suspiciously like 8051 code to me...
1253        */
1254
1255       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1256
1257
1258       /* now for the other interrupts */
1259       for (; i < maxInterrupts; i++)
1260         {
1261           if (interrupts[i])
1262             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1263           else
1264             fprintf (vFile, "\treti\n\t.ds\t7\n");
1265         }
1266     }
1267 }
1268
1269 char *iComments1 =
1270 {
1271   ";--------------------------------------------------------\n"
1272   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1273
1274 char *iComments2 =
1275 {
1276   ";--------------------------------------------------------\n"};
1277
1278
1279 /*-----------------------------------------------------------------*/
1280 /* initialComments - puts in some initial comments                 */
1281 /*-----------------------------------------------------------------*/
1282 void 
1283 initialComments (FILE * afile)
1284 {
1285   time_t t;
1286   time (&t);
1287   fprintf (afile, "%s", iComments1);
1288   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1289   fprintf (afile, "%s", iComments2);
1290 }
1291
1292 /*-----------------------------------------------------------------*/
1293 /* printPublics - generates .global for publics                    */
1294 /*-----------------------------------------------------------------*/
1295 void 
1296 printPublics (FILE * afile)
1297 {
1298   symbol *sym;
1299
1300   fprintf (afile, "%s", iComments2);
1301   fprintf (afile, "; Public variables in this module\n");
1302   fprintf (afile, "%s", iComments2);
1303
1304   for (sym = setFirstItem (publics); sym;
1305        sym = setNextItem (publics))
1306     tfprintf (afile, "\t!global\n", sym->rname);
1307 }
1308
1309 /*-----------------------------------------------------------------*/
1310 /* printExterns - generates .global for externs                    */
1311 /*-----------------------------------------------------------------*/
1312 void 
1313 printExterns (FILE * afile)
1314 {
1315   symbol *sym;
1316
1317   fprintf (afile, "%s", iComments2);
1318   fprintf (afile, "; Externals used\n");
1319   fprintf (afile, "%s", iComments2);
1320
1321   for (sym = setFirstItem (externs); sym;
1322        sym = setNextItem (externs))
1323     tfprintf (afile, "\t!extern\n", sym->rname);
1324 }
1325
1326 /*-----------------------------------------------------------------*/
1327 /* emitOverlay - will emit code for the overlay stuff              */
1328 /*-----------------------------------------------------------------*/
1329 static void 
1330 emitOverlay (FILE * afile)
1331 {
1332   set *ovrset;
1333
1334   if (!elementsInSet (ovrSetSets))
1335     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1336
1337   /* for each of the sets in the overlay segment do */
1338   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1339        ovrset = setNextItem (ovrSetSets))
1340     {
1341
1342       symbol *sym;
1343
1344       if (elementsInSet (ovrset))
1345         {
1346           /* output the area informtion */
1347           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1348         }
1349
1350       for (sym = setFirstItem (ovrset); sym;
1351            sym = setNextItem (ovrset))
1352         {
1353           /* if extern then it is in the publics table: do nothing */
1354           if (IS_EXTERN (sym->etype))
1355             continue;
1356
1357           /* if allocation required check is needed
1358              then check if the symbol really requires
1359              allocation only for local variables */
1360           if (!IS_AGGREGATE (sym->type) &&
1361               !(sym->_isparm && !IS_REGPARM (sym->etype))
1362               && !sym->allocreq && sym->level)
1363             continue;
1364
1365           /* if global variable & not static or extern
1366              and addPublics allowed then add it to the public set */
1367           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1368               && !IS_STATIC (sym->etype))
1369             {
1370               addSetHead (&publics, sym);
1371             }
1372
1373           /* if extern then do nothing or is a function
1374              then do nothing */
1375           if (IS_FUNC (sym->type))
1376             continue;
1377
1378           /* print extra debug info if required */
1379           if (options.debug)
1380             {
1381               cdbSymbol (sym, cdbFile, FALSE, FALSE);
1382
1383               if (!sym->level)
1384                 {               /* global */
1385                   if (IS_STATIC (sym->etype))
1386                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1387                   else
1388                     fprintf (afile, "G$");      /* scope is global */
1389                 }
1390               else
1391                 /* symbol is local */
1392                 fprintf (afile, "L%s$",
1393                          (sym->localof ? sym->localof->name : "-null-"));
1394               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1395             }
1396
1397           /* if is has an absolute address then generate
1398              an equate for this no need to allocate space */
1399           if (SPEC_ABSA (sym->etype))
1400             {
1401
1402               if (options.debug)
1403                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1404
1405               fprintf (afile, "%s\t=\t0x%04x\n",
1406                        sym->rname,
1407                        SPEC_ADDR (sym->etype));
1408             }
1409           else {
1410               int size = getSize(sym->type);
1411
1412               if (size==0) {
1413                   werror(E_UNKNOWN_SIZE,sym->name);
1414               }       
1415               if (options.debug)
1416                   fprintf (afile, "==.\n");
1417               
1418               /* allocate space */
1419               tfprintf (afile, "!labeldef\n", sym->rname);
1420               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1421           }
1422           
1423         }
1424     }
1425 }
1426
1427 /*-----------------------------------------------------------------*/
1428 /* glue - the final glue that hold the whole thing together        */
1429 /*-----------------------------------------------------------------*/
1430 void 
1431 glue (void)
1432 {
1433   FILE *vFile;
1434   FILE *asmFile;
1435   FILE *ovrFile = tempfile ();
1436
1437   addSetHead (&tmpfileSet, ovrFile);
1438   /* print the global struct definitions */
1439   if (options.debug)
1440     cdbStructBlock (0, cdbFile);
1441
1442   vFile = tempfile ();
1443   /* PENDING: this isnt the best place but it will do */
1444   if (port->general.glue_up_main)
1445     {
1446       /* create the interrupt vector table */
1447       createInterruptVect (vFile);
1448     }
1449
1450   addSetHead (&tmpfileSet, vFile);
1451
1452   /* emit code for the all the variables declared */
1453   emitMaps ();
1454   /* do the overlay segments */
1455   emitOverlay (ovrFile);
1456
1457   /* now put it all together into the assembler file */
1458   /* create the assembler file name */
1459
1460   /* -o option overrides default name? */
1461   if ((noAssemble || options.c1mode) && fullDstFileName)
1462     {
1463       strcpy (scratchFileName, fullDstFileName);
1464     }
1465   else
1466     {
1467       strcpy (scratchFileName, dstFileName);
1468       strcat (scratchFileName, port->assembler.file_ext);
1469     }
1470
1471   if (!(asmFile = fopen (scratchFileName, "w")))
1472     {
1473       werror (E_FILE_OPEN_ERR, scratchFileName);
1474       exit (1);
1475     }
1476
1477   /* initial comments */
1478   initialComments (asmFile);
1479
1480   /* print module name */
1481   tfprintf (asmFile, "\t!module\n", moduleName);
1482   tfprintf (asmFile, "\t!fileprelude\n");
1483
1484   /* Let the port generate any global directives, etc. */
1485   if (port->genAssemblerPreamble)
1486     {
1487       port->genAssemblerPreamble (asmFile);
1488     }
1489
1490   /* print the global variables in this module */
1491   printPublics (asmFile);
1492   if (port->assembler.externGlobal)
1493     printExterns (asmFile);
1494
1495   /* copy the sfr segment */
1496   fprintf (asmFile, "%s", iComments2);
1497   fprintf (asmFile, "; special function registers\n");
1498   fprintf (asmFile, "%s", iComments2);
1499   copyFile (asmFile, sfr->oFile);
1500
1501   /* copy the sbit segment */
1502   fprintf (asmFile, "%s", iComments2);
1503   fprintf (asmFile, "; special function bits \n");
1504   fprintf (asmFile, "%s", iComments2);
1505   copyFile (asmFile, sfrbit->oFile);
1506   
1507   /*JCF: Create the areas for the register banks*/
1508   if(port->general.glue_up_main &&
1509      (TARGET_IS_MCS51 || TARGET_IS_DS390 || TARGET_IS_XA51))
1510   {
1511           if(RegBankUsed[0]||RegBankUsed[1]||RegBankUsed[2]||RegBankUsed[3])
1512           {
1513                  fprintf (asmFile, "%s", iComments2);
1514                  fprintf (asmFile, "; overlayable register banks \n");
1515                  fprintf (asmFile, "%s", iComments2);
1516                  if(RegBankUsed[0])
1517                         fprintf (asmFile, "\t.area REG_BANK_0\t(REL,OVR,DATA)\n\t.ds 8\n");
1518                  if(RegBankUsed[1]||options.parms_in_bank1)
1519                         fprintf (asmFile, "\t.area REG_BANK_1\t(REL,OVR,DATA)\n\t.ds 8\n");
1520                  if(RegBankUsed[2])
1521                         fprintf (asmFile, "\t.area REG_BANK_2\t(REL,OVR,DATA)\n\t.ds 8\n");
1522                  if(RegBankUsed[3])
1523                         fprintf (asmFile, "\t.area REG_BANK_3\t(REL,OVR,DATA)\n\t.ds 8\n");
1524           }
1525   }
1526
1527   /* copy the data segment */
1528   fprintf (asmFile, "%s", iComments2);
1529   fprintf (asmFile, "; internal ram data\n");
1530   fprintf (asmFile, "%s", iComments2);
1531   copyFile (asmFile, data->oFile);
1532
1533
1534   /* create the overlay segments */
1535   if (overlay) {
1536     fprintf (asmFile, "%s", iComments2);
1537     fprintf (asmFile, "; overlayable items in internal ram \n");
1538     fprintf (asmFile, "%s", iComments2);
1539     copyFile (asmFile, ovrFile);
1540   }
1541
1542   /* create the stack segment MOF */
1543   if (mainf && IFFUNC_HASBODY(mainf->type))
1544     {
1545       fprintf (asmFile, "%s", iComments2);
1546       fprintf (asmFile, "; Stack segment in internal ram \n");
1547       fprintf (asmFile, "%s", iComments2);
1548       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1549                "__start__stack:\n\t.ds\t1\n\n");
1550     }
1551
1552   /* create the idata segment */
1553   if (idata) {
1554     fprintf (asmFile, "%s", iComments2);
1555     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1556     fprintf (asmFile, "%s", iComments2);
1557     copyFile (asmFile, idata->oFile);
1558   }
1559
1560   /* copy the bit segment */
1561   fprintf (asmFile, "%s", iComments2);
1562   fprintf (asmFile, "; bit data\n");
1563   fprintf (asmFile, "%s", iComments2);
1564   copyFile (asmFile, bit->oFile);
1565
1566   /* if external stack then reserve space of it */
1567   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1568     {
1569       fprintf (asmFile, "%s", iComments2);
1570       fprintf (asmFile, "; external stack \n");
1571       fprintf (asmFile, "%s", iComments2);
1572       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1573       fprintf (asmFile, "\t.ds 256\n");
1574     }
1575
1576
1577   /* copy xtern ram data */
1578   fprintf (asmFile, "%s", iComments2);
1579   fprintf (asmFile, "; external ram data\n");
1580   fprintf (asmFile, "%s", iComments2);
1581   copyFile (asmFile, xdata->oFile);
1582
1583   /* copy xternal initialized ram data */
1584   fprintf (asmFile, "%s", iComments2);
1585   fprintf (asmFile, "; external initialized ram data\n");
1586   fprintf (asmFile, "%s", iComments2);
1587   copyFile (asmFile, xidata->oFile);
1588
1589   /* copy the interrupt vector table */
1590   if (mainf && IFFUNC_HASBODY(mainf->type))
1591     {
1592       fprintf (asmFile, "%s", iComments2);
1593       fprintf (asmFile, "; interrupt vector \n");
1594       fprintf (asmFile, "%s", iComments2);
1595       copyFile (asmFile, vFile);
1596     }
1597
1598   /* copy global & static initialisations */
1599   fprintf (asmFile, "%s", iComments2);
1600   fprintf (asmFile, "; global & static initialisations\n");
1601   fprintf (asmFile, "%s", iComments2);
1602
1603   /* Everywhere we generate a reference to the static_name area,
1604    * (which is currently only here), we immediately follow it with a
1605    * definition of the post_static_name area. This guarantees that
1606    * the post_static_name area will immediately follow the static_name
1607    * area.
1608    */
1609   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1610   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1611   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1612
1613   if (mainf && IFFUNC_HASBODY(mainf->type))
1614     {
1615       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1616       /* if external stack is specified then the
1617          higher order byte of the xdatalocation is
1618          going into P2 and the lower order going into
1619          spx */
1620       if (options.useXstack)
1621         {
1622           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1623                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1624           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1625                    (unsigned int) options.xdata_loc & 0xff);
1626         }
1627
1628       /* initialise the stack pointer.  JCF: aslink takes care of the location */
1629         fprintf (asmFile, "\tmov\tsp,#__start__stack - 1\n");   /* MOF */
1630
1631       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1632       fprintf (asmFile, "\tmov\ta,dpl\n");
1633       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1634       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1635       fprintf (asmFile, "__sdcc_init_data:\n");
1636
1637       // if the port can copy the XINIT segment to XISEG
1638       if (port->genXINIT) {
1639         port->genXINIT(asmFile);
1640       }
1641
1642     }
1643   copyFile (asmFile, statsg->oFile);
1644
1645   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1646     {
1647       /* This code is generated in the post-static area.
1648        * This area is guaranteed to follow the static area
1649        * by the ugly shucking and jiving about 20 lines ago.
1650        */
1651       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1652       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1653     }
1654
1655   fprintf (asmFile,
1656            "%s"
1657            "; Home\n"
1658            "%s", iComments2, iComments2);
1659   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1660   copyFile (asmFile, home->oFile);
1661
1662   /* copy over code */
1663   fprintf (asmFile, "%s", iComments2);
1664   fprintf (asmFile, "; code\n");
1665   fprintf (asmFile, "%s", iComments2);
1666   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1667   if (mainf && IFFUNC_HASBODY(mainf->type))
1668     {
1669
1670       /* entry point @ start of CSEG */
1671       fprintf (asmFile, "__sdcc_program_startup:\n");
1672
1673       /* put in the call to main */
1674       fprintf (asmFile, "\tlcall\t_main\n");
1675       if (options.mainreturn)
1676         {
1677
1678           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1679           fprintf (asmFile, "\tret\n");
1680
1681         }
1682       else
1683         {
1684
1685           fprintf (asmFile, ";\treturn from main will lock up\n");
1686           fprintf (asmFile, "\tsjmp .\n");
1687         }
1688     }
1689   copyFile (asmFile, code->oFile);
1690
1691   if (port->genAssemblerEnd) {
1692       port->genAssemblerEnd(asmFile);
1693   }
1694   fclose (asmFile);
1695
1696   rm_tmpfiles ();
1697 }
1698
1699 /** Creates a temporary file name a'la tmpnam which avoids the bugs
1700     in cygwin wrt c:\tmp.
1701     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1702 */
1703 char *
1704 tempfilename (void)
1705 {
1706   const char *tmpdir = NULL;
1707   if (getenv ("TMP"))
1708     tmpdir = getenv ("TMP");
1709   else if (getenv ("TEMP"))
1710     tmpdir = getenv ("TEMP");
1711   else if (getenv ("TMPDIR"))
1712     tmpdir = getenv ("TMPDIR");
1713   if (tmpdir)
1714     {
1715       char *name = tempnam (tmpdir, "sdcc");
1716       if (name)
1717         {
1718           return name;
1719         }
1720     }
1721   return tmpnam (NULL);
1722 }
1723
1724 /** Creates a temporary file a'la tmpfile which avoids the bugs
1725     in cygwin wrt c:\tmp.
1726     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1727 */
1728 FILE *
1729 tempfile (void)
1730 {
1731   const char *tmpdir = NULL;
1732   if (getenv ("TMP"))
1733     tmpdir = getenv ("TMP");
1734   else if (getenv ("TEMP"))
1735     tmpdir = getenv ("TEMP");
1736   else if (getenv ("TMPDIR"))
1737     tmpdir = getenv ("TMPDIR");
1738   if (tmpdir)
1739     {
1740       char *name = Safe_strdup( tempnam (tmpdir, "sdcc"));
1741       if (name)
1742         {
1743           FILE *fp = fopen (name, "w+b");
1744           if (fp)
1745             {
1746               addSetHead (&tmpfileNameSet, name);
1747             }
1748           return fp;
1749         }
1750       return NULL;
1751     }
1752   return tmpfile ();
1753 }