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