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