# svn co http://svn.code.sf.net/p/sdcc/code/trunk/sdcc/ $ wget http://sourceforge.net/projects/sdcc/files/sdcc/3.4.0/sdcc-src-3.4.0.tar.bz2/download $ tar xvf download $ mkdir sdcc.build $ cd sdcc.build $ sudo apt-get install g++ flex bison libboost-all-dev $ ../sdcc/configure --disable-mcs51-port --disable-z80-port \ --disable-z180-port --disable-r2k-port --disable-r3ka-port \ --disable-gbz80-port --disable-tlcs90-port --disable-ds390-port \ --disable-ds400-port --disable-pic14-port --disable-pic16-port --disable-s08-port $ make $ ./bin/sdcc # 會被 strip 調除錯訊息。 $ make install
-S Compile only; do not assemble or link -c --compile-only Compile and assemble, but do not link Internal debugging options: --dump-ast Dump front-end AST before generating i-code --dump-i-code Dump the i-code structure at all stages --dump-graphs Dump graphs (control-flow, conflict, etc) --i-code-in-asm Include i-code as comments in the asm file --fverbose-asm Include code generator comments in the asm output
# 會列出產生代碼過程中,編譯器內部被調用的函式。 $ export SDCC_DEBUG_FUNCTION_POINTERS=true
$ wget http://sourceforge.net/projects/sdcc/files/sdcc/3.5.0/sdcc-src-3.5.0.tar.bz2/download $ tar xvf download $ mkdir sdcc.build; cd sdcc.build $ ../sdcc/configure --host=x86_64-w64-mingw32 \ --disable-mcs51-port --disable-z80-port \ --disable-z180-port --disable-r2k-port --disable-r3ka-port \ --disable-gbz80-port --disable-tlcs90-port --disable-ds390-port \ --disable-ds400-port --disable-pic14-port --disable-pic16-port --disable-s08-port $ make # 為解決 sdcc.exe: error while loading shared libraries: libstdc++-6.dll 的問題。 $ export PATH=/usr/x86_64-w64-mingw32/sys-root/mingw/bin/:$PATH
yyparse (SDCCmain.c) → AST (SDCCast.c) → iCode (SDCCicode.c) → BBlock (SDCCopt.c) → iCode (SDCCicode.c) → CodeGen
if (fullSrcFileName || options.c1mode) { preProcess (envp); initSymt (); initiCode (); initCSupport (); initBuiltIns (); initPeepHole (); if (options.verbose) printf ("sdcc: Generating code...\n"); yyparse ();
function_definition : function_declarator { /* function type not specified */ /* assume it to be 'int' */ addDecl($1,0,newIntLink()); $1 = createFunctionDecl($1); } function_body { $$ = createFunction($1,$3); } | declaration_specifiers function_declarator { pointerTypes($2->type,copyLinkChain($1)); addDecl($2,0,$1); $2 = createFunctionDecl($2); } function_body { $$ = createFunction($2,$4); } ;
/*-----------------------------------------------------------------*/ /* createFunction - This is the key node that calls the iCode for */ /* generating the code for a function. Note code */ /* is generated function by function, later when */ /* add inter-procedural analysis this will change */ /*-----------------------------------------------------------------*/ ast * createFunction (symbol * name, ast * body) { /* snip */ ex = newAst_VALUE (symbolVal (name)); /* create name */ ex = newNode (FUNCTION, ex, body); ex->values.args = FUNC_ARGS (name->type); ex->decorated = 1; /* snip */ /* create the node & generate intermediate code */ GcurMemmap = code; // 代碼相關 memmap。 codeOutBuf = &code->oBuf; // 代碼輸出緩衝區。 piCode = iCodeFromAst (ex); // AST -> iCode name->generated = 1; eBBlockFromiCode (piCode); // iCode -> eBBlock /* snip */
/*-----------------------------------------------------------------*/ /* iCodeFromAst - given an ast will convert it to iCode */ /*-----------------------------------------------------------------*/ iCode * iCodeFromAst (ast * tree) { returnLabel = newiTempLabel ("_return"); entryLabel = newiTempLabel ("_entry"); ast2iCode (tree, 0); return reverseiCChain (); }
/*-----------------------------------------------------------------*/ /* ast2iCode - creates an icodeList from an ast */ /*-----------------------------------------------------------------*/ operand * ast2iCode (ast * tree, int lvl) {
/*-----------------------------------------------------------------*/ /* eBBlockFromiCode - creates extended basic blocks from iCode */ /* will return an array of eBBlock pointers */ /*-----------------------------------------------------------------*/ eBBlock ** eBBlockFromiCode (iCode * ic) { /* optimize the chain for labels & gotos this will eliminate redundant labels and will change jump to jumps by jumps */ ic = iCodeLabelOptimize (ic); /* break it down into basic blocks */ ebbi = iCodeBreakDown (ic); /* 底層架構無關的優化。 */ /* allocate registers & generate code */ port->assignRegisters (ebbi); // 分配暫存器,並產生代碼。 /* throw away blocks */ setToNull ((void *) &graphEdges); return NULL; }
/*-----------------------------------------------------------------*/ /* assignRegisters - assigns registers to each live range as need */ /*-----------------------------------------------------------------*/ void hc08_assignRegisters (ebbIndex * ebbi) { #ifdef OLDRALLOC if (options.oldralloc) hc08_oldralloc (ebbi); else #endif hc08_ralloc (ebbi); }
/*-----------------------------------------------------------------*/ /* Old, obsolete register allocator */ /*-----------------------------------------------------------------*/ void hc08_oldralloc (ebbIndex * ebbi) { /* first determine for each live range the number of registers & the type of registers required for each */ regTypeNum (*ebbs); /* and serially allocate registers */ serialRegAssign (ebbs, count); /* snip */ /* now get back the chain */ ic = iCodeLabelOptimize (iCodeFromeBBlock (ebbs, count)); // 再將 eBBlock 轉成 iCode。 genhc08Code (ic); // 針對 iCode 產生代碼。 }
/*-----------------------------------------------------------------*/ /* New register allocator */ /*-----------------------------------------------------------------*/ void hc08_ralloc (ebbIndex * ebbi) { /* The new register allocator invokes its magic */ ic = hc08_ralloc2_cc (ebbi); /* now get back the chain */ ic = iCodeLabelOptimize (iCodeFromeBBlock (ebbs, count)); // 再將 eBBlock 轉成 iCode。 genhc08Code (ic); // 針對 iCode 產生代碼。 }
/*-----------------------------------------------------------------*/ /* genhc08Code - generate code for HC08 based controllers */ /*-----------------------------------------------------------------*/ void genhc08Code (iCode *lic) { for (ic = lic; ic; ic = ic->next) { /* snip */ genhc08iCode(ic); /* snip */ } }
/*---------------------------------------------------------------------------------------*/ /* genhc08iode - generate code for HC08 based controllers for a single iCode instruction */ /*---------------------------------------------------------------------------------------*/ static void genhc08iCode (iCode *ic) { /* depending on the operation */ switch (ic->op) { case '!': genNot (ic); break;
/*-----------------------------------------------------------------*/ /* genNot - generate code for ! operation */ /*-----------------------------------------------------------------*/ static void genNot (iCode * ic) { bool needpulla; D (emitcode ("; genNot", "")); /* assign asmOps to operand & result */ aopOp (IC_LEFT (ic), ic, FALSE); aopOp (IC_RESULT (ic), ic, TRUE); needpulla = pushRegIfSurv (hc08_reg_a); asmopToBool (AOP (IC_LEFT (ic)), TRUE); emitcode ("eor", one); regalloc_dry_run_cost += 2; storeRegToFullAop (hc08_reg_a, AOP (IC_RESULT (ic)), FALSE); pullOrFreeReg (hc08_reg_a, needpulla); freeAsmop (IC_RESULT (ic), NULL, ic, TRUE); freeAsmop (IC_LEFT (ic), NULL, ic, TRUE); }
if (port->general.do_glue != NULL) (*port->general.do_glue) ();
/*-----------------------------------------------------------------*/ /* glue - the final glue that hold the whole thing together */ /*-----------------------------------------------------------------*/ void glue (void) { /* emit code for the all the variables declared */ emitMaps (); }
/*-----------------------------------------------------------------*/ /* emitMaps - emits the code for the data portion the code */ /*-----------------------------------------------------------------*/ void emitMaps (void) { namedspacemap *nm; int publicsfr = TARGET_IS_MCS51; /* Ideally, this should be true for all */ /* ports but let's be conservative - EEP */ inInitMode++; /* no special considerations for the following data, idata & bit & xdata */ emitRegularMap (data, TRUE, TRUE);
/*-----------------------------------------------------------------*/ /* emitRegularMap - emit code for maps with no special cases */ /*-----------------------------------------------------------------*/ static void emitRegularMap (memmap * map, bool addPublics, bool arFlag)
#define LRVAL(x) x->left->rvalue // 左節點是否為右值 #define RRVAL(x) x->right->rvalue #define TRVAL(x) x->rvalue // 根節點是否為右值 #define LLVAL(x) x->left->lvalue #define RLVAL(x) x->right->lvalue // 右節點是否為左值 #define TLVAL(x) x->lvalue // 根節點是否為左值 #define RTYPE(x) x->right->ftype // 右節點的型別鏈其開頭節點 #define RETYPE(x) x->right->etype #define LTYPE(x) x->left->ftype #define LETYPE(x) x->left->etype // 左節點的型別鏈其末端節點 #define TTYPE(x) x->ftype // 根節點的型別鏈其開頭節點 #define TETYPE(x) x->etype // 根節點的型別鏈其末端節點
body = resolveSymbols (body); /* resolve the symbols */ body = decorateType (body, RESULT_TYPE_NONE); /* propagateType & do semantic checks */
/*-----------------------------------------------------------------*/ /* resolveSymbols - resolve symbols from the symbol table */ /*-----------------------------------------------------------------*/ ast * resolveSymbols (ast * tree) { /* walk the entire tree and check for values */ /* with symbols if we find one then replace */ /* symbol with that from the symbol table */ /* make sure we resolve the true & false labels for ifx */ if (tree->type == EX_OP && tree->opval.op == IFX) { symbol *csym; if (tree->trueLabel) { if ((csym = findSym (LabelTab, tree->trueLabel, tree->trueLabel->name))) tree->trueLabel = csym; else werrorfl (tree->filename, tree->lineno, E_LABEL_UNDEF, tree->trueLabel->name); } if (tree->falseLabel) { if ((csym = findSym (LabelTab, tree->falseLabel, tree->falseLabel->name))) tree->falseLabel = csym; else werrorfl (tree->filename, tree->lineno, E_LABEL_UNDEF, tree->falseLabel->name); } }
/*--------------------------------------------------------------------*/ /* decorateType - compute type for this tree, also does type checking.*/ /* This is done bottom up, since type has to flow upwards. */ /* resultType flows top-down and forces e.g. char-arithmetic, if the */ /* result is a char and the operand(s) are int's. */ /* It also does constant folding, and parameter checking. */ /*--------------------------------------------------------------------*/ ast * decorateType (ast * tree, RESULT_TYPE resultType) { /* snip */ /*------------------------------------------------------------------*/ /*----------------------------*/ /* multiplication */ /*----------------------------*/ if (!IS_ARITHMETIC (LTYPE (tree)) || !IS_ARITHMETIC (RTYPE (tree))) { werrorfl (tree->filename, tree->lineno, E_INVALID_OP, "multiplication"); goto errorTreeReturn; } /* if they are both literal then */ /* rewrite the tree */ if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree))) { // 常數折疊 (constant folding)。 tree->type = EX_VALUE; tree->opval.val = valMult (valFromType (LETYPE (tree)), valFromType (RETYPE (tree))); tree->right = tree->left = NULL; TETYPE (tree) = getSpec (TTYPE (tree) = tree->opval.val->type); return tree; } /* if left is a literal exchange left & right */ if (IS_LITERAL (LTYPE (tree))) { ast *tTree = tree->left; tree->left = tree->right; tree->right = tTree; } /* if right is a literal and */ /* we can find a 2nd literal in a mul-tree then */ /* rearrange the tree */ if (IS_LITERAL (RTYPE (tree))) { ast *parent; ast *litTree = searchLitOp (tree, &parent, "*"); if (litTree) { DEBUG_CF ("mul") ast *tTree = litTree->left; litTree->left = tree->right; tree->right = tTree; /* both operands in litTree are literal now */ decorateType (parent, resultType); } } LRVAL (tree) = RRVAL (tree) = 1; tree->left = addCast (tree->left, resultTypeProp, FALSE); // 在左右子樹插入 Cast 節點。 tree->right = addCast (tree->right, resultTypeProp, FALSE); TETYPE (tree) = getSpec (TTYPE (tree) = computeType (LTYPE (tree), RTYPE (tree), resultType, tree->opval.op)); return tree;
/*------------------------------------------------------------------*/ /* valMult - multiply constants */ /*------------------------------------------------------------------*/ value * valMult (value * lval, value * rval) { value *val; /* create a new value */ val = newValue (); val->type = val->etype = computeType (lval->etype, rval->etype, RESULT_TYPE_INT, '*'); SPEC_SCLS (val->etype) = S_LITERAL; /* will remain literal */ if (IS_FLOAT (val->type)) SPEC_CVAL (val->type).v_float = floatFromVal (lval) * floatFromVal (rval);
/*-----------------------------------------------------------------*/ /* addCast - adds casts to a type specified by RESULT_TYPE */ /*-----------------------------------------------------------------*/ static ast * addCast (ast * tree, RESULT_TYPE resultType, bool promote) { sym_link *newLink; bool upCasted = FALSE; switch (resultType) { case RESULT_TYPE_NONE: /* if thing smaller than int must be promoted to int */ if (!promote || getSize (tree->etype) >= INTSIZE) /* promotion not necessary or already an int */ return tree; /* char and bits: promote to int */ newLink = newIntLink (); upCasted = TRUE; break; /* snip */ default: return tree; } tree->decorated = 0; tree = newNode (CAST, newAst_LINK (newLink), tree); tree->filename = tree->right->filename; tree->lineno = tree->right->lineno; /* keep unsigned type during cast to smaller type, but not when promoting from char to int */ if (!upCasted) SPEC_USIGN (tree->left->opval.lnk) = IS_UNSIGNED (tree->right->etype) ? 1 : 0; return decorateType (tree, resultType); }
/*------------------------------------------------------------------*/ /* computeType - computes the resultant type from two types */ /*------------------------------------------------------------------*/ sym_link * computeType (sym_link * type1, sym_link * type2, RESULT_TYPE resultType, int op) {
int main() { int a = 0; { int a = 0; int b = 1; int c = a + b; } return 0; }
type chain (return type, storage class) | v FUNCTION (_main=0x9d81ab8) type (int fixed) args (void) | | | v ----> ast node address ----> args type chain function name tree (0x9d81a60) not decorated ----> left node is not decorated ---- L (level), B (block) | v (null):0:{ L1 B0 (null):0: DECLARE SYMBOL (L1 B1 a=0x9d7ef00) type (int fixed) (null):0: { L2 B1 (null):0: DECLARE SYMBOL (L2 B2 a=0x9d7f538) type (int fixed) (null):0: DECLARE SYMBOL (L2 B2 b=0x9d7fa78) type (int fixed) (null):0: DECLARE SYMBOL (L2 B2 c=0x9d7ffb8) type (int fixed) (null):0: } test.c:11: RETURN (0x9d80b50) type (int literal) test.c:0: CONSTANT (0x9d81550) value = 0, 0x0, 0.000000 type (int literal) (null):0:}
int main() { char a = 0; int b = 1; a + b; return 0; }
FUNCTION (_main=0xa204f60) type (int fixed) args (void) tree (0xa204f08) not decorated (null):0:{ L1 B0 (null):0: DECLARE SYMBOL (L1 B1 a=0xa2030a0) type (char fixed) (null):0: DECLARE SYMBOL (L1 B1 b=0xa2035e0) type (int fixed) test.c:4: ADD (0xa2040c8) type (int fixed) test.c:4: CAST (0xa204878) from type (char fixed) to type (int fixed) test.c:4: SYMBOL (L1 B1 a=0xa203d68 @ 0xa2030a0) type (char fixed) test.c:4: SYMBOL (L1 B1 b=0xa204070 @ 0xa2035e0) type (int fixed) test.c:6: RETURN (0xa2042c0) type (int literal) test.c:0: CONSTANT (0xa2049f8) value = 0, 0x0, 0.000000 type (int literal) (null):0:}
ADD (int) / \ CAST SYMBOL (int) / SYMBOL (char)
yyparse (SDCCmain.c) → AST (SDCCast.c) → iCode (SDCCicode.c) → BBlock (SDCCopt.c) → iCode (SDCCicode.c) → CodeGen
%token IFX ADDRESS_OF GET_VALUE_AT_ADDRESS SPIL UNSPIL GETHBIT GETABIT GETBYTE GETWORD %token BITWISEAND UNARYMINUS IPUSH IPOP PCALL ENDFUNCTION JUMPTABLE %token RRC RLC %token CAST CALL PARAM NULLOP BLOCK LABEL RECEIVE SEND ARRAYINIT %token DUMMY_READ_VOLATILE ENDCRITICAL SWAP INLINE NORETURN RESTRICT SMALLC Z88DK_FASTCALL Z88DK_CALLEE ALIGNAS %token ASM
/* definition for intermediate code */ #define IC_RESULT(x) (x)->ulrrcnd.lrr.result // 取得 iCode 的結果 operand #define IC_LEFT(x) (x)->ulrrcnd.lrr.left // 取得 iCode 的左 operand #define IC_RIGHT(x) (x)->ulrrcnd.lrr.right // 取得 iCode 的右 operand #define IC_COND(x) (x)->ulrrcnd.cnd.condition // 取得 iCode 中的條件表達式 #define IC_TRUE(x) (x)->ulrrcnd.cnd.trueLabel // 取得 iCode 中,條件為真的 label #define IC_FALSE(x) (x)->ulrrcnd.cnd.falseLabel // 取得 iCode 中,條件為假的 label #define IC_LABEL(x) (x)->label // 取得 goto 跳轉到的 label #define IC_JTCOND(x) (x)->ulrrcnd.jmpTab.condition // 取得 jump table 中的條件表達式 #define IC_JTLABELS(x) (x)->ulrrcnd.jmpTab.labels // 取得 jump table 中,欲跳轉到的 label 所成之集合 #define IC_INLINE(x) (x)->inlineAsm #define IC_ARRAYILIST(x) (x)->arrayInitList
#define OP_SYMBOL(op) validateOpType(op, "OP_SYMBOL", #op, SYMBOL, __FILE__, __LINE__)->svt.symOperand #define OP_SYMBOL_CONST(op) validateOpTypeConst(op, "OP_SYMBOL", #op, SYMBOL, __FILE__, __LINE__)->svt.symOperand #define OP_VALUE(op) validateOpType(op, "OP_VALUE", #op, VALUE, __FILE__, __LINE__)->svt.valOperand #define OP_SYM_TYPE(op) validateOpType(op, "OP_SYM_TYPE", #op, SYMBOL, __FILE__, __LINE__)->svt.symOperand->type #define OP_SYM_ETYPE(op) validateOpType(op, "OP_SYM_ETYPE", #op, SYMBOL, __FILE__, __LINE__)->svt.symOperand->etype #define SPIL_LOC(op) validateOpType(op, "SPIL_LOC", #op, SYMBOL, __FILE__, __LINE__)->svt.symOperand->usl.spillLoc #define OP_LIVEFROM(op) validateOpType(op, "OP_LIVEFROM", #op, SYMBOL, __FILE__, __LINE__)->svt.symOperand->liveFrom #define OP_LIVETO(op) validateOpType(op, "OP_LIVETO", #op, SYMBOL, __FILE__, __LINE__)->svt.symOperand->liveTo #define OP_REQV(op) validateOpType(op, "OP_REQV", #op, SYMBOL, __FILE__, __LINE__)->svt.symOperand->reqv #define OP_KEY(op) validateOpType(op, "OP_REQV", #op, SYMBOL, __FILE__, __LINE__)->svt.symOperand->key #define OP_TYPE(op) validateOpType(op, "OP_TYPE", #op, TYPE, __FILE__, __LINE__)->svt.typeOperand
/* optimize the chain for labels & gotos this will eliminate redundant labels and will change jump to jumps by jumps */ ic = iCodeLabelOptimize (ic); /* compute the control flow */ computeControlFlow (ebbi); /* dumpraw if asked for */ if (options.dump_i_code) dumpEbbsToFileExt (DUMP_RAW0, ebbi);
/* replace the local variables with their register equivalents : the liveRange computation along with the register allocation will determine if it finally stays in the registers */ replaceRegEqv (ebbi); /* create loop regions */ loops = createLoopRegions (ebbi); /* dumpraw if asked for */ if (options.dump_i_code) dumpEbbsToFileExt (DUMP_RAW1, ebbi);
optimizeCastCast (ebbi->bbOrder, ebbi->count); /* Burn the corpses, so the dead may rest in peace, safe from cse necromancy */ computeDataFlow (ebbi); killDeadCode (ebbi); /* do common subexpression elimination for each block */ change = cseAllBlocks (ebbi, FALSE); /* dumpraw if asked for */ if (options.dump_i_code) dumpEbbsToFileExt (DUMP_CSE, ebbi);
/* compute the data flow */ computeDataFlow (ebbi); /* dumpraw if asked for */ if (options.dump_i_code) dumpEbbsToFileExt (DUMP_DFLOW, ebbi);
/* global common subexpression elimination */ if (optimize.global_cse) { change += cseAllBlocks (ebbi, FALSE); if (options.dump_i_code) dumpEbbsToFileExt (DUMP_GCSE, ebbi); } else { // compute the dataflow only assert(cseAllBlocks (ebbi, TRUE)==0); }
/* kill dead code */ kchange = killDeadCode (ebbi); if (options.dump_i_code) dumpEbbsToFileExt (DUMP_DEADCODE, ebbi);
/* do loop optimizations */ change += (lchange = loopOptimizations (loops, ebbi)); if (options.dump_i_code) dumpEbbsToFileExt (DUMP_LOOP, ebbi);
/* recompute the data flow and apply global cse again if loops optimizations or dead code caused a change: loops will brings out of the loop which then may be available for use in the later blocks: dead code elimination could potentially disconnect some blocks conditional flow may be efected so we need to apply subexpression once more */ if (lchange || kchange) { computeDataFlow (ebbi); change += cseAllBlocks (ebbi, FALSE); if (options.dump_i_code) dumpEbbsToFileExt (DUMP_LOOPG, ebbi); /* if loop optimizations caused a change then do dead code elimination once more : this will get rid of the extra assignments to the induction variables created during loop optimizations */ killDeadCode (ebbi); if (options.dump_i_code) dumpEbbsToFileExt (DUMP_LOOPD, ebbi); }
offsetFoldGet (ebbi->bbOrder, ebbi->count); /* lospre */ computeControlFlow (ebbi); loops = createLoopRegions (ebbi); computeDataFlow (ebbi); computeLiveRanges (ebbi->bbOrder, ebbi->count, FALSE); adjustIChain (ebbi->bbOrder, ebbi->count); ic = iCodeLabelOptimize (iCodeFromeBBlock (ebbi->bbOrder, ebbi->count)); if (optimize.lospre && (TARGET_Z80_LIKE || TARGET_HC08_LIKE || TARGET_IS_STM8)) /* Todo: enable for other ports. */ { lospre (ic, ebbi); if (options.dump_i_code) dumpEbbsToFileExt (DUMP_LOSPRE, ebbi); /* GCSE, lospre and maybe other optimizations sometimes create temporaries that have non-connected live ranges, which is bad. Split them. */ ebbi = iCodeBreakDown (ic); computeControlFlow (ebbi); loops = createLoopRegions (ebbi); computeDataFlow (ebbi); recomputeLiveRanges (ebbi->bbOrder, ebbi->count, FALSE); adjustIChain (ebbi->bbOrder, ebbi->count); ic = iCodeLabelOptimize (iCodeFromeBBlock (ebbi->bbOrder, ebbi->count)); separateLiveRanges (ic, ebbi); }
/* compute the live ranges */ recomputeLiveRanges (ebbi->bbOrder, ebbi->count, TRUE); if (options.dump_i_code) dumpEbbsToFileExt (DUMP_RANGE, ebbi);
/* change assignments this will remove some live ranges reducing some register pressure */ for (i = 0; i < count; i++) packRegisters (ebbs, i); /* liveranges probably changed by register packing so we compute them again */ recomputeLiveRanges (ebbs, count, FALSE); if (options.dump_i_code) dumpEbbsToFileExt (DUMP_PACK, ebbi);
/* first determine for each live range the number of registers & the type of registers required for each */ regTypeNum (*ebbs); /* and serially allocate registers */ serialRegAssign (ebbs, count); freeAllRegs (); /* after that create the register mask for each of the instruction */ createRegMask (ebbs, count); /* Convert the old sym->accuse flag into normal register assignments */ replaceAccuse (ebbs, count); /* redo that offsets for stacked automatic variables */ if (currFunc) { redoStackOffsets (); } if (options.dump_i_code) { dumpEbbsToFileExt (DUMP_RASSGN, ebbi); dumpLiveRanges (DUMP_LRANGE, liveRanges); }
/* break it down into basic blocks */ ebbi = iCodeBreakDown (ic); /* compute the control flow */ computeControlFlow (ebbi); /* dumpraw if asked for */ if (options.dump_i_code) dumpEbbsToFileExt (DUMP_RAW0, ebbi);
/*-----------------------------------------------------------------*/ /* dumpEbbsToFileExt - write all the basic blocks to a file */ /*-----------------------------------------------------------------*/ void dumpEbbsToFileExt (int id, ebbIndex * ebbi) { for (i = 0; i < count; i++) { fprintf (of, "\n----------------------------------------------------------------\n"); fprintf (of, "Basic Block %s (df:%d bb:%d lvl:%d): loopDepth=%d%s%s%s\n", ebbs[i]->entryLabel->name, ebbs[i]->dfnum, ebbs[i]->bbnum, ebbs[i]->entryLabel->level, ebbs[i]->depth, ebbs[i]->noPath ? " noPath" : "", ebbs[i]->partOfLoop ? " partOfLoop" : "", ebbs[i]->isLastInLoop ? " isLastInLoop" : ""); // a --nolabelopt makes this more readable fprintf (of, "\nsuccessors: "); for (bb = setFirstItem (ebbs[i]->succList); bb; bb = setNextItem (ebbs[i]->succList)) { fprintf (of, "%s ", bb->entryLabel->name); } fprintf (of, "\npredecessors: "); for (bb = setFirstItem (ebbs[i]->predList); bb; bb = setNextItem (ebbs[i]->predList)) { fprintf (of, "%s ", bb->entryLabel->name); } fprintf (of, "\ndominators: "); for (d = 0; d < ebbs[i]->domVect->size; d++) { if (bitVectBitValue (ebbs[i]->domVect, d)) { fprintf (of, "%s ", ebbi->bbOrder[d]->entryLabel->name); //ebbs[d]->entryLabel->name); } } fprintf (of, "\n"); fprintf (of, "\ndefines bitVector :"); bitVectDebugOn (ebbs[i]->defSet, of); fprintf (of, "\nlocal defines bitVector :"); bitVectDebugOn (ebbs[i]->ldefs, of); fprintf (of, "\npointers Set bitvector :"); bitVectDebugOn (ebbs[i]->ptrsSet, of); #if 0 fprintf (of, "\nin coming definitions :"); bitVectDebugOn (ebbs[i]->inDefs, of); fprintf (of, "\nout going definitions :"); bitVectDebugOn (ebbs[i]->outDefs, of); fprintf (of, "\ndefines used :"); bitVectDebugOn (ebbs[i]->usesDefs, of); #endif if (ebbs[i]->isLastInLoop) { fprintf (of, "\nInductions Set bitvector :"); bitVectDebugOn (ebbs[i]->linds, of); } fprintf (of, "\ninExprs:"); for (cseSet = ebbs[i]->inExprs; cseSet; cseSet = cseSet->next) { cseDef *item = cseSet->item; fprintf (of, " %s(%d)", OP_SYMBOL (item->sym)->name, item->diCode->key); if (item->fromGlobal) fprintf (of, "g"); } fprintf (of, "\noutExprs:"); for (cseSet = ebbs[i]->outExprs; cseSet; cseSet = cseSet->next) { cseDef *item = cseSet->item; fprintf (of, " %s(%d)", OP_SYMBOL (item->sym)->name, item->diCode->key); if (item->fromGlobal) fprintf (of, "g"); } fprintf (of, "\nkilledExprs:"); for (cseSet = ebbs[i]->killedExprs; cseSet; cseSet = cseSet->next) { cseDef *item = cseSet->item; fprintf (of, " %s(%d)", OP_SYMBOL (item->sym)->name, item->diCode->key); if (item->fromGlobal) fprintf (of, "g"); } fprintf (of, "\n----------------------------------------------------------------\n"); printiCChain (ebbs[i]->sch, of); } fflush (of); }
for (loop = icChain; loop; loop = loop->next) { if ((icTab = getTableEntry (loop->op))) { struct dbuf_s dbuf; fprintf (of, "%s(l%d:s%d:k%d:d%d:s%d)\t", loop->filename, loop->lineno, loop->seq, loop->key, loop->depth, loop->supportRtn); dbuf_init (&dbuf, 1024); icTab->iCodePrint (&dbuf, loop, icTab->printName); dbuf_write_and_destroy (&dbuf, of); fflush (of); } }
int main() { return 0; }
---------------------------------------------------------------- Basic Block _entry (df:1 bb:0 lvl:1): loopDepth=0 successors: _return predecessors: dominators: _entry defines bitVector : local defines bitVector : pointers Set bitvector : inExprs: outExprs: killedExprs: ---------------------------------------------------------------- test.c(l1:s0:k0:d0:s0) _entry($2) : test.c(l1:s0:k1:d0:s0) proc _main [k1 lr0:0 so:0]{ ia0 a2p0 re0 rm0 nos0 ru0 dp0}{int function ( ) fixed} symbol 的內部名稱 symbol 屬性 k : key lr: live range so: stack (local or global symbol) symbol & operand 屬性 ia : is an address a2p: aggregate to pointer to aggregate re : is the register equivalent of a symbol rm : can be remateriazed nos: cannot be assigned a spil location ru : used in return statement only dp : (8051) data pointer symbol type storage class test.c(l3:s0:k2:d0:s0) ret 0x0 {int literal} ---------------------------------------------------------------- Basic Block _return (df:2 bb:1 lvl:1): loopDepth=0 successors: predecessors: _entry dominators: _entry _return defines bitVector : local defines bitVector : pointers Set bitvector : inExprs: outExprs: killedExprs: ---------------------------------------------------------------- test.c(l3:s0:k3:d0:s0) _return($1) : test.c(l3:s0:k4:d0:s0) eproc _main [k1 lr0:0 so:0]{ ia0 a2p0 re0 rm0 nos0 ru0 dp0}{int function ( ) fixed}
__xdata int * p; int gint; /* This function does nothing useful. It is used for the purpose of explaining iCode */ short function (__data int *x) { short i=10; /* dead initialization eliminated */ short sum=10; /* dead initialization eliminated */ short mul; int j ; while (*x) *x++ = *p++; sum = 0 ; mul = 0; /* compiler detects i,j to be induction variables */ for (i = 0, j = 10 ; i < 10 ; i++, j--) { sum += i; mul += i * 3; /* this multiplication remains */ gint += j * 3; /* this multiplication changed to addition */ } return sum+mul; }
/* type asmop : a homogenised type for all the different spaces an operand can be in */ typedef struct asmop {
/*-----------------------------------------------------------------*/ /* genNot - generate code for ! operation */ /*-----------------------------------------------------------------*/ static void genNot (iCode * ic) { bool needpulla; D (emitcode ("; genNot", "")); /* assign asmOps to operand & result */ aopOp (IC_LEFT (ic), ic, FALSE); // 針對 ic 的左 operand 生成 asmop aopOp (IC_RESULT (ic), ic, TRUE); // 針對 ic 的 result 生成 asmop needpulla = pushRegIfSurv (hc08_reg_a); // 如果暫存器 a 當前的值還需要被使用,則入棧加以保存 asmopToBool (AOP (IC_LEFT (ic)), TRUE); // 針對 asmop 生成代碼,產生真假值。 emitcode ("eor", one); regalloc_dry_run_cost += 2; storeRegToFullAop (hc08_reg_a, AOP (IC_RESULT (ic)), FALSE); pullOrFreeReg (hc08_reg_a, needpulla); freeAsmop (IC_RESULT (ic), NULL, ic, TRUE); freeAsmop (IC_LEFT (ic), NULL, ic, TRUE); }
/*-----------------------------------------------------------------*/ /* aopOp - allocates an asmop for an operand : */ /*-----------------------------------------------------------------*/ static void aopOp (operand *op, iCode * ic, bool result) { /* snip */ /* if this a literal */ if (IS_OP_LITERAL (op)) { op->aop = aop = newAsmop (AOP_LIT); // 注意! 生成的 asmop 記錄在 operand 的 aop 欄位。 aop->aopu.aop_lit = OP_VALUE (op); aop->size = getSize (operandType (op)); aop->op = op; return; } /* snip */ }
SDCC 似乎存在有兩套除錯資訊,cdbFile 和 SDCCdwarf2。前者是另外寫至以 .adb 和 .cdb 後綴的檔案 (開啟 –debug
選項即會使用),後者則是將除錯資訊寫至匯編 (hc08 另外再開啟 –out-fmt-elf
選項下會使用)。
typedef struct DebugFile { int (*openFile) (const char *file); int (*closeFile) (void); int (*writeModule) (const char *name); int (*writeFunction) (symbol *pSym, iCode *ic); int (*writeEndFunction) (symbol *pSym, iCode *ic, int offset); int (*writeLabel) (symbol *pSym, iCode *ic); int (*writeScope) (iCode *ic); int (*writeSymbol) (symbol *pSym); int (*writeType) (structdef *sdef, int block, int inStruct, const char *tag); int (*writeCLine) (iCode *ic); int (*writeALine) (const char *module, int Line); int (*writeFrameAddress) (const char *variable, struct reg_info *reg, int offset); }DEBUGFILE;
DEBUGFILE dwarf2DebugFile = { &dwOpenFile, &dwCloseFile, &dwWriteModule, &dwWriteFunction, &dwWriteEndFunction, &dwWriteLabel, &dwWriteScope, &dwWriteSymbol, &dwWriteType, &dwWriteCLine, &dwWriteALine, &dwWriteFrameAddress };
DEBUGFILE *debugFile = &cdbDebugFile;
static bool _hc08_parseOptions (int *pargc, char **argv, int *i) { if (!strcmp (argv[*i], "--out-fmt-elf")) { options.out_fmt = 'E'; debugFile = &dwarf2DebugFile; return TRUE; } if (!strcmp (argv[*i], "--oldralloc")) { options.oldralloc = TRUE; return TRUE; } return FALSE; }
/*-----------------------------------------------------------------*/ /* genEndFunction - generates epilogue for functions */ /*-----------------------------------------------------------------*/ static void genEndFunction (iCode * ic) { symbol *sym = OP_SYMBOL (IC_LEFT (ic)); if (IFFUNC_ISNAKED (sym->type)) { emitcode (";", "naked function: no epilogue."); if (options.debug && currFunc) debugFile->writeEndFunction (currFunc, ic, 0); return; }
struct { void (*emitDebuggerSymbol) (const char *); struct { int (*regNum) (const struct reg_info *); bitVect *cfiSame; bitVect *cfiUndef; int addressSize; int regNumRet; int regNumSP; int regNumBP; int offsetSP; } dwarf; } debugger;
{ hc08_emitDebuggerSymbol, { hc08_dwarfRegNum, NULL, NULL, 4, /* addressSize */ 14, /* regNumRet */ 15, /* regNumSP */ -1, /* regNumBP */ 1, /* offsetSP */ }, },
/*-----------------------------------------------------------------------*/ /* dwWriteFrameAddress - note the current position of the frame pointer */ /* address. The base address can be specified by */ /* either a register or pointer variable, leaving */ /* the other as NULL. If both are NULL, there is */ /* no current frame pointer address defined. */ /*-----------------------------------------------------------------------*/ int dwWriteFrameAddress(const char *variable, struct reg_info *reg, int offset) { /* snip */ else if (reg) /* frame pointer based from a register */ { regNum = port->debugger.dwarf.regNum (reg); /* snip */
{ stm8_emitDebuggerSymbol },
int cdbWriteFunction (symbol *pSym, iCode *ic) { char debugSym[INITIAL_INLINEASM]; if (getenv ("SDCC_DEBUG_FUNCTION_POINTERS")) fprintf (stderr, "cdbFile.c:cdbWriteFunction()\n"); if (!cdbFilePtr) return 0; if (IS_STATIC (pSym->etype)) sprintf (debugSym, "F%s$%s$0$0", moduleName, pSym->name); else sprintf (debugSym, "G$%s$0$0", pSym->name); emitDebuggerSymbol (debugSym); return cdbWriteBasicSymbol (pSym, FALSE, TRUE); }
statement : labeled_statement | compound_statement | expression_statement | selection_statement | iteration_statement | jump_statement | critical_statement | asm_statement ;
exit: case 10: break;
{ // ... code ... }
if (cond) { // ... code ... } else { // ... code .. } switch (cond) { // ... code ... }
while (cond) { // ... code ... } do { // ... code ... } while (cond); for ( init; cond; exp) { // ... code ... }
selection_statement : IF '(' expr ')' { seqPointNo++;} statement else_statement { noLineno++; $$ = createIf ($3, $6, $7 ); $$->lineno = $3->lineno; $$->filename = $3->filename; noLineno--; }
/*-----------------------------------------------------------------*/ /* createIf - creates the parsetree for the if statement */ /*-----------------------------------------------------------------*/ ast * createIf (ast * condAst, ast * ifBody, ast * elseBody) { static int Lblnum = 0; ast *ifTree; symbol *ifTrue, *ifFalse, *ifEnd; struct dbuf_s dbuf; /* if neither exists */ if (!elseBody && !ifBody) { // if there are no side effects (i++, j() etc) if (!hasSEFcalls (condAst)) { return condAst; } } /* create the labels */ dbuf_init (&dbuf, 128); dbuf_printf (&dbuf, "_iffalse_%d", Lblnum); ifFalse = newSymbol (dbuf_c_str (&dbuf), NestLevel); dbuf_destroy (&dbuf); /* if no else body then end == false */ if (!elseBody) ifEnd = ifFalse; else { dbuf_init (&dbuf, 128); dbuf_printf (&dbuf, "_ifend_%d", Lblnum); ifEnd = newSymbol (dbuf_c_str (&dbuf), NestLevel); dbuf_destroy (&dbuf); } dbuf_init (&dbuf, 128); dbuf_printf (&dbuf, "_iftrue_%d", Lblnum); ifTrue = newSymbol (dbuf_c_str (&dbuf), NestLevel); dbuf_destroy (&dbuf); Lblnum++; /* attach the ifTrue label to the top of it body */ ifBody = createLabel (ifTrue, ifBody); /* attach a goto end to the ifBody if else is present */ if (elseBody) { ifBody = newNode (NULLOP, ifBody, newNode (GOTO, newAst_VALUE (symbolVal (ifEnd)), NULL)); /* put the elseLabel on the else body */ elseBody = createLabel (ifFalse, elseBody); /* out the end at the end of the body */ elseBody = newNode (NULLOP, elseBody, createLabel (ifEnd, NULL)); } else { ifBody = newNode (NULLOP, ifBody, createLabel (ifFalse, NULL)); } condAst = backPatchLabels (condAst, ifTrue, ifFalse); if (IS_IFX (condAst)) ifTree = condAst; else ifTree = newIfxNode (condAst, ifTrue, ifFalse); return newNode (NULLOP, ifTree, newNode (NULLOP, ifBody, elseBody)); }
while : WHILE { /* create and push the continue , break & body labels */ static int Lblnum = 0; /* continue */ SNPRINTF (lbuff, sizeof(lbuff), "_whilecontinue_%d",Lblnum); STACK_PUSH(continueStack,newSymbol(lbuff,NestLevel)); /* break */ SNPRINTF (lbuff, sizeof(lbuff), "_whilebreak_%d",Lblnum); STACK_PUSH(breakStack,newSymbol(lbuff,NestLevel)); /* body */ SNPRINTF (lbuff, sizeof(lbuff), "_whilebody_%d",Lblnum++); $$ = newSymbol(lbuff,NestLevel); } ; iteration_statement : while '(' expr ')' { seqPointNo++;} statement { noLineno++; $$ = createWhile ( $1, STACK_POP(continueStack), STACK_POP(breakStack), $3, $6 ); $$->lineno = $1->lineDef; $$->filename = $1->fileDef; noLineno--; }
/*-----------------------------------------------------------------*/ /* createWhile - creates parse tree for while statement */ /* the while statement will be created as follows */ /* */ /* _while_continue_n: */ /* condition_expression +-> trueLabel -> _while_boby_n */ /* | */ /* +-> falseLabel -> _while_break_n */ /* _while_body_n: */ /* statements */ /* goto _while_continue_n */ /* _while_break_n: */ /*-----------------------------------------------------------------*/ ast * createWhile (symbol * trueLabel, symbol * continueLabel, symbol * falseLabel, ast * condExpr, ast * whileBody) { ast *whileTree; /* put the continue label */ condExpr = backPatchLabels (condExpr, trueLabel, falseLabel); if (condExpr && !IS_IFX (condExpr)) { condExpr = newNode (IFX, condExpr, NULL); /* put the true & false labels in place */ condExpr->trueLabel = trueLabel; condExpr->falseLabel = falseLabel; } whileTree = createLabel (continueLabel, condExpr); whileTree->filename = NULL; whileTree->lineno = 0; /* put the body label in front of the body */ if(whileBody && whileBody->type == EX_VALUE && !whileBody->left && !whileBody->right) whileBody = newNode (NULLOP, NULL, whileBody); whileBody = createLabel (trueLabel, whileBody); whileBody->filename = NULL; whileBody->lineno = 0; /* put a jump to continue at the end of the body */ /* and put break label at the end of the body */ whileBody = newNode (NULLOP, whileBody, newNode (GOTO, newAst_VALUE (symbolVal (continueLabel)), createLabel (falseLabel, NULL))); /* put it all together */ return newNode (NULLOP, whileTree, whileBody); }
statement_list : statement | statement_list statement { $$ = newNode(NULLOP,$1,$2);} ;
ast ^ | val ^ | symbol <- lnk (描述 symbol 型別和屬性) (identifier)
#define FUNC_HASVARARGS(x) (x->funcAttrs.hasVargs) #define IFFUNC_HASVARARGS(x) (IS_FUNC(x) && FUNC_HASVARARGS(x))
#define SPEC_NOUN(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.noun #define SPEC_LONG(x) validateLink(x, "SPEC_LONG", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_long
#define DCL_TYPE(l) validateLink(l, "DCL_TYPE", #l, DECLARATOR, __FILE__, __LINE__)->select.d.dcl_type #define DCL_ELEM(l) validateLink(l, "DCL_ELEM", #l, DECLARATOR, __FILE__, __LINE__)->select.d.num_elem
#define IS_FUNC(x) (IS_DECL(x) && DCL_TYPE(x) == FUNCTION) #define IS_LONG(x) (IS_SPEC(x) && x->select.s.b_long)
sym_link * validateLink (sym_link * l, const char *macro, const char *args, const char select, const char *file, unsigned line) { if (l && l->xclass == select) { return l; // 如果 sym_link l 的 xclass 同 select,是 specifier 或 declarator,返回 l。 } fprintf (stderr, "Internal error: validateLink failed in %s(%s) @ %s:%u:" " expected %s, got %s\n", macro, args, file, line, DECLSPEC2TXT (select), l ? DECLSPEC2TXT (l->xclass) : "null-link"); exit (EXIT_FAILURE); return l; // never reached, makes compiler happy. }
bucket *SymbolTab[256]; /* the symbol table */ bucket *StructTab[256]; /* the structure table */ bucket *TypedefTab[256]; /* the typedef table */ bucket *LabelTab[256]; /* the Label table */ bucket *enumTab[256]; /* enumerated table */ bucket *AddrspaceTab[256]; /* the named address space table */
function_definition : function_declarator { /* function type not specified */ /* assume it to be 'int' */ addDecl($1,0,newIntLink()); $1 = createFunctionDecl($1); } function_body { $$ = createFunction($1,$3); } | declaration_specifiers function_declarator { pointerTypes($2->type,copyLinkChain($1)); addDecl($2,0,$1); $2 = createFunctionDecl($2); } function_body { $$ = createFunction($2,$4); } ; function_declarator2 : declarator2 '(' ')' { addDecl ($1, FUNCTION, NULL); } | declarator2 '(' { NestLevel++; STACK_PUSH(blockNum, currBlockno); btree_add_child(currBlockno, ++blockNo); currBlockno = blockNo; seqPointNo++; /* not a true sequence point, but helps resolve scope */ } parameter_type_list ')' { sym_link *funcType; addDecl ($1, FUNCTION, NULL); funcType = $1->type; while (funcType && !IS_FUNC(funcType)) funcType = funcType->next; assert (funcType); FUNC_HASVARARGS(funcType) = IS_VARG($4); FUNC_ARGS(funcType) = reverseVal($4); /* nest level was incremented to take care of the parms */ NestLevel--; currBlockno = STACK_POP(blockNum); seqPointNo++; /* not a true sequence point, but helps resolve scope */ // if this was a pointer (to a function) if (!IS_FUNC($1->type)) cleanUpLevel(SymbolTab, NestLevel + 1); $$ = $1; } | declarator2 '(' identifier_list ')' { werror(E_OLD_STYLE,$1->name); /* assume it returns an int */ $1->type = $1->etype = newIntLink(); $$ = $1; } ;
iteration_statement : while '(' expr ')' { seqPointNo++;} statement { noLineno++; $$ = createWhile ( $1, STACK_POP(continueStack), STACK_POP(breakStack), $3, $6 ); $$->lineno = $1->lineDef; $$->filename = $1->fileDef; noLineno--; } ; while : WHILE { /* create and push the continue , break & body labels */ static int Lblnum = 0; /* continue */ SNPRINTF (lbuff, sizeof(lbuff), "_whilecontinue_%d",Lblnum); STACK_PUSH(continueStack,newSymbol(lbuff,NestLevel)); /* break */ SNPRINTF (lbuff, sizeof(lbuff), "_whilebreak_%d",Lblnum); STACK_PUSH(breakStack,newSymbol(lbuff,NestLevel)); /* body */ SNPRINTF (lbuff, sizeof(lbuff), "_whilebody_%d",Lblnum++); $$ = newSymbol(lbuff,NestLevel); } ;
/*-----------------------------------------------------------------*/ /* createWhile - creates parse tree for while statement */ /* the while statement will be created as follows */ /* */ /* _while_continue_n: */ /* condition_expression +-> trueLabel -> _while_boby_n */ /* | */ /* +-> falseLabel -> _while_break_n */ /* _while_body_n: */ /* statements */ /* goto _while_continue_n */ /* _while_break_n: */ /*-----------------------------------------------------------------*/ ast * createWhile (symbol * trueLabel, symbol * continueLabel, symbol * falseLabel, ast * condExpr, ast * whileBody) { ast *whileTree; /* put the continue label */ condExpr = backPatchLabels (condExpr, trueLabel, falseLabel); if (condExpr && !IS_IFX (condExpr)) { condExpr = newNode (IFX, condExpr, NULL); /* put the true & false labels in place */ condExpr->trueLabel = trueLabel; condExpr->falseLabel = falseLabel; } whileTree = createLabel (continueLabel, condExpr); whileTree->filename = NULL; whileTree->lineno = 0; /* put the body label in front of the body */ whileBody = createLabel (trueLabel, whileBody); whileBody->filename = NULL; whileBody->lineno = 0; /* put a jump to continue at the end of the body */ /* and put break label at the end of the body */ whileBody = newNode (NULLOP, whileBody, newNode (GOTO, newAst_VALUE (symbolVal (continueLabel)), createLabel (falseLabel, NULL))); /* put it all together */ return newNode (NULLOP, whileTree, whileBody); }
void main() { int i, j; bool flag = true; if (flag == false) { i = 1; } else { j = 2; } }
/*-----------------------------------------------------------------*/ /* createIf - creates the parsetree for the if statement */ /* */ /* condition_expression +-> ifTrue */ /* | -> ifEnd */ /* +-> ifFalse */ /*-----------------------------------------------------------------*/ ast * createIf (ast * condAst, ast * ifBody, ast * elseBody) { static int Lblnum = 0; ast *ifTree; symbol *ifTrue, *ifFalse, *ifEnd; struct dbuf_s dbuf; /* if neither exists */ if (!elseBody && !ifBody) { // if there are no side effects (i++, j() etc) if (!hasSEFcalls (condAst)) { return condAst; } } /* create the labels */ dbuf_init (&dbuf, 128); dbuf_printf (&dbuf, "__iffalse_%d", Lblnum); ifFalse = newSymbol (dbuf_c_str (&dbuf), NestLevel); dbuf_destroy (&dbuf); /* if no else body then end == false */ if (!elseBody) { ifEnd = ifFalse; } else { dbuf_init (&dbuf, 128); dbuf_printf (&dbuf, "__ifend_%d", Lblnum); ifEnd = newSymbol (dbuf_c_str (&dbuf), NestLevel); dbuf_destroy (&dbuf); } dbuf_init (&dbuf, 128); dbuf_printf (&dbuf, "__iftrue_%d", Lblnum); ifTrue = newSymbol (dbuf_c_str (&dbuf), NestLevel); dbuf_destroy (&dbuf); Lblnum++; /* attach the ifTrue label to the top of it body */ ifBody = createLabel (ifTrue, ifBody); /* attach a goto end to the ifBody if else is present */ if (elseBody) { ifBody = newNode (NULLOP, ifBody, newNode (GOTO, newAst_VALUE (symbolVal (ifEnd)), NULL)); /* put the elseLabel on the else body */ elseBody = createLabel (ifFalse, elseBody); /* out the end at the end of the body */ elseBody = newNode (NULLOP, elseBody, createLabel (ifEnd, NULL)); } else { ifBody = newNode (NULLOP, ifBody, createLabel (ifFalse, NULL)); } condAst = backPatchLabels (condAst, ifTrue, ifFalse); if (IS_IFX (condAst)) ifTree = condAst; else ifTree = newIfxNode (condAst, ifTrue, ifFalse); return newNode (NULLOP, ifTree, newNode (NULLOP, ifBody, elseBody)); }
if (Flag==0x00) { X_axis = 0; Y_axis = 0; } if (X_axis) do_something();
$ cd sdcc-3.4.0/src/ $ mkdir Y $ cp X/* Y/
// Y 必須符合 C 識別字命名規則,不可以數字開頭。
$ cd sdcc-3.4.0/ $ vim configure.in $ autoconf
$ vi clean.mk $ vi port.h $ vi SDCCmain.c
$ ../sdcc-3.4.0/configure $ make $ ./bin/sdcc -h Special options for the Y port: --out-fmt-elf Output executable in ELF format --oldralloc Use old register allocator $ ./bin/sdcc -mY -S test.c
The 8051 family of microcontrollers provides a distinct memory area for accessing Special Function Registers (SFRs). SFRs are used in your program to control timers, counters, serial I/Os, port I/Os, and peripherals.
With typical 8051 applications, it is often necessary to access individual bits within an SFR. The sbit type provides access to bit-addressable SFRs and other bit-addressable objects.
int foo(); | | | -----> declarator v specifier
/*-----------------------------------------------------------------*/ /* genCall - generates a call statement */ /*-----------------------------------------------------------------*/ static void genCall (iCode * ic) { sym_link *dtype; sym_link *etype; // bool restoreBank = FALSE; // bool swapBanks = FALSE; D (emitcode (";", "genCall")); /* if caller saves & we have not saved then */ if (!ic->regsSaved) saveRegisters (ic); dtype = operandType (IC_LEFT (ic)); etype = getSpec (dtype); /* if send set is not empty then assign */ if (_G.sendSet && !regalloc_dry_run) { if (IFFUNC_ISREENT (dtype)) /* need to reverse the send set */ { genSend (reverseSet (_G.sendSet)); } else { genSend (_G.sendSet); } _G.sendSet = NULL; } /* make the call */ if (IS_LITERAL (etype)) { emitcode ("jsr", "0x%04X", ulFromVal (OP_VALUE (IC_LEFT (ic)))); regalloc_dry_run_cost += 3; } else { bool jump = (!ic->parmBytes && IFFUNC_ISNORETURN (OP_SYMBOL (IC_LEFT (ic))->type)); emitcode (jump ? "jmp" : "jsr", "%s", (OP_SYMBOL (IC_LEFT (ic))->rname[0] ? OP_SYMBOL (IC_LEFT (ic))->rname : OP_SYMBOL (IC_LEFT (ic))->name)); regalloc_dry_run_cost += 3; } hc08_dirtyReg (hc08_reg_a, FALSE); hc08_dirtyReg (hc08_reg_hx, FALSE); /* if we need assign a result value */ if ((IS_ITEMP (IC_RESULT (ic)) && (OP_SYMBOL (IC_RESULT (ic))->nRegs || OP_SYMBOL (IC_RESULT (ic))->spildir)) || IS_TRUE_SYMOP (IC_RESULT (ic))) { } }
else if (c == '/' && (CPP_OPTION (pfile, cplusplus_comments) || cpp_in_system_header (pfile))) { /* Warn about comments only if pedantically GNUC89, and not in system headers. */ if (CPP_OPTION (pfile, lang) == CLK_GNUC89 && CPP_PEDANTIC (pfile) && ! buffer->warned_cplusplus_comments) { cpp_error (pfile, CPP_DL_PEDWARN, "C++ style comments are not allowed in ISO C90"); cpp_error (pfile, CPP_DL_PEDWARN, "(this will be reported only once per input file)"); buffer->warned_cplusplus_comments = 1; } if (skip_line_comment (pfile) && CPP_OPTION (pfile, warn_comments)) cpp_warning (pfile, CPP_W_COMMENTS, "multi-line comment"); }
static void put_char_to_stdout (char c, void* p) _REENTRANT { p; //make compiler happy putchar (c); } int vprintf (const char *format, va_list ap) { return _print_format (put_char_to_stdout, NULL, format, ap); } int printf (const char *format, ...) { va_list arg; int i; va_start (arg, format); i = _print_format (put_char_to_stdout, NULL, format, arg); va_end (arg); return i; }
int _print_format (pfn_outputchar pfn, void* pvoid, const char *format, va_list ap) { while( c=*format++ ) { if ( c=='%' ) { /* 處理 format string */ } else { // nothing special, just output the character OUTPUT_CHAR( c, p ); } } return charsOutputted; }
The formats supported by this implementation are: 'd' 'u' 'c' 's' 'x' 'X'. Zero padding and field width (limited to 255) are also supported.
// 分析 fmt 字串,取得型別資訊,再透過 var_arg 從可變參數取出對應值。 void tfp_printf(char *fmt, ...) { va_list va; char ch; char* p; va_start(va,fmt); while ((ch=*(fmt++))) { if (ch!='%') { putchar(ch); } else { char lz=0; // lz: left zero char w=0; // width ch=*(fmt++); if (ch=='0') { ch=*(fmt++); lz=1; // Left-pads the number with zeroes (0) instead of spaces } if (ch>='0' && ch<='9') { w=0; // Minimum number of characters to be printed. while (ch>='0' && ch<='9') { w=(((w<<2)+w)<<1)+ch-'0'; ch=*fmt++; } } bf=buf; p=bf; zs=0; // 遇到特定 specifier,從 va_arg 抓取參數。 switch (ch) { case 0: goto abort; case 'u': case 'd' : num=va_arg(va, unsigned int); if (ch=='d' && (int)num<0) { num = -(int)num; out('-'); } divOut(10000); divOut(1000); divOut(100); divOut(10); outDgt(num); break; case 'x': case 'X' : uc= ch=='X'; // 判斷 16 進制是否需要 uppercase。 num=va_arg(va, unsigned int); divOut(0x1000); // 將 num 與 0x1000 (4096) 相除取商,並印出。 divOut(0x100); divOut(0x10); outDgt(num); // 印出最後一位。 break; case 'c' : out((char)(va_arg(va, int))); break; case 's' : p=va_arg(va, char*); break; case '%' : out('%'); default: break; } *bf=0; bf=p; // 計算 width 需要補上的長度。 while (*bf++ && w > 0) w--; // 視條件,以 0 或是空白補充 width。 while (w-- > 0) putchar(lz ? '0' : ' '); // 印出參數對應的字串。 while ((ch= *p++)) putchar(ch); } } abort:; va_end(va); }