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