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