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