Consolidate generic pointer code
[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
744   /* take care of the special   case  */
745   /* array of characters can be init  */
746   /* by a string                      */
747   if (IS_CHAR (type->next)) {
748     if (!IS_LITERAL(list2val(ilist)->etype)) {
749       werror (E_CONST_EXPECTED);
750       return;
751     }
752     if (printIvalChar (type,
753                        (ilist->type == INIT_DEEP ? ilist->init.deep : ilist),
754                        oFile, SPEC_CVAL (sym->etype).v_char))
755       return;
756   }
757   /* not the special case             */
758   if (ilist->type != INIT_DEEP)
759     {
760       werror (E_INIT_STRUCT, sym->name);
761       return;
762     }
763
764   iloop = ilist->init.deep;
765   lcnt = DCL_ELEM (type);
766
767   for (;;)
768     {
769       size++;
770       printIval (sym, type->next, iloop, oFile);
771       iloop = (iloop ? iloop->next : NULL);
772
773
774       /* if not array limits given & we */
775       /* are out of initialisers then   */
776       if (!DCL_ELEM (type) && !iloop)
777         break;
778
779       /* no of elements given and we    */
780       /* have generated for all of them */
781       if (!--lcnt) {
782         /* if initializers left */
783         if (iloop) {
784           werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef);
785         }
786         break;
787       }
788     }
789
790   /* if we have not been given a size  */
791   if (!DCL_ELEM (type))
792     DCL_ELEM (type) = size;
793
794   return;
795 }
796
797 /*-----------------------------------------------------------------*/
798 /* printIvalFuncPtr - generate initial value for function pointers */
799 /*-----------------------------------------------------------------*/
800 void 
801 printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile)
802 {
803   value *val;
804   int dLvl = 0;
805
806   val = list2val (ilist);
807
808   if (!val) {
809     // an error has been thrown allready
810     val=constVal("0");
811   }
812
813   if (IS_LITERAL(val->etype)) {
814     if (compareType(type,val->etype)==0) {
815       werror (E_INCOMPAT_TYPES);
816       printFromToType (val->type, type);
817     }
818     printIvalCharPtr (NULL, type, val, oFile);
819     return;
820   }
821
822   /* check the types   */
823   if ((dLvl = compareType (val->type, type->next)) <= 0)
824     {
825       tfprintf (oFile, "\t!dw !constword\n", 0);
826       return;
827     }
828
829   /* now generate the name */
830   if (!val->sym)
831     {
832       if (port->use_dw_for_init)
833         {
834           tfprintf (oFile, "\t!dws\n", val->name);
835         }
836       else
837         {
838           printPointerType (oFile, val->name);
839         }
840     }
841   else if (port->use_dw_for_init)
842     {
843       tfprintf (oFile, "\t!dws\n", val->sym->rname);
844     }
845   else
846     {
847       printPointerType (oFile, val->sym->rname);
848     }
849
850   return;
851 }
852
853 /*-----------------------------------------------------------------*/
854 /* printIvalCharPtr - generates initial values for character pointers */
855 /*-----------------------------------------------------------------*/
856 int 
857 printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile)
858 {
859   int size = 0;
860
861   /* PENDING: this is _very_ mcs51 specific, including a magic
862      number...
863      It's also endin specific.
864    */
865   size = getSize (type);
866
867   if (val->name && strlen (val->name))
868     {
869       if (size == 1)            /* This appears to be Z80 specific?? */
870         {
871           tfprintf (oFile,
872                     "\t!dbs\n", val->name);
873         }
874       else if (size == FPTRSIZE)
875         {
876           if (port->use_dw_for_init)
877             {
878               tfprintf (oFile, "\t!dws\n", val->name);
879             }
880           else
881             {
882               printPointerType (oFile, val->name);
883             }
884         }
885       else if (size == GPTRSIZE)
886         {
887           int type;
888           if (IS_PTR (val->type)) {
889             type = DCL_TYPE (val->type);
890           } else {
891             type = PTR_TYPE (SPEC_OCLS (val->etype));
892           }
893           if (val->sym && val->sym->isstrlit) {
894             // this is a literal string
895             type=CPOINTER;
896           }
897           printGPointerType (oFile, val->name, sym->name, type);
898         }
899       else
900         {
901           fprintf (stderr, "*** internal error: unknown size in "
902                    "printIvalCharPtr.\n");
903         }
904     }
905   else
906     {
907       // these are literals assigned to pointers
908       switch (size)
909         {
910         case 1:
911           tfprintf (oFile, "\t!dbs\n", aopLiteral (val, 0));
912           break;
913         case 2:
914           if (port->use_dw_for_init)
915             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, size));
916           else
917             tfprintf (oFile, "\t.byte %s,%s\n",
918                       aopLiteral (val, 0), aopLiteral (val, 1));
919           break;
920         case 3:
921           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
922             // non-zero mcs51 generic pointer
923             werror (E_LITERAL_GENERIC);
924           }
925           fprintf (oFile, "\t.byte %s,%s,%s\n",
926                    aopLiteral (val, 0), 
927                    aopLiteral (val, 1),
928                    aopLiteral (val, 2));
929           break;
930         case 4:
931           if (IS_GENPTR(type) && floatFromVal(val)!=0) {
932             // non-zero ds390 generic pointer
933             werror (E_LITERAL_GENERIC);
934           }
935           fprintf (oFile, "\t.byte %s,%s,%s,%s\n",
936                    aopLiteral (val, 0), 
937                    aopLiteral (val, 1), 
938                    aopLiteral (val, 2),
939                    aopLiteral (val, 3));
940           break;
941         default:
942           assert (0);
943         }
944     }
945
946   if (val->sym && val->sym->isstrlit && !isinSet(statsg->syms, val->sym)) {
947     addSet (&statsg->syms, val->sym);
948   }
949
950   return 1;
951 }
952
953 /*-----------------------------------------------------------------*/
954 /* printIvalPtr - generates initial value for pointers             */
955 /*-----------------------------------------------------------------*/
956 void 
957 printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
958 {
959   value *val;
960   int size;
961
962   /* if deep then   */
963   if (ilist->type == INIT_DEEP)
964     ilist = ilist->init.deep;
965
966   /* function pointer     */
967   if (IS_FUNC (type->next))
968     {
969       printIvalFuncPtr (type, ilist, oFile);
970       return;
971     }
972
973   if (!(val = initPointer (ilist, type)))
974     return;
975
976   /* if character pointer */
977   if (IS_CHAR (type->next))
978     if (printIvalCharPtr (sym, type, val, oFile))
979       return;
980
981   /* check the type      */
982   if (compareType (type, val->type) == 0) {
983     werror (W_INIT_WRONG);
984     printFromToType (val->type, type);
985   }
986
987   /* if val is literal */
988   if (IS_LITERAL (val->etype))
989     {
990       switch (getSize (type))
991         {
992         case 1:
993           tfprintf (oFile, "\t!db !constbyte\n", (unsigned int) floatFromVal (val) & 0xff);
994           break;
995         case 2:
996           if (port->use_dw_for_init)
997             tfprintf (oFile, "\t!dws\n", aopLiteralLong (val, 0, 2));
998           else
999             tfprintf (oFile, "\t.byte %s,%s\n", aopLiteral (val, 0), aopLiteral (val, 1));
1000           break;
1001         case 3: // how about '390??
1002           fprintf (oFile, "\t.byte %s,%s,#0x%d\n",
1003                    aopLiteral (val, 0), aopLiteral (val, 1), GPTYPE_CODE);
1004         }
1005       return;
1006     }
1007
1008
1009   size = getSize (type);
1010
1011   if (size == 1)                /* Z80 specific?? */
1012     {
1013       tfprintf (oFile, "\t!dbs\n", val->name);
1014     }
1015   else if (size == FPTRSIZE)
1016     {
1017       if (port->use_dw_for_init) {
1018         tfprintf (oFile, "\t!dws\n", val->name);
1019       } else {
1020         printPointerType (oFile, val->name);
1021       }
1022     }
1023   else if (size == GPTRSIZE)
1024     {
1025       printGPointerType (oFile, val->name, sym->name,
1026                          (IS_PTR (val->type) ? DCL_TYPE (val->type) :
1027                           PTR_TYPE (SPEC_OCLS (val->etype))));
1028     }
1029   return;
1030 }
1031
1032 /*-----------------------------------------------------------------*/
1033 /* printIval - generates code for initial value                    */
1034 /*-----------------------------------------------------------------*/
1035 void 
1036 printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile)
1037 {
1038   if (!ilist)
1039     return;
1040
1041   /* update line number for error msgs */
1042   lineno=sym->lineDef;
1043
1044   /* if structure then    */
1045   if (IS_STRUCT (type))
1046     {
1047       printIvalStruct (sym, type, ilist, oFile);
1048       return;
1049     }
1050
1051   /* if this is a pointer */
1052   if (IS_PTR (type))
1053     {
1054       printIvalPtr (sym, type, ilist, oFile);
1055       return;
1056     }
1057
1058   /* if this is an array   */
1059   if (IS_ARRAY (type))
1060     {
1061       printIvalArray (sym, type, ilist, oFile);
1062       return;
1063     }
1064
1065   /* if type is SPECIFIER */
1066   if (IS_SPEC (type))
1067     {
1068       printIvalType (sym, type, ilist, oFile);
1069       return;
1070     }
1071 }
1072
1073 /*-----------------------------------------------------------------*/
1074 /* emitStaticSeg - emitcode for the static segment                 */
1075 /*-----------------------------------------------------------------*/
1076 void 
1077 emitStaticSeg (memmap * map, FILE * out)
1078 {
1079   symbol *sym;
1080
1081   /* fprintf(out, "\t.area\t%s\n", map->sname); */
1082
1083   /* for all variables in this segment do */
1084   for (sym = setFirstItem (map->syms); sym;
1085        sym = setNextItem (map->syms))
1086     {
1087
1088       /* if it is "extern" then do nothing */
1089       if (IS_EXTERN (sym->etype))
1090         continue;
1091
1092       /* if it is not static add it to the public
1093          table */
1094       if (!IS_STATIC (sym->etype))
1095         {
1096           addSetHead (&publics, sym);
1097         }
1098
1099       /* print extra debug info if required */
1100       if (options.debug) {
1101         cdbSymbol (sym, cdbFile, FALSE, FALSE);
1102         if (!sym->level)
1103           {                     /* global */
1104             if (IS_STATIC (sym->etype))
1105               fprintf (out, "F%s$", moduleName);        /* scope is file */
1106             else
1107               fprintf (out, "G$");      /* scope is global */
1108           }
1109         else
1110           /* symbol is local */
1111           fprintf (out, "L%s$",
1112                    (sym->localof ? sym->localof->name : "-null-"));
1113         fprintf (out, "%s$%d$%d", sym->name, sym->level, sym->block);
1114       }
1115       
1116       /* if it has an absolute address */
1117       if (SPEC_ABSA (sym->etype))
1118         {
1119           if (options.debug)
1120             fprintf (out, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1121           
1122           fprintf (out, "%s\t=\t0x%04x\n",
1123                    sym->rname,
1124                    SPEC_ADDR (sym->etype));
1125         }
1126       else
1127         {
1128           if (options.debug)
1129             fprintf (out, " == .\n");
1130           
1131           /* if it has an initial value */
1132           if (sym->ival)
1133             {
1134               fprintf (out, "%s:\n", sym->rname);
1135               noAlloc++;
1136               resolveIvalSym (sym->ival);
1137               printIval (sym, sym->type, sym->ival, out);
1138               noAlloc--;
1139             }
1140           else {
1141               /* allocate space */
1142               int size = getSize (sym->type);
1143               
1144               if (size==0) {
1145                   werror(E_UNKNOWN_SIZE,sym->name);
1146               }
1147               fprintf (out, "%s:\n", sym->rname);
1148               /* special case for character strings */
1149               if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) &&
1150                   SPEC_CVAL (sym->etype).v_char)
1151                   printChar (out,
1152                              SPEC_CVAL (sym->etype).v_char,
1153                              strlen (SPEC_CVAL (sym->etype).v_char) + 1);
1154               else
1155                   tfprintf (out, "\t!ds\n", (unsigned int) size & 0xffff);
1156             }
1157         }
1158     }
1159 }
1160
1161 /*-----------------------------------------------------------------*/
1162 /* emitMaps - emits the code for the data portion the code         */
1163 /*-----------------------------------------------------------------*/
1164 void 
1165 emitMaps ()
1166 {
1167   inInitMode++;
1168   /* no special considerations for the following
1169      data, idata & bit & xdata */
1170   emitRegularMap (data, TRUE, TRUE);
1171   emitRegularMap (idata, TRUE, TRUE);
1172   emitRegularMap (bit, TRUE, FALSE);
1173   emitRegularMap (xdata, TRUE, TRUE);
1174   if (port->genXINIT) {
1175     emitRegularMap (xidata, TRUE, TRUE);
1176   }
1177   emitRegularMap (sfr, FALSE, FALSE);
1178   emitRegularMap (sfrbit, FALSE, FALSE);
1179   emitRegularMap (home, TRUE, FALSE);
1180   emitRegularMap (code, TRUE, FALSE);
1181
1182   emitStaticSeg (statsg, code->oFile);
1183   if (port->genXINIT) {
1184     tfprintf (code->oFile, "\t!area\n", xinit->sname);
1185     emitStaticSeg (xinit, code->oFile);
1186   }
1187   inInitMode--;
1188 }
1189
1190 /*-----------------------------------------------------------------*/
1191 /* flushStatics - flush all currently defined statics out to file  */
1192 /*  and delete.  Temporary function                                */
1193 /*-----------------------------------------------------------------*/
1194 void 
1195 flushStatics (void)
1196 {
1197   emitStaticSeg (statsg, codeOutFile);
1198   statsg->syms = NULL;
1199 }
1200
1201 /*-----------------------------------------------------------------*/
1202 /* createInterruptVect - creates the interrupt vector              */
1203 /*-----------------------------------------------------------------*/
1204 void 
1205 createInterruptVect (FILE * vFile)
1206 {
1207   unsigned i = 0;
1208   mainf = newSymbol ("main", 0);
1209   mainf->block = 0;
1210
1211   /* only if the main function exists */
1212   if (!(mainf = findSymWithLevel (SymbolTab, mainf)))
1213     {
1214       if (!options.cc_only && !noAssemble)
1215         werror (E_NO_MAIN);
1216       return;
1217     }
1218
1219   /* if the main is only a prototype ie. no body then do nothing */
1220   if (!IFFUNC_HASBODY(mainf->type))
1221     {
1222       /* if ! compile only then main function should be present */
1223       if (!options.cc_only && !noAssemble)
1224         werror (E_NO_MAIN);
1225       return;
1226     }
1227
1228   tfprintf (vFile, "\t!areacode\n", CODE_NAME);
1229   fprintf (vFile, "__interrupt_vect:\n");
1230
1231
1232   if (!port->genIVT || !(port->genIVT (vFile, interrupts, maxInterrupts)))
1233     {
1234       /* "generic" interrupt table header (if port doesn't specify one).
1235        * Look suspiciously like 8051 code to me...
1236        */
1237
1238       fprintf (vFile, "\tljmp\t__sdcc_gsinit_startup\n");
1239
1240
1241       /* now for the other interrupts */
1242       for (; i < maxInterrupts; i++)
1243         {
1244           if (interrupts[i])
1245             fprintf (vFile, "\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname);
1246           else
1247             fprintf (vFile, "\treti\n\t.ds\t7\n");
1248         }
1249     }
1250 }
1251
1252 char *iComments1 =
1253 {
1254   ";--------------------------------------------------------\n"
1255   "; File Created by SDCC : FreeWare ANSI-C Compiler\n"};
1256
1257 char *iComments2 =
1258 {
1259   ";--------------------------------------------------------\n"};
1260
1261
1262 /*-----------------------------------------------------------------*/
1263 /* initialComments - puts in some initial comments                 */
1264 /*-----------------------------------------------------------------*/
1265 void 
1266 initialComments (FILE * afile)
1267 {
1268   time_t t;
1269   time (&t);
1270   fprintf (afile, "%s", iComments1);
1271   fprintf (afile, "; Version %s %s\n", VersionString, asctime (localtime (&t)));
1272   fprintf (afile, "%s", iComments2);
1273 }
1274
1275 /*-----------------------------------------------------------------*/
1276 /* printPublics - generates .global for publics                    */
1277 /*-----------------------------------------------------------------*/
1278 void 
1279 printPublics (FILE * afile)
1280 {
1281   symbol *sym;
1282
1283   fprintf (afile, "%s", iComments2);
1284   fprintf (afile, "; Public variables in this module\n");
1285   fprintf (afile, "%s", iComments2);
1286
1287   for (sym = setFirstItem (publics); sym;
1288        sym = setNextItem (publics))
1289     tfprintf (afile, "\t!global\n", sym->rname);
1290 }
1291
1292 /*-----------------------------------------------------------------*/
1293 /* printExterns - generates .global for externs                    */
1294 /*-----------------------------------------------------------------*/
1295 void 
1296 printExterns (FILE * afile)
1297 {
1298   symbol *sym;
1299
1300   fprintf (afile, "%s", iComments2);
1301   fprintf (afile, "; Externals used\n");
1302   fprintf (afile, "%s", iComments2);
1303
1304   for (sym = setFirstItem (externs); sym;
1305        sym = setNextItem (externs))
1306     tfprintf (afile, "\t!extern\n", sym->rname);
1307 }
1308
1309 /*-----------------------------------------------------------------*/
1310 /* emitOverlay - will emit code for the overlay stuff              */
1311 /*-----------------------------------------------------------------*/
1312 static void 
1313 emitOverlay (FILE * afile)
1314 {
1315   set *ovrset;
1316
1317   if (!elementsInSet (ovrSetSets))
1318     tfprintf (afile, "\t!area\n", port->mem.overlay_name);
1319
1320   /* for each of the sets in the overlay segment do */
1321   for (ovrset = setFirstItem (ovrSetSets); ovrset;
1322        ovrset = setNextItem (ovrSetSets))
1323     {
1324
1325       symbol *sym;
1326
1327       if (elementsInSet (ovrset))
1328         {
1329           /* output the area informtion */
1330           fprintf (afile, "\t.area\t%s\n", port->mem.overlay_name);     /* MOF */
1331         }
1332
1333       for (sym = setFirstItem (ovrset); sym;
1334            sym = setNextItem (ovrset))
1335         {
1336           /* if extern then it is in the publics table: do nothing */
1337           if (IS_EXTERN (sym->etype))
1338             continue;
1339
1340           /* if allocation required check is needed
1341              then check if the symbol really requires
1342              allocation only for local variables */
1343           if (!IS_AGGREGATE (sym->type) &&
1344               !(sym->_isparm && !IS_REGPARM (sym->etype))
1345               && !sym->allocreq && sym->level)
1346             continue;
1347
1348           /* if global variable & not static or extern
1349              and addPublics allowed then add it to the public set */
1350           if ((sym->_isparm && !IS_REGPARM (sym->etype))
1351               && !IS_STATIC (sym->etype))
1352             {
1353               addSetHead (&publics, sym);
1354             }
1355
1356           /* if extern then do nothing or is a function
1357              then do nothing */
1358           if (IS_FUNC (sym->type))
1359             continue;
1360
1361           /* print extra debug info if required */
1362           if (options.debug)
1363             {
1364               cdbSymbol (sym, cdbFile, FALSE, FALSE);
1365
1366               if (!sym->level)
1367                 {               /* global */
1368                   if (IS_STATIC (sym->etype))
1369                     fprintf (afile, "F%s$", moduleName);        /* scope is file */
1370                   else
1371                     fprintf (afile, "G$");      /* scope is global */
1372                 }
1373               else
1374                 /* symbol is local */
1375                 fprintf (afile, "L%s$",
1376                          (sym->localof ? sym->localof->name : "-null-"));
1377               fprintf (afile, "%s$%d$%d", sym->name, sym->level, sym->block);
1378             }
1379
1380           /* if is has an absolute address then generate
1381              an equate for this no need to allocate space */
1382           if (SPEC_ABSA (sym->etype))
1383             {
1384
1385               if (options.debug)
1386                 fprintf (afile, " == 0x%04x\n", SPEC_ADDR (sym->etype));
1387
1388               fprintf (afile, "%s\t=\t0x%04x\n",
1389                        sym->rname,
1390                        SPEC_ADDR (sym->etype));
1391             }
1392           else {
1393               int size = getSize(sym->type);
1394
1395               if (size==0) {
1396                   werror(E_UNKNOWN_SIZE,sym->name);
1397               }       
1398               if (options.debug)
1399                   fprintf (afile, "==.\n");
1400               
1401               /* allocate space */
1402               tfprintf (afile, "!labeldef\n", sym->rname);
1403               tfprintf (afile, "\t!ds\n", (unsigned int) getSize (sym->type) & 0xffff);
1404           }
1405           
1406         }
1407     }
1408 }
1409
1410 /*-----------------------------------------------------------------*/
1411 /* glue - the final glue that hold the whole thing together        */
1412 /*-----------------------------------------------------------------*/
1413 void 
1414 glue ()
1415 {
1416   FILE *vFile;
1417   FILE *asmFile;
1418   FILE *ovrFile = tempfile ();
1419
1420   addSetHead (&tmpfileSet, ovrFile);
1421   /* print the global struct definitions */
1422   if (options.debug)
1423     cdbStructBlock (0, cdbFile);
1424
1425   vFile = tempfile ();
1426   /* PENDING: this isnt the best place but it will do */
1427   if (port->general.glue_up_main)
1428     {
1429       /* create the interrupt vector table */
1430       createInterruptVect (vFile);
1431     }
1432
1433   addSetHead (&tmpfileSet, vFile);
1434
1435   /* emit code for the all the variables declared */
1436   emitMaps ();
1437   /* do the overlay segments */
1438   emitOverlay (ovrFile);
1439
1440   /* now put it all together into the assembler file */
1441   /* create the assembler file name */
1442
1443   if (!options.c1mode)
1444     {
1445       sprintf (scratchFileName, srcFileName);
1446       strcat (scratchFileName, port->assembler.file_ext);
1447     }
1448   else
1449     {
1450       strcpy (scratchFileName, options.out_name);
1451     }
1452
1453   if (!(asmFile = fopen (scratchFileName, "w")))
1454     {
1455       werror (E_FILE_OPEN_ERR, scratchFileName);
1456       exit (1);
1457     }
1458
1459   /* initial comments */
1460   initialComments (asmFile);
1461
1462   /* print module name */
1463   tfprintf (asmFile, "\t!module\n", moduleName);
1464   tfprintf (asmFile, "\t!fileprelude\n");
1465
1466   /* Let the port generate any global directives, etc. */
1467   if (port->genAssemblerPreamble)
1468     {
1469       port->genAssemblerPreamble (asmFile);
1470     }
1471
1472   /* print the global variables in this module */
1473   printPublics (asmFile);
1474   if (port->assembler.externGlobal)
1475     printExterns (asmFile);
1476
1477   /* copy the sfr segment */
1478   fprintf (asmFile, "%s", iComments2);
1479   fprintf (asmFile, "; special function registers\n");
1480   fprintf (asmFile, "%s", iComments2);
1481   copyFile (asmFile, sfr->oFile);
1482
1483   /* copy the sbit segment */
1484   fprintf (asmFile, "%s", iComments2);
1485   fprintf (asmFile, "; special function bits \n");
1486   fprintf (asmFile, "%s", iComments2);
1487   copyFile (asmFile, sfrbit->oFile);
1488
1489   /* copy the data segment */
1490   fprintf (asmFile, "%s", iComments2);
1491   fprintf (asmFile, "; internal ram data\n");
1492   fprintf (asmFile, "%s", iComments2);
1493   copyFile (asmFile, data->oFile);
1494
1495
1496   /* create the overlay segments */
1497   if (overlay) {
1498     fprintf (asmFile, "%s", iComments2);
1499     fprintf (asmFile, "; overlayable items in internal ram \n");
1500     fprintf (asmFile, "%s", iComments2);
1501     copyFile (asmFile, ovrFile);
1502   }
1503
1504   /* create the stack segment MOF */
1505   if (mainf && IFFUNC_HASBODY(mainf->type))
1506     {
1507       fprintf (asmFile, "%s", iComments2);
1508       fprintf (asmFile, "; Stack segment in internal ram \n");
1509       fprintf (asmFile, "%s", iComments2);
1510       fprintf (asmFile, "\t.area\tSSEG\t(DATA)\n"
1511                "__start__stack:\n\t.ds\t1\n\n");
1512     }
1513
1514   /* create the idata segment */
1515   if (idata) {
1516     fprintf (asmFile, "%s", iComments2);
1517     fprintf (asmFile, "; indirectly addressable internal ram data\n");
1518     fprintf (asmFile, "%s", iComments2);
1519     copyFile (asmFile, idata->oFile);
1520   }
1521
1522   /* copy the bit segment */
1523   fprintf (asmFile, "%s", iComments2);
1524   fprintf (asmFile, "; bit data\n");
1525   fprintf (asmFile, "%s", iComments2);
1526   copyFile (asmFile, bit->oFile);
1527
1528   /* if external stack then reserve space of it */
1529   if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack)
1530     {
1531       fprintf (asmFile, "%s", iComments2);
1532       fprintf (asmFile, "; external stack \n");
1533       fprintf (asmFile, "%s", iComments2);
1534       fprintf (asmFile, "\t.area XSEG (XDATA)\n");      /* MOF */
1535       fprintf (asmFile, "\t.ds 256\n");
1536     }
1537
1538
1539   /* copy xtern ram data */
1540   fprintf (asmFile, "%s", iComments2);
1541   fprintf (asmFile, "; external ram data\n");
1542   fprintf (asmFile, "%s", iComments2);
1543   copyFile (asmFile, xdata->oFile);
1544
1545   /* copy xternal initialized ram data */
1546   fprintf (asmFile, "%s", iComments2);
1547   fprintf (asmFile, "; external initialized ram data\n");
1548   fprintf (asmFile, "%s", iComments2);
1549   copyFile (asmFile, xidata->oFile);
1550
1551   /* copy the interrupt vector table */
1552   if (mainf && IFFUNC_HASBODY(mainf->type))
1553     {
1554       fprintf (asmFile, "%s", iComments2);
1555       fprintf (asmFile, "; interrupt vector \n");
1556       fprintf (asmFile, "%s", iComments2);
1557       copyFile (asmFile, vFile);
1558     }
1559
1560   /* copy global & static initialisations */
1561   fprintf (asmFile, "%s", iComments2);
1562   fprintf (asmFile, "; global & static initialisations\n");
1563   fprintf (asmFile, "%s", iComments2);
1564
1565   /* Everywhere we generate a reference to the static_name area,
1566    * (which is currently only here), we immediately follow it with a
1567    * definition of the post_static_name area. This guarantees that
1568    * the post_static_name area will immediately follow the static_name
1569    * area.
1570    */
1571   tfprintf (asmFile, "\t!area\n", port->mem.static_name);       /* MOF */
1572   tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1573   tfprintf (asmFile, "\t!area\n", port->mem.static_name);
1574
1575   if (mainf && IFFUNC_HASBODY(mainf->type))
1576     {
1577       fprintf (asmFile, "__sdcc_gsinit_startup:\n");
1578       /* if external stack is specified then the
1579          higher order byte of the xdatalocation is
1580          going into P2 and the lower order going into
1581          spx */
1582       if (options.useXstack)
1583         {
1584           fprintf (asmFile, "\tmov\tP2,#0x%02x\n",
1585                    (((unsigned int) options.xdata_loc) >> 8) & 0xff);
1586           fprintf (asmFile, "\tmov\t_spx,#0x%02x\n",
1587                    (unsigned int) options.xdata_loc & 0xff);
1588         }
1589
1590       /* initialise the stack pointer */
1591       /* if the user specified a value then use it */
1592       if (options.stack_loc)
1593         fprintf (asmFile, "\tmov\tsp,#%d\n", options.stack_loc & 0xff);
1594       else
1595         /* no: we have to compute it */
1596       if (!options.stackOnData && maxRegBank <= 3)
1597         fprintf (asmFile, "\tmov\tsp,#%d\n", ((maxRegBank + 1) * 8) - 1);
1598       else
1599         fprintf (asmFile, "\tmov\tsp,#__start__stack\n");       /* MOF */
1600
1601       fprintf (asmFile, "\tlcall\t__sdcc_external_startup\n");
1602       fprintf (asmFile, "\tmov\ta,dpl\n");
1603       fprintf (asmFile, "\tjz\t__sdcc_init_data\n");
1604       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1605       fprintf (asmFile, "__sdcc_init_data:\n");
1606
1607       // if the port can copy the XINIT segment to XISEG
1608       if (port->genXINIT) {
1609         port->genXINIT(asmFile);
1610       }
1611
1612     }
1613   copyFile (asmFile, statsg->oFile);
1614
1615   if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type))
1616     {
1617       /* This code is generated in the post-static area.
1618        * This area is guaranteed to follow the static area
1619        * by the ugly shucking and jiving about 20 lines ago.
1620        */
1621       tfprintf (asmFile, "\t!area\n", port->mem.post_static_name);
1622       fprintf (asmFile, "\tljmp\t__sdcc_program_startup\n");
1623     }
1624
1625   fprintf (asmFile,
1626            "%s"
1627            "; Home\n"
1628            "%s", iComments2, iComments2);
1629   tfprintf (asmFile, "\t!areahome\n", HOME_NAME);
1630   copyFile (asmFile, home->oFile);
1631
1632   /* copy over code */
1633   fprintf (asmFile, "%s", iComments2);
1634   fprintf (asmFile, "; code\n");
1635   fprintf (asmFile, "%s", iComments2);
1636   tfprintf (asmFile, "\t!areacode\n", CODE_NAME);
1637   if (mainf && IFFUNC_HASBODY(mainf->type))
1638     {
1639
1640       /* entry point @ start of CSEG */
1641       fprintf (asmFile, "__sdcc_program_startup:\n");
1642
1643       /* put in the call to main */
1644       fprintf (asmFile, "\tlcall\t_main\n");
1645       if (options.mainreturn)
1646         {
1647
1648           fprintf (asmFile, ";\treturn from main ; will return to caller\n");
1649           fprintf (asmFile, "\tret\n");
1650
1651         }
1652       else
1653         {
1654
1655           fprintf (asmFile, ";\treturn from main will lock up\n");
1656           fprintf (asmFile, "\tsjmp .\n");
1657         }
1658     }
1659   copyFile (asmFile, code->oFile);
1660
1661   if (port->genAssemblerEnd) {
1662       port->genAssemblerEnd(asmFile);
1663   }
1664   fclose (asmFile);
1665   applyToSet (tmpfileSet, closeTmpFiles);
1666   applyToSet (tmpfileNameSet, rmTmpFiles);
1667 }
1668
1669 #if defined (__MINGW32__) || defined (__CYGWIN__) || defined (_MSC_VER)
1670 void
1671 rm_tmpfiles (void)
1672 {
1673   applyToSet (tmpfileSet, closeTmpFiles);
1674   applyToSet (tmpfileNameSet, rmTmpFiles);
1675 }
1676 #endif
1677
1678 /** Creates a temporary file name a'la tmpnam which avoids the bugs
1679     in cygwin wrt c:\tmp.
1680     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1681 */
1682 char *
1683 tempfilename (void)
1684 {
1685 #if !defined(_MSC_VER)
1686   const char *tmpdir = NULL;
1687   if (getenv ("TMP"))
1688     tmpdir = getenv ("TMP");
1689   else if (getenv ("TEMP"))
1690     tmpdir = getenv ("TEMP");
1691   else if (getenv ("TMPDIR"))
1692     tmpdir = getenv ("TMPDIR");
1693   if (tmpdir)
1694     {
1695       char *name = tempnam (tmpdir, "sdcc");
1696       if (name)
1697         {
1698           return name;
1699         }
1700     }
1701 #endif
1702   return tmpnam (NULL);
1703 }
1704
1705 /** Creates a temporary file a'la tmpfile which avoids the bugs
1706     in cygwin wrt c:\tmp.
1707     Scans, in order: TMP, TEMP, TMPDIR, else uses tmpfile().
1708 */
1709 FILE *
1710 tempfile (void)
1711 {
1712 #if !defined(_MSC_VER)
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 #endif
1735   return tmpfile ();
1736 }
1737