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