diff --git a/gcc/ChangeLog b/gcc/ChangeLog index ceca00fa137ded4625678f73b199bf8e6cf2496c..c1fdc2ccaca4361bf5fc750be65c6789e1e7907d 100644 --- a/gcc/ChangeLog +++ b/gcc/ChangeLog @@ -1,4 +1,28 @@ -003-02-20 Aldy Hernandez <aldyh@redhat.com> +2003-02-25 Vladimir Makarov <vmakarov@redhat.com> + Richard Henderson <rth@redhat.com> + + * sched-int.h (INSN_TRAP_CLASS, WORST_CLASS): Move them from + sched-rgn.c. + (add_forward_dependence): New function prototype. + + * sched-rgn.c (INSN_TRAP_CLASS, WORST_CLASS): Move them to + sched-init.h. + (CONST_BASED_ADDRESS_P, may_trap_exp, haifa_classify_insn): Move + them to haifa-sched.c. + + * haifa-sched.c (CONST_BASED_ADDRESS_P, may_trap_exp, + haifa_classify_insn): Move them from sched-rgn.c. + + * sched-deps.c (add_dependence): Return flag of creating a new + entry. + (add_forward_dependence): New function. + (compute_forward_dependences): Use the function. + + * sched-ebb.c (earliest_block_with_similiar_load): New function. + (add_deps_for_risky_insns): New function. + (schedule_ebb): Call the function. + +2003-02-20 Aldy Hernandez <aldyh@redhat.com> * doc/tm.texi: Document Rename TARGET_VECTOR_TYPES_COMPATIBLE to TARGET_VECTOR_OPAQUE_P. Document accordingly. diff --git a/gcc/haifa-sched.c b/gcc/haifa-sched.c index a06c2f9307179f9fd8c17555abb50affa470dfee..8ea2481ce81693bf31e2fa64d524e9f7e3cbd485 100644 --- a/gcc/haifa-sched.c +++ b/gcc/haifa-sched.c @@ -305,6 +305,170 @@ struct ready_list int n_ready; }; +static int may_trap_exp PARAMS ((rtx, int)); + +/* Nonzero iff the address is comprised from at most 1 register. */ +#define CONST_BASED_ADDRESS_P(x) \ + (GET_CODE (x) == REG \ + || ((GET_CODE (x) == PLUS || GET_CODE (x) == MINUS \ + || (GET_CODE (x) == LO_SUM)) \ + && (CONSTANT_P (XEXP (x, 0)) \ + || CONSTANT_P (XEXP (x, 1))))) + +/* Returns a class that insn with GET_DEST(insn)=x may belong to, + as found by analyzing insn's expression. */ + +static int +may_trap_exp (x, is_store) + rtx x; + int is_store; +{ + enum rtx_code code; + + if (x == 0) + return TRAP_FREE; + code = GET_CODE (x); + if (is_store) + { + if (code == MEM && may_trap_p (x)) + return TRAP_RISKY; + else + return TRAP_FREE; + } + if (code == MEM) + { + /* The insn uses memory: a volatile load. */ + if (MEM_VOLATILE_P (x)) + return IRISKY; + /* An exception-free load. */ + if (!may_trap_p (x)) + return IFREE; + /* A load with 1 base register, to be further checked. */ + if (CONST_BASED_ADDRESS_P (XEXP (x, 0))) + return PFREE_CANDIDATE; + /* No info on the load, to be further checked. */ + return PRISKY_CANDIDATE; + } + else + { + const char *fmt; + int i, insn_class = TRAP_FREE; + + /* Neither store nor load, check if it may cause a trap. */ + if (may_trap_p (x)) + return TRAP_RISKY; + /* Recursive step: walk the insn... */ + fmt = GET_RTX_FORMAT (code); + for (i = GET_RTX_LENGTH (code) - 1; i >= 0; i--) + { + if (fmt[i] == 'e') + { + int tmp_class = may_trap_exp (XEXP (x, i), is_store); + insn_class = WORST_CLASS (insn_class, tmp_class); + } + else if (fmt[i] == 'E') + { + int j; + for (j = 0; j < XVECLEN (x, i); j++) + { + int tmp_class = may_trap_exp (XVECEXP (x, i, j), is_store); + insn_class = WORST_CLASS (insn_class, tmp_class); + if (insn_class == TRAP_RISKY || insn_class == IRISKY) + break; + } + } + if (insn_class == TRAP_RISKY || insn_class == IRISKY) + break; + } + return insn_class; + } +} + +/* Classifies insn for the purpose of verifying that it can be + moved speculatively, by examining it's patterns, returning: + TRAP_RISKY: store, or risky non-load insn (e.g. division by variable). + TRAP_FREE: non-load insn. + IFREE: load from a globaly safe location. + IRISKY: volatile load. + PFREE_CANDIDATE, PRISKY_CANDIDATE: load that need to be checked for + being either PFREE or PRISKY. */ + +int +haifa_classify_insn (insn) + rtx insn; +{ + rtx pat = PATTERN (insn); + int tmp_class = TRAP_FREE; + int insn_class = TRAP_FREE; + enum rtx_code code; + + if (GET_CODE (pat) == PARALLEL) + { + int i, len = XVECLEN (pat, 0); + + for (i = len - 1; i >= 0; i--) + { + code = GET_CODE (XVECEXP (pat, 0, i)); + switch (code) + { + case CLOBBER: + /* Test if it is a 'store'. */ + tmp_class = may_trap_exp (XEXP (XVECEXP (pat, 0, i), 0), 1); + break; + case SET: + /* Test if it is a store. */ + tmp_class = may_trap_exp (SET_DEST (XVECEXP (pat, 0, i)), 1); + if (tmp_class == TRAP_RISKY) + break; + /* Test if it is a load. */ + tmp_class + = WORST_CLASS (tmp_class, + may_trap_exp (SET_SRC (XVECEXP (pat, 0, i)), + 0)); + break; + case COND_EXEC: + case TRAP_IF: + tmp_class = TRAP_RISKY; + break; + default: + ; + } + insn_class = WORST_CLASS (insn_class, tmp_class); + if (insn_class == TRAP_RISKY || insn_class == IRISKY) + break; + } + } + else + { + code = GET_CODE (pat); + switch (code) + { + case CLOBBER: + /* Test if it is a 'store'. */ + tmp_class = may_trap_exp (XEXP (pat, 0), 1); + break; + case SET: + /* Test if it is a store. */ + tmp_class = may_trap_exp (SET_DEST (pat), 1); + if (tmp_class == TRAP_RISKY) + break; + /* Test if it is a load. */ + tmp_class = + WORST_CLASS (tmp_class, + may_trap_exp (SET_SRC (pat), 0)); + break; + case COND_EXEC: + case TRAP_IF: + tmp_class = TRAP_RISKY; + break; + default:; + } + insn_class = tmp_class; + } + + return insn_class; +} + /* Forward declarations. */ /* The scheduler using only DFA description should never use the diff --git a/gcc/sched-deps.c b/gcc/sched-deps.c index fc9d4d857db8eac0b03c46176ca71db3b3f59fd5..b3c619df51d613172ef54144daec6040b4fb40c9 100644 --- a/gcc/sched-deps.c +++ b/gcc/sched-deps.c @@ -173,10 +173,11 @@ conditions_mutex_p (cond1, cond2) } /* Add ELEM wrapped in an INSN_LIST with reg note kind DEP_TYPE to the - LOG_LINKS of INSN, if not already there. DEP_TYPE indicates the type - of dependence that this link represents. */ + LOG_LINKS of INSN, if not already there. DEP_TYPE indicates the + type of dependence that this link represents. The function returns + nonzero if a new entry has been added to insn's LOG_LINK. */ -void +int add_dependence (insn, elem, dep_type) rtx insn; rtx elem; @@ -188,13 +189,13 @@ add_dependence (insn, elem, dep_type) /* Don't depend an insn on itself. */ if (insn == elem) - return; + return 0; /* We can get a dependency on deleted insns due to optimizations in the register allocation and reloading or due to splitting. Any such dependency is useless and can be ignored. */ if (GET_CODE (elem) == NOTE) - return; + return 0; /* flow.c doesn't handle conditional lifetimes entirely correctly; calls mess up the conditional lifetimes. */ @@ -213,7 +214,7 @@ add_dependence (insn, elem, dep_type) /* Make sure second instruction doesn't affect condition of first instruction if switched. */ && !modified_in_p (cond2, insn)) - return; + return 0; } present_p = 1; @@ -227,7 +228,7 @@ add_dependence (insn, elem, dep_type) elem is a CALL is still required. */ if (GET_CODE (insn) == CALL_INSN && (INSN_BB (elem) != INSN_BB (insn))) - return; + return 0; #endif /* If we already have a dependency for ELEM, then we do not need to @@ -251,7 +252,7 @@ add_dependence (insn, elem, dep_type) else present_p = 0; if (present_p && (int) dep_type >= (int) present_dep_type) - return; + return 0; } #endif @@ -276,7 +277,7 @@ add_dependence (insn, elem, dep_type) abort (); } #endif - + /* If this is a more restrictive type of dependence than the existing one, then change the existing dependence to this type. */ if ((int) dep_type < (int) REG_NOTE_KIND (link)) @@ -298,8 +299,8 @@ add_dependence (insn, elem, dep_type) INSN_LUID (elem)); } #endif - return; - } + return 0; + } /* Might want to check one level of transitivity to save conses. */ link = alloc_INSN_LIST (elem, LOG_LINKS (insn)); @@ -321,6 +322,7 @@ add_dependence (insn, elem, dep_type) SET_BIT (output_dependency_cache[INSN_LUID (insn)], INSN_LUID (elem)); } #endif + return 1; } /* A convenience wrapper to operate on an entire list. */ @@ -1310,6 +1312,46 @@ sched_analyze (deps, head, tail) abort (); } + +/* The following function adds forward dependence (FROM, TO) with + given DEP_TYPE. The forward dependence should be not exist before. */ + +void +add_forward_dependence (from, to, dep_type) + rtx from; + rtx to; + enum reg_note dep_type; +{ + rtx new_link; + +#ifdef ENABLE_CHECKING + /* If add_dependence is working properly there should never + be notes, deleted insns or duplicates in the backward + links. Thus we need not check for them here. + + However, if we have enabled checking we might as well go + ahead and verify that add_dependence worked properly. */ + if (GET_CODE (from) == NOTE + || INSN_DELETED_P (from) + || (forward_dependency_cache != NULL + && TEST_BIT (forward_dependency_cache[INSN_LUID (from)], + INSN_LUID (to))) + || (forward_dependency_cache == NULL + && find_insn_list (to, INSN_DEPEND (from)))) + abort (); + if (forward_dependency_cache != NULL) + SET_BIT (forward_dependency_cache[INSN_LUID (from)], + INSN_LUID (to)); +#endif + + new_link = alloc_INSN_LIST (to, INSN_DEPEND (from)); + + PUT_REG_NOTE_KIND (new_link, dep_type); + + INSN_DEPEND (from) = new_link; + INSN_DEP_COUNT (to) += 1; +} + /* Examine insns in the range [ HEAD, TAIL ] and Use the backward dependences from LOG_LINKS to build forward dependences in INSN_DEPEND. */ @@ -1320,7 +1362,6 @@ compute_forward_dependences (head, tail) { rtx insn, link; rtx next_tail; - enum reg_note dep_type; next_tail = NEXT_INSN (tail); for (insn = head; insn != next_tail; insn = NEXT_INSN (insn)) @@ -1329,41 +1370,7 @@ compute_forward_dependences (head, tail) continue; for (link = LOG_LINKS (insn); link; link = XEXP (link, 1)) - { - rtx x = XEXP (link, 0); - rtx new_link; - - if (x != XEXP (link, 0)) - continue; - -#ifdef ENABLE_CHECKING - /* If add_dependence is working properly there should never - be notes, deleted insns or duplicates in the backward - links. Thus we need not check for them here. - - However, if we have enabled checking we might as well go - ahead and verify that add_dependence worked properly. */ - if (GET_CODE (x) == NOTE - || INSN_DELETED_P (x) - || (forward_dependency_cache != NULL - && TEST_BIT (forward_dependency_cache[INSN_LUID (x)], - INSN_LUID (insn))) - || (forward_dependency_cache == NULL - && find_insn_list (insn, INSN_DEPEND (x)))) - abort (); - if (forward_dependency_cache != NULL) - SET_BIT (forward_dependency_cache[INSN_LUID (x)], - INSN_LUID (insn)); -#endif - - new_link = alloc_INSN_LIST (insn, INSN_DEPEND (x)); - - dep_type = REG_NOTE_KIND (link); - PUT_REG_NOTE_KIND (new_link, dep_type); - - INSN_DEPEND (x) = new_link; - INSN_DEP_COUNT (insn) += 1; - } + add_forward_dependence (XEXP (link, 0), insn, REG_NOTE_KIND (link)); } } diff --git a/gcc/sched-ebb.c b/gcc/sched-ebb.c index eefee1c168a97cef68ca0fad4bccc67e7ada1da5..3d25d80da374130e821702602af1accb580b71d5 100644 --- a/gcc/sched-ebb.c +++ b/gcc/sched-ebb.c @@ -56,6 +56,9 @@ static const char *ebb_print_insn PARAMS ((rtx, int)); static int rank PARAMS ((rtx, rtx)); static int contributes_to_priority PARAMS ((rtx, rtx)); static void compute_jump_reg_dependencies PARAMS ((rtx, regset)); +static basic_block earliest_block_with_similiar_load PARAMS ((basic_block, + rtx)); +static void add_deps_for_risky_insns PARAMS ((rtx, rtx)); static basic_block schedule_ebb PARAMS ((rtx, rtx)); static basic_block fix_basic_block_boundaries PARAMS ((basic_block, basic_block, rtx, rtx)); static void add_missing_bbs PARAMS ((rtx, basic_block, basic_block)); @@ -339,6 +342,137 @@ fix_basic_block_boundaries (bb, last, head, tail) return bb->prev_bb; } +/* Returns the earliest block in EBB currently being processed where a + "similar load" 'insn2' is found, and hence LOAD_INSN can move + speculatively into the found block. All the following must hold: + + (1) both loads have 1 base register (PFREE_CANDIDATEs). + (2) load_insn and load2 have a def-use dependence upon + the same insn 'insn1'. + + From all these we can conclude that the two loads access memory + addresses that differ at most by a constant, and hence if moving + load_insn would cause an exception, it would have been caused by + load2 anyhow. + + The function uses list (given by LAST_BLOCK) of already processed + blocks in EBB. The list is formed in `add_deps_for_risky_insns'. */ + +static basic_block +earliest_block_with_similiar_load (last_block, load_insn) + basic_block last_block; + rtx load_insn; +{ + rtx back_link; + basic_block bb, earliest_block = NULL; + + for (back_link = LOG_LINKS (load_insn); + back_link; + back_link = XEXP (back_link, 1)) + { + rtx insn1 = XEXP (back_link, 0); + + if (GET_MODE (back_link) == VOIDmode) + { + /* Found a DEF-USE dependence (insn1, load_insn). */ + rtx fore_link; + + for (fore_link = INSN_DEPEND (insn1); + fore_link; + fore_link = XEXP (fore_link, 1)) + { + rtx insn2 = XEXP (fore_link, 0); + basic_block insn2_block = BLOCK_FOR_INSN (insn2); + + if (GET_MODE (fore_link) == VOIDmode) + { + if (earliest_block != NULL + && earliest_block->index < insn2_block->index) + continue; + + /* Found a DEF-USE dependence (insn1, insn2). */ + if (haifa_classify_insn (insn2) != PFREE_CANDIDATE) + /* insn2 not guaranteed to be a 1 base reg load. */ + continue; + + for (bb = last_block; bb; bb = bb->aux) + if (insn2_block == bb) + break; + + if (!bb) + /* insn2 is the similar load. */ + earliest_block = insn2_block; + } + } + } + } + + return earliest_block; +} + +/* The following function adds dependecies between jumps and risky + insns in given ebb. */ + +static void +add_deps_for_risky_insns (head, tail) + rtx head, tail; +{ + rtx insn, prev; + int class; + rtx last_jump = NULL_RTX; + rtx next_tail = NEXT_INSN (tail); + basic_block last_block = NULL, bb; + + for (insn = head; insn != next_tail; insn = NEXT_INSN (insn)) + if (GET_CODE (insn) == JUMP_INSN) + { + bb = BLOCK_FOR_INSN (insn); + bb->aux = last_block; + last_block = bb; + last_jump = insn; + } + else if (INSN_P (insn) && last_jump != NULL_RTX) + { + class = haifa_classify_insn (insn); + prev = last_jump; + switch (class) + { + case PFREE_CANDIDATE: + if (flag_schedule_speculative_load) + { + bb = earliest_block_with_similiar_load (last_block, insn); + if (bb) + bb = bb->aux; + if (!bb) + break; + prev = bb->end; + } + /* FALLTHRU */ + case TRAP_RISKY: + case IRISKY: + case PRISKY_CANDIDATE: + /* ??? We could implement better checking PRISKY_CANDIATEs + analogous to sched-rgn.c. */ + /* We can not change the mode of the backward + dependency because REG_DEP_ANTI has the lowest + rank. */ + if (add_dependence (insn, prev, REG_DEP_ANTI)) + add_forward_dependence (prev, insn, REG_DEP_ANTI); + break; + + default: + break; + } + } + /* Maintain the invariant that bb->aux is clear after use. */ + while (last_block) + { + bb = last_block->aux; + last_block->aux = NULL; + last_block = bb; + } +} + /* Schedule a single extended basic block, defined by the boundaries HEAD and TAIL. */ @@ -365,6 +499,8 @@ schedule_ebb (head, tail) /* Compute INSN_DEPEND. */ compute_forward_dependences (head, tail); + add_deps_for_risky_insns (head, tail); + if (targetm.sched.dependencies_evaluation_hook) targetm.sched.dependencies_evaluation_hook (head, tail); diff --git a/gcc/sched-int.h b/gcc/sched-int.h index 1b196562b184f772c0db6e5dad5943b2ba883451..2041a2f5e3910dbf50544a6a93cc5d1b93bb2140 100644 --- a/gcc/sched-int.h +++ b/gcc/sched-int.h @@ -258,6 +258,76 @@ extern struct haifa_insn_data *h_i_d; extern FILE *sched_dump; extern int sched_verbose; +/* Exception Free Loads: + + We define five classes of speculative loads: IFREE, IRISKY, + PFREE, PRISKY, and MFREE. + + IFREE loads are loads that are proved to be exception-free, just + by examining the load insn. Examples for such loads are loads + from TOC and loads of global data. + + IRISKY loads are loads that are proved to be exception-risky, + just by examining the load insn. Examples for such loads are + volatile loads and loads from shared memory. + + PFREE loads are loads for which we can prove, by examining other + insns, that they are exception-free. Currently, this class consists + of loads for which we are able to find a "similar load", either in + the target block, or, if only one split-block exists, in that split + block. Load2 is similar to load1 if both have same single base + register. We identify only part of the similar loads, by finding + an insn upon which both load1 and load2 have a DEF-USE dependence. + + PRISKY loads are loads for which we can prove, by examining other + insns, that they are exception-risky. Currently we have two proofs for + such loads. The first proof detects loads that are probably guarded by a + test on the memory address. This proof is based on the + backward and forward data dependence information for the region. + Let load-insn be the examined load. + Load-insn is PRISKY iff ALL the following hold: + + - insn1 is not in the same block as load-insn + - there is a DEF-USE dependence chain (insn1, ..., load-insn) + - test-insn is either a compare or a branch, not in the same block + as load-insn + - load-insn is reachable from test-insn + - there is a DEF-USE dependence chain (insn1, ..., test-insn) + + This proof might fail when the compare and the load are fed + by an insn not in the region. To solve this, we will add to this + group all loads that have no input DEF-USE dependence. + + The second proof detects loads that are directly or indirectly + fed by a speculative load. This proof is affected by the + scheduling process. We will use the flag fed_by_spec_load. + Initially, all insns have this flag reset. After a speculative + motion of an insn, if insn is either a load, or marked as + fed_by_spec_load, we will also mark as fed_by_spec_load every + insn1 for which a DEF-USE dependence (insn, insn1) exists. A + load which is fed_by_spec_load is also PRISKY. + + MFREE (maybe-free) loads are all the remaining loads. They may be + exception-free, but we cannot prove it. + + Now, all loads in IFREE and PFREE classes are considered + exception-free, while all loads in IRISKY and PRISKY classes are + considered exception-risky. As for loads in the MFREE class, + these are considered either exception-free or exception-risky, + depending on whether we are pessimistic or optimistic. We have + to take the pessimistic approach to assure the safety of + speculative scheduling, but we can take the optimistic approach + by invoking the -fsched_spec_load_dangerous option. */ + +enum INSN_TRAP_CLASS +{ + TRAP_FREE = 0, IFREE = 1, PFREE_CANDIDATE = 2, + PRISKY_CANDIDATE = 3, IRISKY = 4, TRAP_RISKY = 5 +}; + +#define WORST_CLASS(class1, class2) \ +((class1 > class2) ? class1 : class2) + #ifndef __GNUC__ #define __inline #endif @@ -278,7 +348,7 @@ extern void visualize_alloc PARAMS ((void)); extern void visualize_free PARAMS ((void)); /* Functions in sched-deps.c. */ -extern void add_dependence PARAMS ((rtx, rtx, enum reg_note)); +extern int add_dependence PARAMS ((rtx, rtx, enum reg_note)); extern void add_insn_mem_dependence PARAMS ((struct deps *, rtx *, rtx *, rtx, rtx)); extern void sched_analyze PARAMS ((struct deps *, rtx, rtx)); @@ -286,12 +356,14 @@ extern void init_deps PARAMS ((struct deps *)); extern void free_deps PARAMS ((struct deps *)); extern void init_deps_global PARAMS ((void)); extern void finish_deps_global PARAMS ((void)); +extern void add_forward_dependence PARAMS ((rtx, rtx, enum reg_note)); extern void compute_forward_dependences PARAMS ((rtx, rtx)); extern rtx find_insn_list PARAMS ((rtx, rtx)); extern void init_dependency_caches PARAMS ((int)); extern void free_dependency_caches PARAMS ((void)); /* Functions in haifa-sched.c. */ +extern int haifa_classify_insn PARAMS ((rtx)); extern void get_block_head_tail PARAMS ((int, rtx *, rtx *)); extern int no_real_insns_p PARAMS ((rtx, rtx)); diff --git a/gcc/sched-rgn.c b/gcc/sched-rgn.c index 36a53f73c26162bc35f7f299dcfb5395b59791ba..c7e7f808ee93f284885e02aa152118000fb39016 100644 --- a/gcc/sched-rgn.c +++ b/gcc/sched-rgn.c @@ -288,8 +288,6 @@ static void set_spec_fed PARAMS ((rtx)); static int is_pfree PARAMS ((rtx, int, int)); static int find_conditional_protection PARAMS ((rtx, int)); static int is_conditionally_protected PARAMS ((rtx, int, int)); -static int may_trap_exp PARAMS ((rtx, int)); -static int haifa_classify_insn PARAMS ((rtx)); static int is_prisky PARAMS ((rtx, int, int)); static int is_exception_free PARAMS ((rtx, int, int)); @@ -1490,76 +1488,6 @@ update_live (insn, src) } } -/* Exception Free Loads: - - We define five classes of speculative loads: IFREE, IRISKY, - PFREE, PRISKY, and MFREE. - - IFREE loads are loads that are proved to be exception-free, just - by examining the load insn. Examples for such loads are loads - from TOC and loads of global data. - - IRISKY loads are loads that are proved to be exception-risky, - just by examining the load insn. Examples for such loads are - volatile loads and loads from shared memory. - - PFREE loads are loads for which we can prove, by examining other - insns, that they are exception-free. Currently, this class consists - of loads for which we are able to find a "similar load", either in - the target block, or, if only one split-block exists, in that split - block. Load2 is similar to load1 if both have same single base - register. We identify only part of the similar loads, by finding - an insn upon which both load1 and load2 have a DEF-USE dependence. - - PRISKY loads are loads for which we can prove, by examining other - insns, that they are exception-risky. Currently we have two proofs for - such loads. The first proof detects loads that are probably guarded by a - test on the memory address. This proof is based on the - backward and forward data dependence information for the region. - Let load-insn be the examined load. - Load-insn is PRISKY iff ALL the following hold: - - - insn1 is not in the same block as load-insn - - there is a DEF-USE dependence chain (insn1, ..., load-insn) - - test-insn is either a compare or a branch, not in the same block - as load-insn - - load-insn is reachable from test-insn - - there is a DEF-USE dependence chain (insn1, ..., test-insn) - - This proof might fail when the compare and the load are fed - by an insn not in the region. To solve this, we will add to this - group all loads that have no input DEF-USE dependence. - - The second proof detects loads that are directly or indirectly - fed by a speculative load. This proof is affected by the - scheduling process. We will use the flag fed_by_spec_load. - Initially, all insns have this flag reset. After a speculative - motion of an insn, if insn is either a load, or marked as - fed_by_spec_load, we will also mark as fed_by_spec_load every - insn1 for which a DEF-USE dependence (insn, insn1) exists. A - load which is fed_by_spec_load is also PRISKY. - - MFREE (maybe-free) loads are all the remaining loads. They may be - exception-free, but we cannot prove it. - - Now, all loads in IFREE and PFREE classes are considered - exception-free, while all loads in IRISKY and PRISKY classes are - considered exception-risky. As for loads in the MFREE class, - these are considered either exception-free or exception-risky, - depending on whether we are pessimistic or optimistic. We have - to take the pessimistic approach to assure the safety of - speculative scheduling, but we can take the optimistic approach - by invoking the -fsched_spec_load_dangerous option. */ - -enum INSN_TRAP_CLASS -{ - TRAP_FREE = 0, IFREE = 1, PFREE_CANDIDATE = 2, - PRISKY_CANDIDATE = 3, IRISKY = 4, TRAP_RISKY = 5 -}; - -#define WORST_CLASS(class1, class2) \ -((class1 > class2) ? class1 : class2) - /* Nonzero if block bb_to is equal to, or reachable from block bb_from. */ #define IS_REACHABLE(bb_from, bb_to) \ (bb_from == bb_to \ @@ -1567,14 +1495,6 @@ enum INSN_TRAP_CLASS || (TEST_BIT (ancestor_edges[bb_to], \ EDGE_TO_BIT (IN_EDGES (BB_TO_BLOCK (bb_from)))))) -/* Nonzero iff the address is comprised from at most 1 register. */ -#define CONST_BASED_ADDRESS_P(x) \ - (GET_CODE (x) == REG \ - || ((GET_CODE (x) == PLUS || GET_CODE (x) == MINUS \ - || (GET_CODE (x) == LO_SUM)) \ - && (CONSTANT_P (XEXP (x, 0)) \ - || CONSTANT_P (XEXP (x, 1))))) - /* Turns on the fed_by_spec_load flag for insns fed by load_insn. */ static void @@ -1729,160 +1649,6 @@ is_pfree (load_insn, bb_src, bb_trg) return 0; } /* is_pfree */ -/* Returns a class that insn with GET_DEST(insn)=x may belong to, - as found by analyzing insn's expression. */ - -static int -may_trap_exp (x, is_store) - rtx x; - int is_store; -{ - enum rtx_code code; - - if (x == 0) - return TRAP_FREE; - code = GET_CODE (x); - if (is_store) - { - if (code == MEM && may_trap_p (x)) - return TRAP_RISKY; - else - return TRAP_FREE; - } - if (code == MEM) - { - /* The insn uses memory: a volatile load. */ - if (MEM_VOLATILE_P (x)) - return IRISKY; - /* An exception-free load. */ - if (!may_trap_p (x)) - return IFREE; - /* A load with 1 base register, to be further checked. */ - if (CONST_BASED_ADDRESS_P (XEXP (x, 0))) - return PFREE_CANDIDATE; - /* No info on the load, to be further checked. */ - return PRISKY_CANDIDATE; - } - else - { - const char *fmt; - int i, insn_class = TRAP_FREE; - - /* Neither store nor load, check if it may cause a trap. */ - if (may_trap_p (x)) - return TRAP_RISKY; - /* Recursive step: walk the insn... */ - fmt = GET_RTX_FORMAT (code); - for (i = GET_RTX_LENGTH (code) - 1; i >= 0; i--) - { - if (fmt[i] == 'e') - { - int tmp_class = may_trap_exp (XEXP (x, i), is_store); - insn_class = WORST_CLASS (insn_class, tmp_class); - } - else if (fmt[i] == 'E') - { - int j; - for (j = 0; j < XVECLEN (x, i); j++) - { - int tmp_class = may_trap_exp (XVECEXP (x, i, j), is_store); - insn_class = WORST_CLASS (insn_class, tmp_class); - if (insn_class == TRAP_RISKY || insn_class == IRISKY) - break; - } - } - if (insn_class == TRAP_RISKY || insn_class == IRISKY) - break; - } - return insn_class; - } -} - -/* Classifies insn for the purpose of verifying that it can be - moved speculatively, by examining it's patterns, returning: - TRAP_RISKY: store, or risky non-load insn (e.g. division by variable). - TRAP_FREE: non-load insn. - IFREE: load from a globaly safe location. - IRISKY: volatile load. - PFREE_CANDIDATE, PRISKY_CANDIDATE: load that need to be checked for - being either PFREE or PRISKY. */ - -static int -haifa_classify_insn (insn) - rtx insn; -{ - rtx pat = PATTERN (insn); - int tmp_class = TRAP_FREE; - int insn_class = TRAP_FREE; - enum rtx_code code; - - if (GET_CODE (pat) == PARALLEL) - { - int i, len = XVECLEN (pat, 0); - - for (i = len - 1; i >= 0; i--) - { - code = GET_CODE (XVECEXP (pat, 0, i)); - switch (code) - { - case CLOBBER: - /* Test if it is a 'store'. */ - tmp_class = may_trap_exp (XEXP (XVECEXP (pat, 0, i), 0), 1); - break; - case SET: - /* Test if it is a store. */ - tmp_class = may_trap_exp (SET_DEST (XVECEXP (pat, 0, i)), 1); - if (tmp_class == TRAP_RISKY) - break; - /* Test if it is a load. */ - tmp_class - = WORST_CLASS (tmp_class, - may_trap_exp (SET_SRC (XVECEXP (pat, 0, i)), - 0)); - break; - case COND_EXEC: - case TRAP_IF: - tmp_class = TRAP_RISKY; - break; - default: - ; - } - insn_class = WORST_CLASS (insn_class, tmp_class); - if (insn_class == TRAP_RISKY || insn_class == IRISKY) - break; - } - } - else - { - code = GET_CODE (pat); - switch (code) - { - case CLOBBER: - /* Test if it is a 'store'. */ - tmp_class = may_trap_exp (XEXP (pat, 0), 1); - break; - case SET: - /* Test if it is a store. */ - tmp_class = may_trap_exp (SET_DEST (pat), 1); - if (tmp_class == TRAP_RISKY) - break; - /* Test if it is a load. */ - tmp_class = - WORST_CLASS (tmp_class, - may_trap_exp (SET_SRC (pat), 0)); - break; - case COND_EXEC: - case TRAP_IF: - tmp_class = TRAP_RISKY; - break; - default:; - } - insn_class = tmp_class; - } - - return insn_class; -} - /* Return 1 if load_insn is prisky (i.e. if load_insn is fed by a load moved speculatively, or if load_insn is protected by a compare on load_insn's address). */