Commit 9091e8d1 authored by Tom Lane's avatar Tom Lane

Add the ability to extract OR indexscan conditions from OR-of-AND

join conditions in which each OR subclause includes a constraint on
the same relation.  This implements the other useful side-effect of
conversion to CNF format, without its unpleasant side-effects.  As
per pghackers discussion of a few weeks ago.
parent bf488a68
...@@ -15,7 +15,7 @@ ...@@ -15,7 +15,7 @@
* Portions Copyright (c) 1994, Regents of the University of California * Portions Copyright (c) 1994, Regents of the University of California
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/nodes/copyfuncs.c,v 1.272 2004/01/04 03:51:52 tgl Exp $ * $PostgreSQL: pgsql/src/backend/nodes/copyfuncs.c,v 1.273 2004/01/05 05:07:35 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -1168,8 +1168,9 @@ _copyRestrictInfo(RestrictInfo *from) ...@@ -1168,8 +1168,9 @@ _copyRestrictInfo(RestrictInfo *from)
RestrictInfo *newnode = makeNode(RestrictInfo); RestrictInfo *newnode = makeNode(RestrictInfo);
COPY_NODE_FIELD(clause); COPY_NODE_FIELD(clause);
COPY_SCALAR_FIELD(ispusheddown); COPY_SCALAR_FIELD(is_pushed_down);
COPY_SCALAR_FIELD(canjoin); COPY_SCALAR_FIELD(valid_everywhere);
COPY_SCALAR_FIELD(can_join);
COPY_BITMAPSET_FIELD(clause_relids); COPY_BITMAPSET_FIELD(clause_relids);
COPY_BITMAPSET_FIELD(left_relids); COPY_BITMAPSET_FIELD(left_relids);
COPY_BITMAPSET_FIELD(right_relids); COPY_BITMAPSET_FIELD(right_relids);
......
...@@ -18,7 +18,7 @@ ...@@ -18,7 +18,7 @@
* Portions Copyright (c) 1994, Regents of the University of California * Portions Copyright (c) 1994, Regents of the University of California
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/nodes/equalfuncs.c,v 1.211 2003/12/30 23:53:14 tgl Exp $ * $PostgreSQL: pgsql/src/backend/nodes/equalfuncs.c,v 1.212 2004/01/05 05:07:35 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -560,7 +560,8 @@ static bool ...@@ -560,7 +560,8 @@ static bool
_equalRestrictInfo(RestrictInfo *a, RestrictInfo *b) _equalRestrictInfo(RestrictInfo *a, RestrictInfo *b)
{ {
COMPARE_NODE_FIELD(clause); COMPARE_NODE_FIELD(clause);
COMPARE_SCALAR_FIELD(ispusheddown); COMPARE_SCALAR_FIELD(is_pushed_down);
COMPARE_SCALAR_FIELD(valid_everywhere);
/* /*
* We ignore all the remaining fields, since they may not be set yet, * We ignore all the remaining fields, since they may not be set yet,
......
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
* *
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/nodes/outfuncs.c,v 1.225 2004/01/04 03:51:52 tgl Exp $ * $PostgreSQL: pgsql/src/backend/nodes/outfuncs.c,v 1.226 2004/01/05 05:07:35 tgl Exp $
* *
* NOTES * NOTES
* Every node type that can appear in stored rules' parsetrees *must* * Every node type that can appear in stored rules' parsetrees *must*
...@@ -971,7 +971,7 @@ _outIndexPath(StringInfo str, IndexPath *node) ...@@ -971,7 +971,7 @@ _outIndexPath(StringInfo str, IndexPath *node)
WRITE_NODE_FIELD(indexqual); WRITE_NODE_FIELD(indexqual);
WRITE_NODE_FIELD(indexjoinclauses); WRITE_NODE_FIELD(indexjoinclauses);
WRITE_ENUM_FIELD(indexscandir, ScanDirection); WRITE_ENUM_FIELD(indexscandir, ScanDirection);
WRITE_FLOAT_FIELD(rows, "%.2f"); WRITE_FLOAT_FIELD(rows, "%.0f");
} }
static void static void
...@@ -1073,8 +1073,9 @@ _outRestrictInfo(StringInfo str, RestrictInfo *node) ...@@ -1073,8 +1073,9 @@ _outRestrictInfo(StringInfo str, RestrictInfo *node)
/* NB: this isn't a complete set of fields */ /* NB: this isn't a complete set of fields */
WRITE_NODE_FIELD(clause); WRITE_NODE_FIELD(clause);
WRITE_BOOL_FIELD(ispusheddown); WRITE_BOOL_FIELD(is_pushed_down);
WRITE_BOOL_FIELD(canjoin); WRITE_BOOL_FIELD(valid_everywhere);
WRITE_BOOL_FIELD(can_join);
WRITE_BITMAPSET_FIELD(clause_relids); WRITE_BITMAPSET_FIELD(clause_relids);
WRITE_BITMAPSET_FIELD(left_relids); WRITE_BITMAPSET_FIELD(left_relids);
WRITE_BITMAPSET_FIELD(right_relids); WRITE_BITMAPSET_FIELD(right_relids);
......
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
* *
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/optimizer/path/allpaths.c,v 1.110 2003/12/17 17:07:48 tgl Exp $ * $PostgreSQL: pgsql/src/backend/optimizer/path/allpaths.c,v 1.111 2004/01/05 05:07:35 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -151,6 +151,17 @@ set_plain_rel_pathlist(Query *root, RelOptInfo *rel, RangeTblEntry *rte) ...@@ -151,6 +151,17 @@ set_plain_rel_pathlist(Query *root, RelOptInfo *rel, RangeTblEntry *rte)
/* Mark rel with estimated output rows, width, etc */ /* Mark rel with estimated output rows, width, etc */
set_baserel_size_estimates(root, rel); set_baserel_size_estimates(root, rel);
/* Test any partial indexes of rel for applicability */
check_partial_indexes(root, rel);
/*
* Check to see if we can extract any restriction conditions from
* join quals that are OR-of-AND structures. If so, add them to the
* rel's restriction list, and recompute the size estimates.
*/
if (create_or_index_quals(root, rel))
set_baserel_size_estimates(root, rel);
/* /*
* Generate paths and add them to the rel's pathlist. * Generate paths and add them to the rel's pathlist.
* *
...@@ -167,8 +178,6 @@ set_plain_rel_pathlist(Query *root, RelOptInfo *rel, RangeTblEntry *rte) ...@@ -167,8 +178,6 @@ set_plain_rel_pathlist(Query *root, RelOptInfo *rel, RangeTblEntry *rte)
/* Consider index paths for both simple and OR index clauses */ /* Consider index paths for both simple and OR index clauses */
create_index_paths(root, rel); create_index_paths(root, rel);
/* create_index_paths must be done before create_or_index_paths */
create_or_index_paths(root, rel); create_or_index_paths(root, rel);
/* Now find the cheapest of the paths for this rel */ /* Now find the cheapest of the paths for this rel */
......
This diff is collapsed.
...@@ -9,7 +9,7 @@ ...@@ -9,7 +9,7 @@
* *
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/optimizer/path/indxpath.c,v 1.153 2004/01/04 03:51:52 tgl Exp $ * $PostgreSQL: pgsql/src/backend/optimizer/path/indxpath.c,v 1.154 2004/01/05 05:07:35 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -63,8 +63,7 @@ static bool match_join_clause_to_indexcol(RelOptInfo *rel, IndexOptInfo *index, ...@@ -63,8 +63,7 @@ static bool match_join_clause_to_indexcol(RelOptInfo *rel, IndexOptInfo *index,
RestrictInfo *rinfo); RestrictInfo *rinfo);
static Oid indexable_operator(Expr *clause, Oid opclass, static Oid indexable_operator(Expr *clause, Oid opclass,
bool indexkey_on_left); bool indexkey_on_left);
static bool pred_test(List *predicate_list, List *restrictinfo_list, static bool pred_test(List *predicate_list, List *restrictinfo_list);
List *joininfo_list);
static bool pred_test_restrict_list(Expr *predicate, List *restrictinfo_list); static bool pred_test_restrict_list(Expr *predicate, List *restrictinfo_list);
static bool pred_test_recurse_clause(Expr *predicate, Node *clause); static bool pred_test_recurse_clause(Expr *predicate, Node *clause);
static bool pred_test_recurse_pred(Expr *predicate, Node *clause); static bool pred_test_recurse_pred(Expr *predicate, Node *clause);
...@@ -114,12 +113,12 @@ static Const *string_to_const(const char *str, Oid datatype); ...@@ -114,12 +113,12 @@ static Const *string_to_const(const char *str, Oid datatype);
* and avoid repeated computation. * and avoid repeated computation.
* *
* 'rel' is the relation for which we want to generate index paths * 'rel' is the relation for which we want to generate index paths
*
* Note: check_partial_indexes() must have been run previously.
*/ */
void void
create_index_paths(Query *root, RelOptInfo *rel) create_index_paths(Query *root, RelOptInfo *rel)
{ {
List *restrictinfo_list = rel->baserestrictinfo;
List *joininfo_list = rel->joininfo;
Relids all_join_outerrelids = NULL; Relids all_join_outerrelids = NULL;
List *ilist; List *ilist;
...@@ -132,16 +131,9 @@ create_index_paths(Query *root, RelOptInfo *rel) ...@@ -132,16 +131,9 @@ create_index_paths(Query *root, RelOptInfo *rel)
bool index_is_ordered; bool index_is_ordered;
Relids join_outerrelids; Relids join_outerrelids;
/* /* Ignore partial indexes that do not match the query */
* If this is a partial index, we can only use it if it passes the if (index->indpred != NIL && !index->predOK)
* predicate test. continue;
*/
if (index->indpred != NIL)
{
if (!pred_test(index->indpred, restrictinfo_list, joininfo_list))
continue;
index->predOK = true; /* set flag for orindxpaths.c */
}
/* /*
* 1. Match the index against non-OR restriction clauses. * 1. Match the index against non-OR restriction clauses.
...@@ -336,7 +328,7 @@ group_clauses_by_indexkey_for_join(Query *root, ...@@ -336,7 +328,7 @@ group_clauses_by_indexkey_for_join(Query *root,
RestrictInfo *rinfo = (RestrictInfo *) lfirst(i); RestrictInfo *rinfo = (RestrictInfo *) lfirst(i);
/* Can't use pushed-down clauses in outer join */ /* Can't use pushed-down clauses in outer join */
if (isouterjoin && rinfo->ispusheddown) if (isouterjoin && rinfo->is_pushed_down)
continue; continue;
if (match_clause_to_indexcol(rel, if (match_clause_to_indexcol(rel,
...@@ -365,7 +357,7 @@ group_clauses_by_indexkey_for_join(Query *root, ...@@ -365,7 +357,7 @@ group_clauses_by_indexkey_for_join(Query *root,
RestrictInfo *rinfo = (RestrictInfo *) lfirst(j); RestrictInfo *rinfo = (RestrictInfo *) lfirst(j);
/* Can't use pushed-down clauses in outer join */ /* Can't use pushed-down clauses in outer join */
if (isouterjoin && rinfo->ispusheddown) if (isouterjoin && rinfo->is_pushed_down)
continue; continue;
if (match_join_clause_to_indexcol(rel, if (match_join_clause_to_indexcol(rel,
...@@ -736,6 +728,32 @@ indexable_operator(Expr *clause, Oid opclass, bool indexkey_on_left) ...@@ -736,6 +728,32 @@ indexable_operator(Expr *clause, Oid opclass, bool indexkey_on_left)
* ---- ROUTINES TO DO PARTIAL INDEX PREDICATE TESTS ---- * ---- ROUTINES TO DO PARTIAL INDEX PREDICATE TESTS ----
****************************************************************************/ ****************************************************************************/
/*
* check_partial_indexes
* Check each partial index of the relation, and mark it predOK or not
* depending on whether the predicate is satisfied for this query.
*/
void
check_partial_indexes(Query *root, RelOptInfo *rel)
{
List *restrictinfo_list = rel->baserestrictinfo;
List *ilist;
foreach(ilist, rel->indexlist)
{
IndexOptInfo *index = (IndexOptInfo *) lfirst(ilist);
/*
* If this is a partial index, we can only use it if it passes the
* predicate test.
*/
if (index->indpred == NIL)
continue; /* ignore non-partial indexes */
index->predOK = pred_test(index->indpred, restrictinfo_list);
}
}
/* /*
* pred_test * pred_test
* Does the "predicate inclusion test" for partial indexes. * Does the "predicate inclusion test" for partial indexes.
...@@ -751,7 +769,7 @@ indexable_operator(Expr *clause, Oid opclass, bool indexkey_on_left) ...@@ -751,7 +769,7 @@ indexable_operator(Expr *clause, Oid opclass, bool indexkey_on_left)
* to CNF format). --Nels, Jan '93 * to CNF format). --Nels, Jan '93
*/ */
static bool static bool
pred_test(List *predicate_list, List *restrictinfo_list, List *joininfo_list) pred_test(List *predicate_list, List *restrictinfo_list)
{ {
List *pred; List *pred;
...@@ -1464,8 +1482,7 @@ make_innerjoin_index_path(Query *root, ...@@ -1464,8 +1482,7 @@ make_innerjoin_index_path(Query *root,
rel->relid, /* do not use 0! */ rel->relid, /* do not use 0! */
JOIN_INNER); JOIN_INNER);
/* Like costsize.c, force estimate to be at least one row */ /* Like costsize.c, force estimate to be at least one row */
if (pathnode->rows < 1.0) pathnode->rows = clamp_row_est(pathnode->rows);
pathnode->rows = 1.0;
cost_index(&pathnode->path, root, rel, index, indexquals, true); cost_index(&pathnode->path, root, rel, index, indexquals, true);
......
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
* *
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/optimizer/path/joinpath.c,v 1.84 2003/12/30 23:53:14 tgl Exp $ * $PostgreSQL: pgsql/src/backend/optimizer/path/joinpath.c,v 1.85 2004/01/05 05:07:35 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -690,7 +690,7 @@ hash_inner_and_outer(Query *root, ...@@ -690,7 +690,7 @@ hash_inner_and_outer(Query *root,
{ {
RestrictInfo *restrictinfo = (RestrictInfo *) lfirst(i); RestrictInfo *restrictinfo = (RestrictInfo *) lfirst(i);
if (!restrictinfo->canjoin || if (!restrictinfo->can_join ||
restrictinfo->hashjoinoperator == InvalidOid) restrictinfo->hashjoinoperator == InvalidOid)
continue; /* not hashjoinable */ continue; /* not hashjoinable */
...@@ -698,7 +698,7 @@ hash_inner_and_outer(Query *root, ...@@ -698,7 +698,7 @@ hash_inner_and_outer(Query *root,
* If processing an outer join, only use its own join clauses for * If processing an outer join, only use its own join clauses for
* hashing. For inner joins we need not be so picky. * hashing. For inner joins we need not be so picky.
*/ */
if (isouterjoin && restrictinfo->ispusheddown) if (isouterjoin && restrictinfo->is_pushed_down)
continue; continue;
/* /*
...@@ -804,17 +804,17 @@ select_mergejoin_clauses(RelOptInfo *joinrel, ...@@ -804,17 +804,17 @@ select_mergejoin_clauses(RelOptInfo *joinrel,
*/ */
if (isouterjoin) if (isouterjoin)
{ {
if (restrictinfo->ispusheddown) if (restrictinfo->is_pushed_down)
continue; continue;
switch (jointype) switch (jointype)
{ {
case JOIN_RIGHT: case JOIN_RIGHT:
if (!restrictinfo->canjoin || if (!restrictinfo->can_join ||
restrictinfo->mergejoinoperator == InvalidOid) restrictinfo->mergejoinoperator == InvalidOid)
return NIL; /* not mergejoinable */ return NIL; /* not mergejoinable */
break; break;
case JOIN_FULL: case JOIN_FULL:
if (!restrictinfo->canjoin || if (!restrictinfo->can_join ||
restrictinfo->mergejoinoperator == InvalidOid) restrictinfo->mergejoinoperator == InvalidOid)
ereport(ERROR, ereport(ERROR,
(errcode(ERRCODE_FEATURE_NOT_SUPPORTED), (errcode(ERRCODE_FEATURE_NOT_SUPPORTED),
...@@ -826,7 +826,7 @@ select_mergejoin_clauses(RelOptInfo *joinrel, ...@@ -826,7 +826,7 @@ select_mergejoin_clauses(RelOptInfo *joinrel,
} }
} }
if (!restrictinfo->canjoin || if (!restrictinfo->can_join ||
restrictinfo->mergejoinoperator == InvalidOid) restrictinfo->mergejoinoperator == InvalidOid)
continue; /* not mergejoinable */ continue; /* not mergejoinable */
......
...@@ -8,20 +8,21 @@ ...@@ -8,20 +8,21 @@
* *
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/optimizer/path/orindxpath.c,v 1.55 2004/01/04 00:07:32 tgl Exp $ * $PostgreSQL: pgsql/src/backend/optimizer/path/orindxpath.c,v 1.56 2004/01/05 05:07:35 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
#include "postgres.h" #include "postgres.h"
#include "optimizer/clauses.h"
#include "optimizer/cost.h" #include "optimizer/cost.h"
#include "optimizer/pathnode.h" #include "optimizer/pathnode.h"
#include "optimizer/paths.h" #include "optimizer/paths.h"
#include "optimizer/restrictinfo.h" #include "optimizer/restrictinfo.h"
static IndexPath *best_or_subclause_indices(Query *root, RelOptInfo *rel, static IndexPath *best_or_subclause_indexes(Query *root, RelOptInfo *rel,
List *subclauses); List *subclauses);
static bool best_or_subclause_index(Query *root, static bool best_or_subclause_index(Query *root,
RelOptInfo *rel, RelOptInfo *rel,
...@@ -32,16 +33,166 @@ static bool best_or_subclause_index(Query *root, ...@@ -32,16 +33,166 @@ static bool best_or_subclause_index(Query *root,
Cost *retTotalCost); Cost *retTotalCost);
/*----------
* create_or_index_quals
* Examine join OR-of-AND quals to see if any useful restriction OR
* clauses can be extracted. If so, add them to the query.
*
* Although a join clause must reference other relations overall,
* an OR of ANDs clause might contain sub-clauses that reference just this
* relation and can be used to build a restriction clause.
* For example consider
* WHERE ((a.x = 42 AND b.y = 43) OR (a.x = 44 AND b.z = 45));
* We can transform this into
* WHERE ((a.x = 42 AND b.y = 43) OR (a.x = 44 AND b.z = 45))
* AND (a.x = 42 OR a.x = 44)
* AND (b.y = 43 OR b.z = 45);
* which opens the potential to build OR indexscans on a and b. In essence
* this is a partial transformation to CNF (AND of ORs format). It is not
* complete, however, because we do not unravel the original OR --- doing so
* would usually bloat the qualification expression to little gain.
*
* The added quals are partially redundant with the original OR, and therefore
* will cause the size of the joinrel to be underestimated when it is finally
* formed. (This would be true of a full transformation to CNF as well; the
* fault is not really in the transformation, but in clauselist_selectivity's
* inability to recognize redundant conditions.) To minimize the collateral
* damage, we want to minimize the number of quals added. Therefore we do
* not add every possible extracted restriction condition to the query.
* Instead, we search for the single restriction condition that generates
* the most useful (cheapest) OR indexscan, and add only that condition.
* This is a pretty ad-hoc heuristic, but quite useful.
*
* We can then compensate for the redundancy of the added qual by poking
* the recorded selectivity of the original OR clause, thereby ensuring
* the added qual doesn't change the estimated size of the joinrel when
* it is finally formed. This is a MAJOR HACK: it depends on the fact
* that clause selectivities are cached and on the fact that the same
* RestrictInfo node will appear in every joininfo list that might be used
* when the joinrel is formed. And it probably isn't right in cases where
* the size estimation is nonlinear (i.e., outer and IN joins). But it
* beats not doing anything.
*
* NOTE: one might think this messiness could be worked around by generating
* the indexscan path with a small path->rows value, and not touching the
* rel's baserestrictinfo or rel->rows. However, that does not work.
* The optimizer's fundamental design assumes that every general-purpose
* Path for a given relation generates the same number of rows. Without
* this assumption we'd not be able to optimize solely on the cost of Paths,
* but would have to take number of output rows into account as well.
* (Perhaps someday that'd be worth doing, but it's a pretty big change...)
*
* 'rel' is the relation entry for which quals are to be created
*
* If successful, adds qual(s) to rel->baserestrictinfo and returns TRUE.
* If no quals available, returns FALSE and doesn't change rel.
*
* Note: check_partial_indexes() must have been run previously.
*----------
*/
bool
create_or_index_quals(Query *root, RelOptInfo *rel)
{
IndexPath *bestpath = NULL;
RestrictInfo *bestrinfo = NULL;
FastList orclauses;
List *orclause;
Expr *indxqual_or_expr;
RestrictInfo *or_rinfo;
Selectivity or_selec,
orig_selec;
List *i;
/*
* We use the best_or_subclause_indexes() machinery to locate the
* best combination of restriction subclauses. Note we must ignore
* any joinclauses that are not marked valid_everywhere, because they
* cannot be pushed down due to outer-join rules.
*/
foreach(i, rel->joininfo)
{
JoinInfo *joininfo = (JoinInfo *) lfirst(i);
List *j;
foreach(j, joininfo->jinfo_restrictinfo)
{
RestrictInfo *rinfo = (RestrictInfo *) lfirst(j);
if (restriction_is_or_clause(rinfo) &&
rinfo->valid_everywhere)
{
IndexPath *pathnode;
pathnode = best_or_subclause_indexes(root,
rel,
((BoolExpr *) rinfo->orclause)->args);
if (pathnode)
{
if (bestpath == NULL ||
pathnode->path.total_cost < bestpath->path.total_cost)
{
bestpath = pathnode;
bestrinfo = rinfo;
}
}
}
}
}
/* Fail if no suitable clauses found */
if (bestpath == NULL)
return false;
/*
* Build an expression representation of the indexqual, expanding
* the implicit OR and AND semantics of the first- and
* second-level lists.
*/
FastListInit(&orclauses);
foreach(orclause, bestpath->indexqual)
FastAppend(&orclauses, make_ands_explicit(lfirst(orclause)));
indxqual_or_expr = make_orclause(FastListValue(&orclauses));
/*
* And add it to the rel's restriction list.
*/
or_rinfo = make_restrictinfo(indxqual_or_expr, true, true);
rel->baserestrictinfo = lappend(rel->baserestrictinfo, or_rinfo);
/*
* Adjust the original OR clause's cached selectivity to compensate
* for the selectivity of the added (but redundant) lower-level qual.
* This should result in the join rel getting approximately the same
* rows estimate as it would have gotten without all these shenanigans.
* (XXX major hack alert ... this depends on the assumption that the
* selectivity will stay cached ...)
*/
or_selec = clause_selectivity(root, (Node *) or_rinfo,
0, JOIN_INNER);
if (or_selec > 0 && or_selec < 1)
{
orig_selec = clause_selectivity(root, (Node *) bestrinfo,
0, JOIN_INNER);
bestrinfo->this_selec = orig_selec / or_selec;
/* clamp result to sane range */
if (bestrinfo->this_selec > 1)
bestrinfo->this_selec = 1;
}
/* Tell caller to recompute rel's rows estimate */
return true;
}
/* /*
* create_or_index_paths * create_or_index_paths
* Creates multi-scan index paths for indices that match OR clauses. * Creates multi-scan index paths for indexes that match OR clauses.
* *
* 'rel' is the relation entry for which the paths are to be created * 'rel' is the relation entry for which the paths are to be created
* *
* Returns nothing, but adds paths to rel->pathlist via add_path(). * Returns nothing, but adds paths to rel->pathlist via add_path().
* *
* Note: create_index_paths() must have been run already, since it does * Note: check_partial_indexes() must have been run previously.
* the heavy lifting to determine whether partial indexes may be used.
*/ */
void void
create_or_index_paths(Query *root, RelOptInfo *rel) create_or_index_paths(Query *root, RelOptInfo *rel)
...@@ -60,7 +211,7 @@ create_or_index_paths(Query *root, RelOptInfo *rel) ...@@ -60,7 +211,7 @@ create_or_index_paths(Query *root, RelOptInfo *rel)
{ {
IndexPath *pathnode; IndexPath *pathnode;
pathnode = best_or_subclause_indices(root, pathnode = best_or_subclause_indexes(root,
rel, rel,
((BoolExpr *) rinfo->orclause)->args); ((BoolExpr *) rinfo->orclause)->args);
...@@ -68,49 +219,10 @@ create_or_index_paths(Query *root, RelOptInfo *rel) ...@@ -68,49 +219,10 @@ create_or_index_paths(Query *root, RelOptInfo *rel)
add_path(rel, (Path *) pathnode); add_path(rel, (Path *) pathnode);
} }
} }
/*
* Also consider join clauses that are ORs. Although a join clause
* must reference other relations overall, an OR of ANDs clause might
* contain sub-clauses that reference just our relation and can be
* used to build a non-join indexscan. For example consider
* WHERE (a.x = 42 AND b.y = 43) OR (a.x = 44 AND b.z = 45);
* We could build an OR indexscan on a.x using those subclauses.
*
* XXX don't enable this code quite yet. Although the plans it creates
* are correct, and possibly even useful, we are totally confused about
* the number of rows returned, leading to poor choices of join plans
* above the indexscan. Need to restructure the way join sizes are
* calculated before this will really work.
*/
#ifdef NOT_YET
foreach(i, rel->joininfo)
{
JoinInfo *joininfo = (JoinInfo *) lfirst(i);
List *j;
foreach(j, joininfo->jinfo_restrictinfo)
{
RestrictInfo *rinfo = (RestrictInfo *) lfirst(j);
if (restriction_is_or_clause(rinfo))
{
IndexPath *pathnode;
pathnode = best_or_subclause_indices(root,
rel,
((BoolExpr *) rinfo->orclause)->args);
if (pathnode)
add_path(rel, (Path *) pathnode);
}
}
}
#endif
} }
/* /*
* best_or_subclause_indices * best_or_subclause_indexes
* Determine the best index to be used in conjunction with each subclause * Determine the best index to be used in conjunction with each subclause
* of an OR clause, and build a Path for a multi-index scan. * of an OR clause, and build a Path for a multi-index scan.
* *
...@@ -134,7 +246,7 @@ create_or_index_paths(Query *root, RelOptInfo *rel) ...@@ -134,7 +246,7 @@ create_or_index_paths(Query *root, RelOptInfo *rel)
* single tuple more than once). * single tuple more than once).
*/ */
static IndexPath * static IndexPath *
best_or_subclause_indices(Query *root, best_or_subclause_indexes(Query *root,
RelOptInfo *rel, RelOptInfo *rel,
List *subclauses) List *subclauses)
{ {
...@@ -202,7 +314,10 @@ best_or_subclause_indices(Query *root, ...@@ -202,7 +314,10 @@ best_or_subclause_indices(Query *root,
/* We don't actually care what order the index scans in. */ /* We don't actually care what order the index scans in. */
pathnode->indexscandir = NoMovementScanDirection; pathnode->indexscandir = NoMovementScanDirection;
/* XXX this may be wrong when using join OR clauses... */ /*
* The number of rows is the same as the parent rel's estimate, since
* this isn't a join inner indexscan.
*/
pathnode->rows = rel->rows; pathnode->rows = rel->rows;
return pathnode; return pathnode;
......
...@@ -10,7 +10,7 @@ ...@@ -10,7 +10,7 @@
* *
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/optimizer/plan/createplan.c,v 1.161 2003/11/29 19:51:50 pgsql Exp $ * $PostgreSQL: pgsql/src/backend/optimizer/plan/createplan.c,v 1.162 2004/01/05 05:07:35 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -643,6 +643,7 @@ create_unique_plan(Query *root, UniquePath *best_path) ...@@ -643,6 +643,7 @@ create_unique_plan(Query *root, UniquePath *best_path)
plan = (Plan *) make_unique(my_tlist, plan, sortList); plan = (Plan *) make_unique(my_tlist, plan, sortList);
} }
/* Adjust output size estimate (other fields should be OK already) */
plan->plan_rows = best_path->rows; plan->plan_rows = best_path->rows;
return plan; return plan;
......
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
* *
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/optimizer/plan/initsplan.c,v 1.96 2004/01/04 03:51:52 tgl Exp $ * $PostgreSQL: pgsql/src/backend/optimizer/plan/initsplan.c,v 1.97 2004/01/05 05:07:35 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -37,7 +37,7 @@ ...@@ -37,7 +37,7 @@
static void mark_baserels_for_outer_join(Query *root, Relids rels, static void mark_baserels_for_outer_join(Query *root, Relids rels,
Relids outerrels); Relids outerrels);
static void distribute_qual_to_rels(Query *root, Node *clause, static void distribute_qual_to_rels(Query *root, Node *clause,
bool ispusheddown, bool is_pushed_down,
bool isdeduced, bool isdeduced,
Relids outerjoin_nonnullable, Relids outerjoin_nonnullable,
Relids qualscope); Relids qualscope);
...@@ -356,7 +356,7 @@ mark_baserels_for_outer_join(Query *root, Relids rels, Relids outerrels) ...@@ -356,7 +356,7 @@ mark_baserels_for_outer_join(Query *root, Relids rels, Relids outerrels)
* equijoined vars. * equijoined vars.
* *
* 'clause': the qual clause to be distributed * 'clause': the qual clause to be distributed
* 'ispusheddown': if TRUE, force the clause to be marked 'ispusheddown' * 'is_pushed_down': if TRUE, force the clause to be marked 'is_pushed_down'
* (this indicates the clause came from a FromExpr, not a JoinExpr) * (this indicates the clause came from a FromExpr, not a JoinExpr)
* 'isdeduced': TRUE if the qual came from implied-equality deduction * 'isdeduced': TRUE if the qual came from implied-equality deduction
* 'outerjoin_nonnullable': NULL if not an outer-join qual, else the set of * 'outerjoin_nonnullable': NULL if not an outer-join qual, else the set of
...@@ -365,16 +365,17 @@ mark_baserels_for_outer_join(Query *root, Relids rels, Relids outerrels) ...@@ -365,16 +365,17 @@ mark_baserels_for_outer_join(Query *root, Relids rels, Relids outerrels)
* *
* 'qualscope' identifies what level of JOIN the qual came from. For a top * 'qualscope' identifies what level of JOIN the qual came from. For a top
* level qual (WHERE qual), qualscope lists all baserel ids and in addition * level qual (WHERE qual), qualscope lists all baserel ids and in addition
* 'ispusheddown' will be TRUE. * 'is_pushed_down' will be TRUE.
*/ */
static void static void
distribute_qual_to_rels(Query *root, Node *clause, distribute_qual_to_rels(Query *root, Node *clause,
bool ispusheddown, bool is_pushed_down,
bool isdeduced, bool isdeduced,
Relids outerjoin_nonnullable, Relids outerjoin_nonnullable,
Relids qualscope) Relids qualscope)
{ {
Relids relids; Relids relids;
bool valid_everywhere;
bool can_be_equijoin; bool can_be_equijoin;
RestrictInfo *restrictinfo; RestrictInfo *restrictinfo;
RelOptInfo *rel; RelOptInfo *rel;
...@@ -415,6 +416,7 @@ distribute_qual_to_rels(Query *root, Node *clause, ...@@ -415,6 +416,7 @@ distribute_qual_to_rels(Query *root, Node *clause,
* the vars were equal). * the vars were equal).
*/ */
Assert(bms_equal(relids, qualscope)); Assert(bms_equal(relids, qualscope));
valid_everywhere = true;
can_be_equijoin = true; can_be_equijoin = true;
} }
else if (bms_overlap(relids, outerjoin_nonnullable)) else if (bms_overlap(relids, outerjoin_nonnullable))
...@@ -433,6 +435,7 @@ distribute_qual_to_rels(Query *root, Node *clause, ...@@ -433,6 +435,7 @@ distribute_qual_to_rels(Query *root, Node *clause,
* result, so we treat it the same as an ordinary inner-join qual. * result, so we treat it the same as an ordinary inner-join qual.
*/ */
relids = qualscope; relids = qualscope;
valid_everywhere = false;
can_be_equijoin = false; can_be_equijoin = false;
} }
else else
...@@ -447,18 +450,26 @@ distribute_qual_to_rels(Query *root, Node *clause, ...@@ -447,18 +450,26 @@ distribute_qual_to_rels(Query *root, Node *clause,
* time we are called, the outerjoinset of each baserel will show * time we are called, the outerjoinset of each baserel will show
* exactly those outer joins that are below the qual in the join * exactly those outer joins that are below the qual in the join
* tree. * tree.
*
* We also need to determine whether the qual is "valid everywhere",
* which is true if the qual mentions no variables that are involved
* in lower-level outer joins (this may be an overly strong test).
*/ */
Relids addrelids = NULL; Relids addrelids = NULL;
Relids tmprelids; Relids tmprelids;
int relno; int relno;
valid_everywhere = true;
tmprelids = bms_copy(relids); tmprelids = bms_copy(relids);
while ((relno = bms_first_member(tmprelids)) >= 0) while ((relno = bms_first_member(tmprelids)) >= 0)
{ {
RelOptInfo *rel = find_base_rel(root, relno); RelOptInfo *rel = find_base_rel(root, relno);
if (rel->outerjoinset != NULL) if (rel->outerjoinset != NULL)
{
addrelids = bms_add_members(addrelids, rel->outerjoinset); addrelids = bms_add_members(addrelids, rel->outerjoinset);
valid_everywhere = false;
}
} }
bms_free(tmprelids); bms_free(tmprelids);
...@@ -489,13 +500,15 @@ distribute_qual_to_rels(Query *root, Node *clause, ...@@ -489,13 +500,15 @@ distribute_qual_to_rels(Query *root, Node *clause,
* same joinrel. A qual originating from WHERE is always considered * same joinrel. A qual originating from WHERE is always considered
* "pushed down". * "pushed down".
*/ */
if (!ispusheddown) if (!is_pushed_down)
ispusheddown = !bms_equal(relids, qualscope); is_pushed_down = !bms_equal(relids, qualscope);
/* /*
* Build the RestrictInfo node itself. * Build the RestrictInfo node itself.
*/ */
restrictinfo = make_restrictinfo((Expr *) clause, ispusheddown); restrictinfo = make_restrictinfo((Expr *) clause,
is_pushed_down,
valid_everywhere);
/* /*
* Figure out where to attach it. * Figure out where to attach it.
......
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
* *
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/optimizer/util/pathnode.c,v 1.96 2003/11/29 19:51:51 pgsql Exp $ * $PostgreSQL: pgsql/src/backend/optimizer/util/pathnode.c,v 1.97 2004/01/05 05:07:35 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -373,13 +373,6 @@ create_index_path(Query *root, ...@@ -373,13 +373,6 @@ create_index_path(Query *root,
*/ */
pathnode->rows = rel->rows; pathnode->rows = rel->rows;
/*
* Not sure if this is necessary, but it should help if the statistics
* are too far off
*/
if (index->indpred && index->tuples < pathnode->rows)
pathnode->rows = index->tuples;
cost_index(&pathnode->path, root, rel, index, indexquals, false); cost_index(&pathnode->path, root, rel, index, indexquals, false);
return pathnode; return pathnode;
...@@ -398,6 +391,7 @@ create_tidscan_path(Query *root, RelOptInfo *rel, List *tideval) ...@@ -398,6 +391,7 @@ create_tidscan_path(Query *root, RelOptInfo *rel, List *tideval)
pathnode->path.pathtype = T_TidScan; pathnode->path.pathtype = T_TidScan;
pathnode->path.parent = rel; pathnode->path.parent = rel;
pathnode->path.pathkeys = NIL; pathnode->path.pathkeys = NIL;
pathnode->tideval = tideval; pathnode->tideval = tideval;
cost_tidscan(&pathnode->path, root, rel, tideval); cost_tidscan(&pathnode->path, root, rel, tideval);
......
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
* *
* *
* IDENTIFICATION * IDENTIFICATION
* $PostgreSQL: pgsql/src/backend/optimizer/util/restrictinfo.c,v 1.23 2004/01/04 03:51:52 tgl Exp $ * $PostgreSQL: pgsql/src/backend/optimizer/util/restrictinfo.c,v 1.24 2004/01/05 05:07:36 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -20,7 +20,8 @@ ...@@ -20,7 +20,8 @@
#include "optimizer/var.h" #include "optimizer/var.h"
static Expr *make_sub_restrictinfos(Expr *clause, bool ispusheddown); static Expr *make_sub_restrictinfos(Expr *clause, bool is_pushed_down,
bool valid_everywhere);
static bool join_clause_is_redundant(Query *root, static bool join_clause_is_redundant(Query *root,
RestrictInfo *rinfo, RestrictInfo *rinfo,
List *reference_list, List *reference_list,
...@@ -32,18 +33,22 @@ static bool join_clause_is_redundant(Query *root, ...@@ -32,18 +33,22 @@ static bool join_clause_is_redundant(Query *root,
* *
* Build a RestrictInfo node containing the given subexpression. * Build a RestrictInfo node containing the given subexpression.
* *
* The ispusheddown flag must be supplied by the caller. We initialize * The is_pushed_down and valid_everywhere flags must be supplied by the
* fields that depend only on the given subexpression, leaving others that * caller.
* depend on context (or may never be needed at all) to be filled later. *
* We initialize fields that depend only on the given subexpression, leaving
* others that depend on context (or may never be needed at all) to be filled
* later.
*/ */
RestrictInfo * RestrictInfo *
make_restrictinfo(Expr *clause, bool ispusheddown) make_restrictinfo(Expr *clause, bool is_pushed_down, bool valid_everywhere)
{ {
RestrictInfo *restrictinfo = makeNode(RestrictInfo); RestrictInfo *restrictinfo = makeNode(RestrictInfo);
restrictinfo->clause = clause; restrictinfo->clause = clause;
restrictinfo->ispusheddown = ispusheddown; restrictinfo->is_pushed_down = is_pushed_down;
restrictinfo->canjoin = false; /* may get set below */ restrictinfo->valid_everywhere = valid_everywhere;
restrictinfo->can_join = false; /* may get set below */
/* /*
* If it's a binary opclause, set up left/right relids info. * If it's a binary opclause, set up left/right relids info.
...@@ -67,7 +72,7 @@ make_restrictinfo(Expr *clause, bool ispusheddown) ...@@ -67,7 +72,7 @@ make_restrictinfo(Expr *clause, bool ispusheddown)
!bms_is_empty(restrictinfo->right_relids) && !bms_is_empty(restrictinfo->right_relids) &&
!bms_overlap(restrictinfo->left_relids, !bms_overlap(restrictinfo->left_relids,
restrictinfo->right_relids)) restrictinfo->right_relids))
restrictinfo->canjoin = true; restrictinfo->can_join = true;
} }
else else
{ {
...@@ -84,7 +89,9 @@ make_restrictinfo(Expr *clause, bool ispusheddown) ...@@ -84,7 +89,9 @@ make_restrictinfo(Expr *clause, bool ispusheddown)
*/ */
if (or_clause((Node *) clause)) if (or_clause((Node *) clause))
{ {
restrictinfo->orclause = make_sub_restrictinfos(clause, ispusheddown); restrictinfo->orclause = make_sub_restrictinfos(clause,
is_pushed_down,
valid_everywhere);
} }
else else
{ {
...@@ -126,7 +133,8 @@ make_restrictinfo(Expr *clause, bool ispusheddown) ...@@ -126,7 +133,8 @@ make_restrictinfo(Expr *clause, bool ispusheddown)
* Recursively insert sub-RestrictInfo nodes into a boolean expression. * Recursively insert sub-RestrictInfo nodes into a boolean expression.
*/ */
static Expr * static Expr *
make_sub_restrictinfos(Expr *clause, bool ispusheddown) make_sub_restrictinfos(Expr *clause, bool is_pushed_down,
bool valid_everywhere)
{ {
if (or_clause((Node *) clause)) if (or_clause((Node *) clause))
{ {
...@@ -136,7 +144,8 @@ make_sub_restrictinfos(Expr *clause, bool ispusheddown) ...@@ -136,7 +144,8 @@ make_sub_restrictinfos(Expr *clause, bool ispusheddown)
foreach(temp, ((BoolExpr *) clause)->args) foreach(temp, ((BoolExpr *) clause)->args)
orlist = lappend(orlist, orlist = lappend(orlist,
make_sub_restrictinfos(lfirst(temp), make_sub_restrictinfos(lfirst(temp),
ispusheddown)); is_pushed_down,
valid_everywhere));
return make_orclause(orlist); return make_orclause(orlist);
} }
else if (and_clause((Node *) clause)) else if (and_clause((Node *) clause))
...@@ -147,11 +156,14 @@ make_sub_restrictinfos(Expr *clause, bool ispusheddown) ...@@ -147,11 +156,14 @@ make_sub_restrictinfos(Expr *clause, bool ispusheddown)
foreach(temp, ((BoolExpr *) clause)->args) foreach(temp, ((BoolExpr *) clause)->args)
andlist = lappend(andlist, andlist = lappend(andlist,
make_sub_restrictinfos(lfirst(temp), make_sub_restrictinfos(lfirst(temp),
ispusheddown)); is_pushed_down,
valid_everywhere));
return make_andclause(andlist); return make_andclause(andlist);
} }
else else
return (Expr *) make_restrictinfo(clause, ispusheddown); return (Expr *) make_restrictinfo(clause,
is_pushed_down,
valid_everywhere);
} }
/* /*
...@@ -207,7 +219,7 @@ get_actual_join_clauses(List *restrictinfo_list, ...@@ -207,7 +219,7 @@ get_actual_join_clauses(List *restrictinfo_list,
{ {
RestrictInfo *clause = (RestrictInfo *) lfirst(temp); RestrictInfo *clause = (RestrictInfo *) lfirst(temp);
if (clause->ispusheddown) if (clause->is_pushed_down)
*otherquals = lappend(*otherquals, clause->clause); *otherquals = lappend(*otherquals, clause->clause);
else else
*joinquals = lappend(*joinquals, clause->clause); *joinquals = lappend(*joinquals, clause->clause);
...@@ -348,7 +360,7 @@ join_clause_is_redundant(Query *root, ...@@ -348,7 +360,7 @@ join_clause_is_redundant(Query *root,
if (refrinfo->mergejoinoperator != InvalidOid && if (refrinfo->mergejoinoperator != InvalidOid &&
rinfo->left_pathkey == refrinfo->left_pathkey && rinfo->left_pathkey == refrinfo->left_pathkey &&
rinfo->right_pathkey == refrinfo->right_pathkey && rinfo->right_pathkey == refrinfo->right_pathkey &&
(rinfo->ispusheddown == refrinfo->ispusheddown || (rinfo->is_pushed_down == refrinfo->is_pushed_down ||
!IS_OUTER_JOIN(jointype))) !IS_OUTER_JOIN(jointype)))
{ {
redundant = true; redundant = true;
......
...@@ -7,7 +7,7 @@ ...@@ -7,7 +7,7 @@
* Portions Copyright (c) 1996-2003, PostgreSQL Global Development Group * Portions Copyright (c) 1996-2003, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California * Portions Copyright (c) 1994, Regents of the University of California
* *
* $PostgreSQL: pgsql/src/include/nodes/relation.h,v 1.90 2004/01/04 03:51:52 tgl Exp $ * $PostgreSQL: pgsql/src/include/nodes/relation.h,v 1.91 2004/01/05 05:07:36 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -321,6 +321,8 @@ typedef struct Path ...@@ -321,6 +321,8 @@ typedef struct Path
{ {
NodeTag type; NodeTag type;
NodeTag pathtype; /* tag identifying scan/join method */
RelOptInfo *parent; /* the relation this path can build */ RelOptInfo *parent; /* the relation this path can build */
/* estimated execution costs for path (see costsize.c for more info) */ /* estimated execution costs for path (see costsize.c for more info) */
...@@ -329,8 +331,6 @@ typedef struct Path ...@@ -329,8 +331,6 @@ typedef struct Path
Cost total_cost; /* total cost (assuming all tuples Cost total_cost; /* total cost (assuming all tuples
* fetched) */ * fetched) */
NodeTag pathtype; /* tag identifying scan/join method */
List *pathkeys; /* sort ordering of path's output */ List *pathkeys; /* sort ordering of path's output */
/* pathkeys is a List of Lists of PathKeyItem nodes; see above */ /* pathkeys is a List of Lists of PathKeyItem nodes; see above */
} Path; } Path;
...@@ -389,6 +389,9 @@ typedef struct IndexPath ...@@ -389,6 +389,9 @@ typedef struct IndexPath
/* /*
* TidPath represents a scan by TID * TidPath represents a scan by TID
*
* tideval is an implicitly OR'ed list of quals of the form CTID = something.
* Note they are bare quals, not RestrictInfos.
*/ */
typedef struct TidPath typedef struct TidPath
{ {
...@@ -570,13 +573,17 @@ typedef struct HashPath ...@@ -570,13 +573,17 @@ typedef struct HashPath
* When we do form the outer join's joinrel, we still need to distinguish * When we do form the outer join's joinrel, we still need to distinguish
* those quals that are actually in that join's JOIN/ON condition from those * those quals that are actually in that join's JOIN/ON condition from those
* that appeared higher in the tree and were pushed down to the join rel * that appeared higher in the tree and were pushed down to the join rel
* because they used no other rels. That's what the ispusheddown flag is for; * because they used no other rels. That's what the is_pushed_down flag is
* it tells us that a qual came from a point above the join of the specific * for; it tells us that a qual came from a point above the join of the
* set of base rels that it uses (or that the JoinInfo structures claim it * specific set of base rels that it uses (or that the JoinInfo structures
* uses). A clause that originally came from WHERE will *always* have its * claim it uses). A clause that originally came from WHERE will *always*
* ispusheddown flag set; a clause that came from an INNER JOIN condition, * have its is_pushed_down flag set; a clause that came from an INNER JOIN
* but doesn't use all the rels being joined, will also have ispusheddown set * condition, but doesn't use all the rels being joined, will also have
* because it will get attached to some lower joinrel. * is_pushed_down set because it will get attached to some lower joinrel.
*
* We also store a valid_everywhere flag, which says that the clause is not
* affected by any lower-level outer join, and therefore any conditions it
* asserts can be presumed true throughout the plan tree.
* *
* In general, the referenced clause might be arbitrarily complex. The * In general, the referenced clause might be arbitrarily complex. The
* kinds of clauses we can handle as indexscan quals, mergejoin clauses, * kinds of clauses we can handle as indexscan quals, mergejoin clauses,
...@@ -602,7 +609,9 @@ typedef struct RestrictInfo ...@@ -602,7 +609,9 @@ typedef struct RestrictInfo
Expr *clause; /* the represented clause of WHERE or JOIN */ Expr *clause; /* the represented clause of WHERE or JOIN */
bool ispusheddown; /* TRUE if clause was pushed down in level */ bool is_pushed_down; /* TRUE if clause was pushed down in level */
bool valid_everywhere; /* TRUE if valid on every level */
/* /*
* This flag is set true if the clause looks potentially useful as a * This flag is set true if the clause looks potentially useful as a
...@@ -611,7 +620,7 @@ typedef struct RestrictInfo ...@@ -611,7 +620,7 @@ typedef struct RestrictInfo
* (Whether the operator is actually merge or hash joinable isn't * (Whether the operator is actually merge or hash joinable isn't
* checked, however.) * checked, however.)
*/ */
bool canjoin; bool can_join;
/* The set of relids (varnos) referenced in the clause: */ /* The set of relids (varnos) referenced in the clause: */
Relids clause_relids; Relids clause_relids;
......
...@@ -7,7 +7,7 @@ ...@@ -7,7 +7,7 @@
* Portions Copyright (c) 1996-2003, PostgreSQL Global Development Group * Portions Copyright (c) 1996-2003, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California * Portions Copyright (c) 1994, Regents of the University of California
* *
* $PostgreSQL: pgsql/src/include/optimizer/cost.h,v 1.59 2004/01/04 03:51:52 tgl Exp $ * $PostgreSQL: pgsql/src/include/optimizer/cost.h,v 1.60 2004/01/05 05:07:36 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -49,6 +49,7 @@ extern bool enable_nestloop; ...@@ -49,6 +49,7 @@ extern bool enable_nestloop;
extern bool enable_mergejoin; extern bool enable_mergejoin;
extern bool enable_hashjoin; extern bool enable_hashjoin;
extern double clamp_row_est(double nrows);
extern void cost_seqscan(Path *path, Query *root, extern void cost_seqscan(Path *path, Query *root,
RelOptInfo *baserel); RelOptInfo *baserel);
extern void cost_index(Path *path, Query *root, extern void cost_index(Path *path, Query *root,
......
...@@ -8,7 +8,7 @@ ...@@ -8,7 +8,7 @@
* Portions Copyright (c) 1996-2003, PostgreSQL Global Development Group * Portions Copyright (c) 1996-2003, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California * Portions Copyright (c) 1994, Regents of the University of California
* *
* $PostgreSQL: pgsql/src/include/optimizer/paths.h,v 1.71 2004/01/04 00:07:32 tgl Exp $ * $PostgreSQL: pgsql/src/include/optimizer/paths.h,v 1.72 2004/01/05 05:07:36 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -43,11 +43,13 @@ extern List *group_clauses_by_indexkey_for_or(RelOptInfo *rel, ...@@ -43,11 +43,13 @@ extern List *group_clauses_by_indexkey_for_or(RelOptInfo *rel,
Expr *orsubclause); Expr *orsubclause);
extern List *expand_indexqual_conditions(IndexOptInfo *index, extern List *expand_indexqual_conditions(IndexOptInfo *index,
List *clausegroups); List *clausegroups);
extern void check_partial_indexes(Query *root, RelOptInfo *rel);
/* /*
* orindxpath.c * orindxpath.c
* additional routines for indexable OR clauses * additional routines for indexable OR clauses
*/ */
extern bool create_or_index_quals(Query *root, RelOptInfo *rel);
extern void create_or_index_paths(Query *root, RelOptInfo *rel); extern void create_or_index_paths(Query *root, RelOptInfo *rel);
/* /*
......
...@@ -7,7 +7,7 @@ ...@@ -7,7 +7,7 @@
* Portions Copyright (c) 1996-2003, PostgreSQL Global Development Group * Portions Copyright (c) 1996-2003, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California * Portions Copyright (c) 1994, Regents of the University of California
* *
* $PostgreSQL: pgsql/src/include/optimizer/restrictinfo.h,v 1.21 2004/01/04 00:07:32 tgl Exp $ * $PostgreSQL: pgsql/src/include/optimizer/restrictinfo.h,v 1.22 2004/01/05 05:07:36 tgl Exp $
* *
*------------------------------------------------------------------------- *-------------------------------------------------------------------------
*/ */
...@@ -16,7 +16,8 @@ ...@@ -16,7 +16,8 @@
#include "nodes/relation.h" #include "nodes/relation.h"
extern RestrictInfo *make_restrictinfo(Expr *clause, bool ispusheddown); extern RestrictInfo *make_restrictinfo(Expr *clause, bool is_pushed_down,
bool valid_everywhere);
extern bool restriction_is_or_clause(RestrictInfo *restrictinfo); extern bool restriction_is_or_clause(RestrictInfo *restrictinfo);
extern List *get_actual_clauses(List *restrictinfo_list); extern List *get_actual_clauses(List *restrictinfo_list);
extern void get_actual_join_clauses(List *restrictinfo_list, extern void get_actual_join_clauses(List *restrictinfo_list,
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment