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