X-Git-Url: https://git.gag.com/?a=blobdiff_plain;f=src%2Fpic%2Fglue.c;h=e0f73fb7c1b42c958143df29235f2be4b69b1c93;hb=fb6e4e5e313436e0a55a16bf1c71de991f6c35dd;hp=abd20a56c9949e9bfd2a6d378d25e0915db55f6e;hpb=b4d69dfd516f175255aa87b18b59dcf309d98b46;p=fw%2Fsdcc diff --git a/src/pic/glue.c b/src/pic/glue.c index abd20a56..e0f73fb7 100644 --- a/src/pic/glue.c +++ b/src/pic/glue.c @@ -25,13 +25,23 @@ #include "../common.h" #include #include "ralloc.h" +#include "pcode.h" #include "newalloc.h" + +#ifdef _BIG_ENDIAN + #define _ENDIAN(x) (3-x) +#else + #define _ENDIAN(x) (x) +#endif + +#define BYTE_IN_LONG(x,b) ((x>>(8*_ENDIAN(b)))&0xff) + extern symbol *interrupts[256]; -void printIval (symbol *, sym_link *, initList *, FILE *); +static void printIval (symbol * sym, sym_link * type, initList * ilist, pBlock *pb); extern int noAlloc; extern set *publics; -extern int maxInterrupts; +extern unsigned maxInterrupts; extern int maxRegBank; extern symbol *mainf; extern char *VersionString; @@ -45,67 +55,43 @@ extern char *iComments2; extern DEFSETFUNC (closeTmpFiles); extern DEFSETFUNC (rmTmpFiles); +extern void AnalyzeBanking (void); extern void copyFile (FILE * dest, FILE * src); +extern void InlinepCode(void); +extern void writeUsedRegs(FILE *); - -//extern void emitMaps (); -//extern void createInterruptVect (FILE * vFile); extern void initialComments (FILE * afile); extern void printPublics (FILE * afile); extern void printChar (FILE * ofile, char *s, int plen); - -#if 0 -char * -aopLiteral (value * val, int offset) - static void emitRegularMap (memmap * map, bool addPublics, bool arFlag) - value *initPointer (initList * ilist) - void printIvalType (sym_link * type, initList * ilist, FILE * oFile) - void printIvalStruct (symbol * sym, sym_link * type, - initList * ilist, FILE * oFile) - int printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s) - void printIvalArray (symbol * sym, sym_link * type, initList * ilist, - FILE * oFile) - void printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile) - int printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile) - void printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) -#endif - +void pCodeInitRegisters(void); /*-----------------------------------------------------------------*/ /* aopLiteral - string from a literal value */ /*-----------------------------------------------------------------*/ - char *pic14aopLiteral (value * val, int offset) +int pic14aopLiteral (value *val, int offset) { - char *rs; - union - { - float f; - unsigned char c[4]; - } - fl; + union { + float f; + unsigned char c[4]; + } fl; /* if it is a float then it gets tricky */ /* otherwise it is fairly simple */ - if (!IS_FLOAT (val->type)) - { - unsigned long v = floatFromVal (val); + if (!IS_FLOAT(val->type)) { + unsigned long v = (unsigned long) floatFromVal(val); - v >>= (offset * 8); - sprintf (buffer, "0x%02x", ((char) v) & 0xff); - rs = Safe_calloc (1, strlen (buffer) + 1); - return strcpy (rs, buffer); - } + return ( (v >> (offset * 8)) & 0xff); + } /* it is type float */ - fl.f = (float) floatFromVal (val); -#ifdef _BIG_ENDIAN - sprintf (buffer, "0x%02x", fl.c[3 - offset]); + fl.f = (float) floatFromVal(val); +#ifdef _BIG_ENDIAN + return fl.c[3-offset]; #else - sprintf (buffer, "0x%02x", fl.c[offset]); + return fl.c[offset]; #endif - rs = Safe_calloc (1, strlen (buffer) + 1); - return strcpy (rs, buffer); + } @@ -189,18 +175,6 @@ pic14emitRegularMap (memmap * map, bool addPublics, bool arFlag) /* by grouping the bits together into groups of 8 and storing them in the normal ram. */ if (IS_BITVAR (sym->etype)) { - if ((bitvars % 8) == 0) - { - fprintf (map->oFile, " cblock\n"); - fprintf (map->oFile, "\tbitfield%d\n", bitvars); - fprintf (map->oFile, " endc\n"); - } - - fprintf (map->oFile, "%s\tEQU\t( (bitfield%d<<3)+%d)\n", - sym->rname, - bitvars & 0xfff8, - bitvars & 0x0007); - bitvars++; } else @@ -214,216 +188,91 @@ pic14emitRegularMap (memmap * map, bool addPublics, bool arFlag) } //fprintf (map->oFile, "\t.ds\t0x%04x\n", (unsigned int)getSize (sym->type) & 0xffff); } - - /* if it has a initial value then do it only if - it is a global variable */ - if (sym->ival && sym->level == 0) - { - ast *ival = NULL; - - if (IS_AGGREGATE (sym->type)) - ival = initAggregates (sym, sym->ival, NULL); - else - ival = newNode ('=', newAst_VALUE (symbolVal (sym)), - decorateType (resolveSymbols (list2expr (sym->ival)))); - codeOutFile = statsg->oFile; - eBBlockFromiCode (iCodeFromAst (ival)); - sym->ival = NULL; - } - } -} - - -#if 0 -/*-----------------------------------------------------------------*/ -/* initPointer - pointer initialization code massaging */ -/*-----------------------------------------------------------------*/ -value * -initPointer (initList * ilist) -{ - value *val; - ast *expr = list2expr (ilist); - - if (!expr) - goto wrong; - - /* try it the oldway first */ - if ((val = constExprValue (expr, FALSE))) - return val; - - /* no then we have to do these cludgy checks */ - /* pointers can be initialized with address of - a variable or address of an array element */ - if (IS_AST_OP (expr) && expr->opval.op == '&') - { - /* address of symbol */ - if (IS_AST_SYM_VALUE (expr->left)) - { - val = copyValue (AST_VALUE (expr->left)); - val->type = newLink (); - if (SPEC_SCLS (expr->left->etype) == S_CODE) - { - DCL_TYPE (val->type) = CPOINTER; - DCL_PTR_CONST (val->type) = port->mem.code_ro; - } - else if (SPEC_SCLS (expr->left->etype) == S_XDATA) - DCL_TYPE (val->type) = FPOINTER; - else if (SPEC_SCLS (expr->left->etype) == S_XSTACK) - DCL_TYPE (val->type) = PPOINTER; - else if (SPEC_SCLS (expr->left->etype) == S_IDATA) - DCL_TYPE (val->type) = IPOINTER; - else if (SPEC_SCLS (expr->left->etype) == S_EEPROM) - DCL_TYPE (val->type) = EEPPOINTER; - else - DCL_TYPE (val->type) = POINTER; - val->type->next = expr->left->ftype; - val->etype = getSpec (val->type); - return val; - } - - /* if address of indexed array */ - if (IS_AST_OP (expr->left) && expr->left->opval.op == '[') - return valForArray (expr->left); - - /* if address of structure element then - case 1. a.b ; */ - if (IS_AST_OP (expr->left) && - expr->left->opval.op == '.') - { - return valForStructElem (expr->left->left, - expr->left->right); + + /* if it has a initial value then do it only if + it is a global variable */ + if (sym->ival && sym->level == 0) { + ast *ival = NULL; + + if (IS_AGGREGATE (sym->type)) + ival = initAggregates (sym, sym->ival, NULL); + else + ival = newNode ('=', newAst_VALUE(symbolVal (sym)), + decorateType (resolveSymbols (list2expr (sym->ival)))); + codeOutFile = statsg->oFile; + GcurMemmap = statsg; + eBBlockFromiCode (iCodeFromAst (ival)); + sym->ival = NULL; } - - /* case 2. (&a)->b ; - (&some_struct)->element */ - if (IS_AST_OP (expr->left) && - expr->left->opval.op == PTR_OP && - IS_ADDRESS_OF_OP (expr->left->left)) - return valForStructElem (expr->left->left->left, - expr->left->right); } - -wrong: - werror (E_INIT_WRONG); - return NULL; - } -/*-----------------------------------------------------------------*/ -/* printChar - formats and prints a characater string with DB */ -/*-----------------------------------------------------------------*/ -void -printChar (FILE * ofile, char *s, int plen) -{ - int i; - int len = strlen (s); - int pplen = 0; - - while (len && pplen < plen) - { - - fprintf (ofile, "\t.ascii /"); - i = 60; - while (i && *s && pplen < plen) - { - if (*s < ' ' || *s == '/') - { - fprintf (ofile, "/\n\t.byte 0x%02x\n\t.ascii /", *s++); - } - else - fprintf (ofile, "%c", *s++); - pplen++; - i--; - } - fprintf (ofile, "/\n"); - - if (len > 60) - len -= 60; - else - len = 0; - } - if (pplen < plen) - fprintf (ofile, "\t.byte\t0\n"); -} /*-----------------------------------------------------------------*/ /* printIvalType - generates ival for int/char */ /*-----------------------------------------------------------------*/ -void -printIvalType (sym_link * type, initList * ilist, FILE * oFile) +static void +printIvalType (symbol *sym, sym_link * type, initList * ilist, pBlock *pb) { value *val; + unsigned long ulval; + + //fprintf(stderr, "%s\n",__FUNCTION__); /* if initList is deep */ if (ilist->type == INIT_DEEP) ilist = ilist->init.deep; - val = list2val (ilist); - switch (getSize (type)) - { - case 1: - if (!val) - fprintf (oFile, "\t.byte 0\n"); - else - fprintf (oFile, "\t.byte %s\n", - aopLiteral (val, 0)); - break; - - case 2: - if (!val) - fprintf (oFile, "\t.word 0\n"); - else - fprintf (oFile, "\t.byte %s,%s\n", - aopLiteral (val, 0), aopLiteral (val, 1)); - break; - - case 4: - if (!val) - fprintf (oFile, "\t.word 0,0\n"); - else - fprintf (oFile, "\t.byte %s,%s,%s,%s\n", - aopLiteral (val, 0), aopLiteral (val, 1), - aopLiteral (val, 2), aopLiteral (val, 3)); - break; - } - - return; -} - -/*-----------------------------------------------------------------*/ -/* printIvalStruct - generates initial value for structures */ -/*-----------------------------------------------------------------*/ -void -printIvalStruct (symbol * sym, sym_link * type, - initList * ilist, FILE * oFile) -{ - symbol *sflds; - initList *iloop; - - sflds = SPEC_STRUCT (type)->fields; - if (ilist->type != INIT_DEEP) - { - werror (E_INIT_STRUCT, sym->name); - return; - } + if (!IS_AGGREGATE(sym->type) && getNelements(type, ilist)>1) { + werror (W_EXCESS_INITIALIZERS, "scalar", sym->name, sym->lineDef); + } - iloop = ilist->init.deep; + if (!(val = list2val (ilist))) { + // assuming a warning has been thrown + val=constVal("0"); + } - for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL)) - printIval (sflds, sflds->type, iloop, oFile); + if (val->type != type) { + val = valCastLiteral(type, floatFromVal(val)); + } - return; + if(val) + ulval = (unsigned long) floatFromVal (val); + else + ulval =0; + + switch (getSize (type)) { + case 1: + addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,0)))); + break; + + case 2: + addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,0)))); + addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,1)))); + break; + + case 4: + addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,0)))); + addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,1)))); + addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,2)))); + addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(BYTE_IN_LONG(ulval,3)))); + break; + } } /*-----------------------------------------------------------------*/ /* printIvalChar - generates initital value for character array */ /*-----------------------------------------------------------------*/ -int -printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s) +static int +printIvalChar (sym_link * type, initList * ilist, pBlock *pb, char *s) { value *val; int remain; + if(!pb) + return 0; + + fprintf(stderr, "%s\n",__FUNCTION__); if (!s) { @@ -434,45 +283,58 @@ printIvalChar (sym_link * type, initList * ilist, FILE * oFile, char *s) if (!DCL_ELEM (type)) DCL_ELEM (type) = strlen (SPEC_CVAL (val->etype).v_char) + 1; - /* if size mismatch */ -/* if (DCL_ELEM (type) < ((int) strlen (SPEC_CVAL (val->etype).v_char) + 1)) */ -/* werror (E_ARRAY_BOUND); */ - - printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type)); + //printChar (oFile, SPEC_CVAL (val->etype).v_char, DCL_ELEM (type)); + //fprintf(stderr, "%s omitting call to printChar\n",__FUNCTION__); + addpCode2pBlock(pb,newpCodeCharP(";omitting call to printChar")); if ((remain = (DCL_ELEM (type) - strlen (SPEC_CVAL (val->etype).v_char) - 1)) > 0) while (remain--) - fprintf (oFile, "\t.byte 0\n"); - + //tfprintf (oFile, "\t!db !constbyte\n", 0); + addpCode2pBlock(pb,newpCode(POC_RETLW,newpCodeOpLit(0))); return 1; } else return 0; } - else - printChar (oFile, s, strlen (s) + 1); + else { + //printChar (oFile, s, strlen (s) + 1); + + for(remain=0; remainnext)) + if (IS_CHAR (type->next)) { + //fprintf(stderr,"%s:%d - is_char\n",__FUNCTION__,__LINE__); + if (!IS_LITERAL(list2val(ilist)->etype)) { + werror (W_INIT_WRONG); + return; + } if (printIvalChar (type, (ilist->type == INIT_DEEP ? ilist->init.deep : ilist), - oFile, SPEC_CVAL (sym->etype).v_char)) + pb, SPEC_CVAL (sym->etype).v_char)) return; - + } /* not the special case */ if (ilist->type != INIT_DEEP) { @@ -485,8 +347,9 @@ printIvalArray (symbol * sym, sym_link * type, initList * ilist, for (;;) { + //fprintf(stderr,"%s:%d - is_char\n",__FUNCTION__,__LINE__); size++; - printIval (sym, type->next, iloop, oFile); + printIval (sym, type->next, iloop, pb); iloop = (iloop ? iloop->next : NULL); @@ -497,8 +360,13 @@ printIvalArray (symbol * sym, sym_link * type, initList * ilist, /* no of elements given and we */ /* have generated for all of them */ - if (!--lcnt) + if (!--lcnt) { + /* if initializers left */ + if (iloop) { + werror (W_EXCESS_INITIALIZERS, "array", sym->name, sym->lineDef); + } break; + } } /* if we have not been given a size */ @@ -508,177 +376,49 @@ printIvalArray (symbol * sym, sym_link * type, initList * ilist, return; } -/*-----------------------------------------------------------------*/ -/* printIvalFuncPtr - generate initial value for function pointers */ -/*-----------------------------------------------------------------*/ -void -printIvalFuncPtr (sym_link * type, initList * ilist, FILE * oFile) -{ - value *val; - int dLvl = 0; - - val = list2val (ilist); - /* check the types */ - if ((dLvl = checkType (val->type, type->next)) <= 0) - { - - fprintf (oFile, "\t.word 0\n"); - return; - } - - /* now generate the name */ - if (!val->sym) - { - if (IS_LITERAL (val->etype)) - fprintf (oFile, "\t.byte %s,%s\n", - aopLiteral (val, 0), aopLiteral (val, 1)); - else - fprintf (oFile, "\t.byte %s,(%s >> 8)\n", - val->name, val->name); - } - else - fprintf (oFile, "\t.byte %s,(%s >> 8)\n", - val->sym->rname, val->sym->rname); - - return; -} - -/*-----------------------------------------------------------------*/ -/* printIvalCharPtr - generates initial values for character pointers */ -/*-----------------------------------------------------------------*/ -int -printIvalCharPtr (symbol * sym, sym_link * type, value * val, FILE * oFile) -{ - int size = 0; - - size = getSize (type); - - if (size == 1) - fprintf (oFile, - "\t.byte %s", val->name); - else - fprintf (oFile, - "\t.byte %s,(%s >> 8)", - val->name, val->name); - - if (size > 2) - fprintf (oFile, ",#0x02\n"); - else - fprintf (oFile, "\n"); - - if (val->sym && val->sym->isstrlit) - addSet (&statsg->syms, val->sym); - - return 1; -} - -/*-----------------------------------------------------------------*/ -/* printIvalPtr - generates initial value for pointers */ -/*-----------------------------------------------------------------*/ -void -printIvalPtr (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) -{ - value *val; - - /* if deep then */ - if (ilist->type == INIT_DEEP) - ilist = ilist->init.deep; - - /* function pointer */ - if (IS_FUNC (type->next)) - { - printIvalFuncPtr (type, ilist, oFile); - return; - } - - if (!(val = initPointer (ilist))) - return; - - /* if character pointer */ - if (IS_CHAR (type->next)) - if (printIvalCharPtr (sym, type, val, oFile)) - return; - - /* check the type */ - if (checkType (type, val->type) != 1) - werror (E_INIT_WRONG); - - /* if val is literal */ - if (IS_LITERAL (val->etype)) - { - switch (getSize (type)) - { - case 1: - fprintf (oFile, "\t.byte 0x%02x\n", ((char) floatFromVal (val)) & 0xff); - break; - case 2: - fprintf (oFile, "\t.byte %s,%s\n", - aopLiteral (val, 0), aopLiteral (val, 1)); - - break; - case 3: - fprintf (oFile, "\t.byte %s,%s,0x%02x\n", - aopLiteral (val, 0), aopLiteral (val, 1), CPOINTER); - } - return; - } - - - switch (getSize (type)) - { - case 1: - fprintf (oFile, "\t.byte %s\n", val->name); - break; - case 2: - fprintf (oFile, "\t.byte %s,(%s >> 8)\n", val->name, val->name); - break; - - case 3: - fprintf (oFile, "\t.byte %s,(%s >> 8),0x%02x\n", - val->name, val->name, DCL_TYPE (val->type)); - } - return; -} - /*-----------------------------------------------------------------*/ /* printIval - generates code for initial value */ /*-----------------------------------------------------------------*/ -void -printIval (symbol * sym, sym_link * type, initList * ilist, FILE * oFile) +static void +printIval (symbol * sym, sym_link * type, initList * ilist, pBlock *pb) { - if (!ilist) + if (!ilist || !pb) return; /* if structure then */ if (IS_STRUCT (type)) { - printIvalStruct (sym, type, ilist, oFile); + //fprintf(stderr,"%s struct\n",__FUNCTION__); + //printIvalStruct (sym, type, ilist, oFile); return; } /* if this is a pointer */ if (IS_PTR (type)) { - printIvalPtr (sym, type, ilist, oFile); + //fprintf(stderr,"%s pointer\n",__FUNCTION__); + //printIvalPtr (sym, type, ilist, oFile); return; } /* if this is an array */ if (IS_ARRAY (type)) { - printIvalArray (sym, type, ilist, oFile); + //fprintf(stderr,"%s array\n",__FUNCTION__); + printIvalArray (sym, type, ilist, pb); return; } /* if type is SPECIFIER */ if (IS_SPEC (type)) { - printIvalType (type, ilist, oFile); + //fprintf(stderr,"%s spec\n",__FUNCTION__); + printIvalType (sym, type, ilist, pb); return; } } -#endif +extern void pCodeConstString(char *name, char *value); /*-----------------------------------------------------------------*/ /* emitStaticSeg - emitcode for the static segment */ /*-----------------------------------------------------------------*/ @@ -689,12 +429,12 @@ pic14emitStaticSeg (memmap * map) fprintf (map->oFile, ";\t.area\t%s\n", map->sname); + //fprintf(stderr, "%s\n",__FUNCTION__); /* for all variables in this segment do */ for (sym = setFirstItem (map->syms); sym; sym = setNextItem (map->syms)) { - /* if it is "extern" then do nothing */ if (IS_EXTERN (sym->etype)) continue; @@ -707,8 +447,10 @@ pic14emitStaticSeg (memmap * map) /* print extra debug info if required */ if (options.debug || sym->level == 0) { - - cdbSymbol (sym, cdbFile, FALSE, FALSE); + /* NOTE to me - cdbFile may be null in which case, + * the sym name will be printed to stdout. oh well */ + if(cdbFile) + cdbSymbol (sym, cdbFile, FALSE, FALSE); if (!sym->level) { /* global */ @@ -722,6 +464,7 @@ pic14emitStaticSeg (memmap * map) fprintf (code->oFile, "L%s_", (sym->localof ? sym->localof->name : "-null-")); fprintf (code->oFile, "%s_%d_%d", sym->name, sym->level, sym->block); + } /* if it has an absolute address */ @@ -742,27 +485,37 @@ pic14emitStaticSeg (memmap * map) /* if it has an initial value */ if (sym->ival) { + pBlock *pb; + fprintf (code->oFile, "%s:\n", sym->rname); noAlloc++; resolveIvalSym (sym->ival); - printIval (sym, sym->type, sym->ival, code->oFile); + //printIval (sym, sym->type, sym->ival, code->oFile); + pb = newpCodeChain(NULL, 'P',newpCodeCharP("; Starting pCode block for Ival")); + addpBlock(pb); + addpCode2pBlock(pb,newpCodeLabel(sym->rname,-1)); + + printIval (sym, sym->type, sym->ival, pb); noAlloc--; } else { + /* allocate space */ fprintf (code->oFile, "%s:\n", sym->rname); /* special case for character strings */ if (IS_ARRAY (sym->type) && IS_CHAR (sym->type->next) && SPEC_CVAL (sym->etype).v_char) - printChar (code->oFile, + pCodeConstString(sym->rname , SPEC_CVAL (sym->etype).v_char); + /*printChar (code->oFile, SPEC_CVAL (sym->etype).v_char, - strlen (SPEC_CVAL (sym->etype).v_char) + 1); + strlen (SPEC_CVAL (sym->etype).v_char) + 1);*/ else fprintf (code->oFile, "\t.ds\t0x%04x\n", (unsigned int) getSize (sym->type) & 0xffff); } } } + } @@ -790,7 +543,7 @@ pic14emitMaps () static void pic14createInterruptVect (FILE * vFile) { - int i = 0; + unsigned i = 0; mainf = newSymbol ("main", 0); mainf->block = 0; @@ -803,7 +556,7 @@ pic14createInterruptVect (FILE * vFile) } /* if the main is only a prototype ie. no body then do nothing */ - if (!mainf->fbody) + if (!IFFUNC_HASBODY(mainf->type)) { /* if ! compile only then main function should be present */ if (!options.cc_only) @@ -829,7 +582,7 @@ pic14createInterruptVect (FILE * vFile) for (; i < maxInterrupts; i++) { if (interrupts[i]) - fprintf (vFile, ";\tljmp\t%s\n\t.ds\t5\n", interrupts[i]->rname); + fprintf (vFile, ";\tljmp\t%s\n;\t.ds\t5\n", interrupts[i]->rname); else fprintf (vFile, ";\treti\n;\t.ds\t7\n"); } @@ -971,157 +724,166 @@ pic14emitOverlay (FILE * afile) } - /*-----------------------------------------------------------------*/ /* glue - the final glue that hold the whole thing together */ /*-----------------------------------------------------------------*/ void -pic14glue () +picglue () { + FILE *vFile; FILE *asmFile; - FILE *ovrFile = tempfile (); - int i; + FILE *ovrFile = tempfile(); + + addSetHead(&tmpfileSet,ovrFile); + pCodeInitRegisters(); + + if (mainf && IFFUNC_HASBODY(mainf->type)) { + + pBlock *pb = newpCodeChain(NULL,'X',newpCodeCharP("; Starting pCode block")); + addpBlock(pb); + + /* entry point @ start of CSEG */ + addpCode2pBlock(pb,newpCodeLabel("__sdcc_program_startup",-1)); + /* put in the call to main */ + addpCode2pBlock(pb,newpCode(POC_CALL,newpCodeOp("_main",PO_STR))); + + if (options.mainreturn) { + + addpCode2pBlock(pb,newpCodeCharP(";\treturn from main will return to caller\n")); + addpCode2pBlock(pb,newpCode(POC_RETURN,NULL)); + + } else { + + addpCode2pBlock(pb,newpCodeCharP(";\treturn from main will lock up\n")); + addpCode2pBlock(pb,newpCode(POC_GOTO,newpCodeOp("$",PO_STR))); + + } + } + + + /* At this point we've got all the code in the form of pCode structures */ + /* Now it needs to be rearranged into the order it should be placed in the */ + /* code space */ + + movepBlock2Head('P'); // Last + movepBlock2Head(code->dbName); + movepBlock2Head('X'); + movepBlock2Head(statsg->dbName); // First + - addSetHead (&tmpfileSet, ovrFile); /* print the global struct definitions */ if (options.debug) - cdbStructBlock (0, cdbFile); + cdbStructBlock (0,cdbFile); - vFile = tempfile (); + vFile = tempfile(); /* PENDING: this isnt the best place but it will do */ - if (port->general.glue_up_main) - { - /* create the interrupt vector table */ - pic14createInterruptVect (vFile); - } - - addSetHead (&tmpfileSet, vFile); + if (port->general.glue_up_main) { + /* create the interrupt vector table */ + pic14createInterruptVect (vFile); + } + addSetHead(&tmpfileSet,vFile); + /* emit code for the all the variables declared */ pic14emitMaps (); /* do the overlay segments */ - pic14emitOverlay (ovrFile); + pic14emitOverlay(ovrFile); - /* now put it all together into the assembler file */ - /* create the assembler file name */ - if (!options.c1mode) - { - sprintf (buffer, srcFileName); - strcat (buffer, ".asm"); - } - else - { - strcpy (buffer, options.out_name); - } + AnalyzepCode('*'); - if (!(asmFile = fopen (buffer, "w"))) - { - werror (E_FILE_OPEN_ERR, buffer); - exit (1); - } + //#ifdef PCODE_DEBUG + //printCallTree(stderr); + //#endif + + InlinepCode(); + AnalyzepCode('*'); + + pcode_test(); + + + /* now put it all together into the assembler file */ + /* create the assembler file name */ + + if (!options.c1mode) { + sprintf (buffer, srcFileName); + strcat (buffer, ".asm"); + } + else { + strcpy(buffer, options.out_name); + } + + if (!(asmFile = fopen (buffer, "w"))) { + werror (E_FILE_OPEN_ERR, buffer); + exit (1); + } + /* initial comments */ pic14initialComments (asmFile); - + /* print module name */ fprintf (asmFile, ";\t.module %s\n", moduleName); - + /* Let the port generate any global directives, etc. */ if (port->genAssemblerPreamble) { - port->genAssemblerPreamble (asmFile); + port->genAssemblerPreamble(asmFile); } - + /* print the global variables in this module */ pic14printPublics (asmFile); - + /* copy the sfr segment */ fprintf (asmFile, "%s", iComments2); fprintf (asmFile, "; special function registers\n"); fprintf (asmFile, "%s", iComments2); copyFile (asmFile, sfr->oFile); - + /* Put all variables into a cblock */ - fprintf (asmFile, "\n\n\tcblock 0x13\n\n"); - - for (i = 0; i < pic14_nRegs; i++) - { - if (regspic14[i].wasUsed && (regspic14[i].offset >= 0x0c)) - fprintf (asmFile, "\t%s\n", regspic14[i].name); - } - //fprintf (asmFile, "\tr0x0C\n"); - //fprintf (asmFile, "\tr0x0D\n"); - - /* For now, create a "dpl" and a "dph" in the register space */ - /* of the pic so that we can use the same calling mechanism */ - /* as the 8051 port */ - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; dpl and dph to emulate the 8051 calling mechanism \n"); - fprintf (asmFile, "%s", iComments2); - - fprintf (asmFile, "\tdph\n"); - - - - /* copy the sbit segment */ - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; special function bits \n"); - fprintf (asmFile, "%s", iComments2); - copyFile (asmFile, sfrbit->oFile); - - /* copy the data segment */ - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; internal ram data\n"); - fprintf (asmFile, "%s", iComments2); - copyFile (asmFile, data->oFile); - + AnalyzeBanking(); + writeUsedRegs(asmFile); /* create the overlay segments */ fprintf (asmFile, "%s", iComments2); fprintf (asmFile, "; overlayable items in internal ram \n"); - fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "%s", iComments2); copyFile (asmFile, ovrFile); /* create the stack segment MOF */ - if (mainf && mainf->fbody) - { - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; Stack segment in internal ram \n"); - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, ";\t.area\tSSEG\t(DATA)\n" - ";__start__stack:\n;\t.ds\t1\n\n"); - } + if (mainf && IFFUNC_HASBODY(mainf->type)) { + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; Stack segment in internal ram \n"); + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, ";\t.area\tSSEG\t(DATA)\n" + ";__start__stack:\n;\t.ds\t1\n\n"); + } /* create the idata segment */ fprintf (asmFile, "%s", iComments2); fprintf (asmFile, "; indirectly addressable internal ram data\n"); fprintf (asmFile, "%s", iComments2); copyFile (asmFile, idata->oFile); - + /* if external stack then reserve space of it */ - if (mainf && mainf->fbody && options.useXstack) - { - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; external stack \n"); - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, ";\t.area XSEG (XDATA)\n"); /* MOF */ - fprintf (asmFile, ";\t.ds 256\n"); - } - - + if (mainf && IFFUNC_HASBODY(mainf->type) && options.useXstack ) { + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; external stack \n"); + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile,";\t.area XSEG (XDATA)\n"); /* MOF */ + fprintf (asmFile,";\t.ds 256\n"); + } + + /* copy xtern ram data */ fprintf (asmFile, "%s", iComments2); fprintf (asmFile, "; external ram data\n"); fprintf (asmFile, "%s", iComments2); copyFile (asmFile, xdata->oFile); - - - fprintf (asmFile, "\tendc\n"); - + /* copy the bit segment */ fprintf (asmFile, "%s", iComments2); @@ -1133,106 +895,72 @@ pic14glue () fprintf (asmFile, "\tORG 0\n"); /* copy the interrupt vector table */ - if (mainf && mainf->fbody) - { - fprintf (asmFile, "%s", iComments2); - fprintf (asmFile, "; interrupt vector \n"); - fprintf (asmFile, "%s", iComments2); - copyFile (asmFile, vFile); - } - + if (mainf && IFFUNC_HASBODY(mainf->type)) { + fprintf (asmFile, "%s", iComments2); + fprintf (asmFile, "; interrupt vector \n"); + fprintf (asmFile, "%s", iComments2); + copyFile (asmFile, vFile); + } + /* copy global & static initialisations */ fprintf (asmFile, "%s", iComments2); fprintf (asmFile, "; global & static initialisations\n"); fprintf (asmFile, "%s", iComments2); - - /* Everywhere we generate a reference to the static_name area, - * (which is currently only here), we immediately follow it with a + + /* Everywhere we generate a reference to the static_name area, + * (which is currently only here), we immediately follow it with a * definition of the post_static_name area. This guarantees that * the post_static_name area will immediately follow the static_name * area. */ - fprintf (asmFile, ";\t.area %s\n", port->mem.static_name); /* MOF */ + fprintf (asmFile, ";\t.area %s\n", port->mem.static_name); /* MOF */ fprintf (asmFile, ";\t.area %s\n", port->mem.post_static_name); fprintf (asmFile, ";\t.area %s\n", port->mem.static_name); - - if (mainf && mainf->fbody) - { - fprintf (asmFile, "__sdcc_gsinit_startup:\n"); - /* if external stack is specified then the - higher order byte of the xdatalocation is - going into P2 and the lower order going into - spx */ - if (options.useXstack) - { - fprintf (asmFile, ";\tmov\tP2,#0x%02x\n", - (((unsigned int) options.xdata_loc) >> 8) & 0xff); - fprintf (asmFile, ";\tmov\t_spx,#0x%02x\n", - (unsigned int) options.xdata_loc & 0xff); - } - - /* initialise the stack pointer */ - /* if the user specified a value then use it */ - if (options.stack_loc) - fprintf (asmFile, ";\tmov\tsp,#%d\n", options.stack_loc); - else - /* no: we have to compute it */ - if (!options.stackOnData && maxRegBank <= 3) - fprintf (asmFile, ";\tmov\tsp,#%d\n", ((maxRegBank + 1) * 8) - 1); - else - fprintf (asmFile, ";\tmov\tsp,#__start__stack\n"); /* MOF */ - - fprintf (asmFile, ";\tlcall\t__sdcc_external_startup\n"); - fprintf (asmFile, ";\tmov\ta,dpl\n"); - fprintf (asmFile, ";\tjz\t__sdcc_init_data\n"); - fprintf (asmFile, ";\tljmp\t__sdcc_program_startup\n"); - fprintf (asmFile, ";__sdcc_init_data:\n"); - + + if (mainf && IFFUNC_HASBODY(mainf->type)) { + fprintf (asmFile,"__sdcc_gsinit_startup:\n"); + /* if external stack is specified then the + higher order byte of the xdatalocation is + going into P2 and the lower order going into + spx */ + if (options.useXstack) { + fprintf(asmFile,";\tmov\tP2,#0x%02x\n", + (((unsigned int)options.xdata_loc) >> 8) & 0xff); + fprintf(asmFile,";\tmov\t_spx,#0x%02x\n", + (unsigned int)options.xdata_loc & 0xff); } - copyFile (asmFile, statsg->oFile); - if (port->general.glue_up_main && mainf && mainf->fbody) + } + + if (port->general.glue_up_main && mainf && IFFUNC_HASBODY(mainf->type)) { /* This code is generated in the post-static area. * This area is guaranteed to follow the static area * by the ugly shucking and jiving about 20 lines ago. */ - fprintf (asmFile, ";\t.area %s\n", port->mem.post_static_name); - fprintf (asmFile, ";\tljmp\t__sdcc_program_startup\n"); + fprintf(asmFile, ";\t.area %s\n", port->mem.post_static_name); + fprintf (asmFile,";\tljmp\t__sdcc_program_startup\n"); } - + /* copy over code */ fprintf (asmFile, "%s", iComments2); fprintf (asmFile, "; code\n"); fprintf (asmFile, "%s", iComments2); fprintf (asmFile, ";\t.area %s\n", port->mem.code_name); - if (mainf && mainf->fbody) - { - - /* entry point @ start of CSEG */ - fprintf (asmFile, "__sdcc_program_startup:\n"); - /* put in the call to main */ - fprintf (asmFile, "\tcall\t_main\n"); - if (options.mainreturn) - { - - fprintf (asmFile, ";\treturn from main ; will return to caller\n"); - fprintf (asmFile, "\treturn\n"); + //copyFile (stderr, code->oFile); - } - else - { + copypCode(asmFile, 'I'); + copypCode(asmFile, statsg->dbName); + copypCode(asmFile, 'X'); + copypCode(asmFile, 'M'); + copypCode(asmFile, code->dbName); + copypCode(asmFile, 'P'); - fprintf (asmFile, ";\treturn from main will lock up\n"); - fprintf (asmFile, "\tgoto\t$\n"); - } - } - copyFile (asmFile, code->oFile); - fprintf (asmFile, "\tend\n"); + fprintf (asmFile,"\tend\n"); fclose (asmFile); - applyToSet (tmpfileSet, closeTmpFiles); - applyToSet (tmpfileNameSet, rmTmpFiles); + + rm_tmpfiles(); }