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