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