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