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