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