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