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