* Portions Copyright (c) 1994, Regents of the University of California
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/nodes/copyfuncs.c,v 1.305 2005/06/05 22:32:54 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/nodes/copyfuncs.c,v 1.306 2005/06/09 04:18:58 tgl Exp $
*
*-------------------------------------------------------------------------
*/
COPY_SCALAR_FIELD(valid_everywhere);
COPY_SCALAR_FIELD(can_join);
COPY_BITMAPSET_FIELD(clause_relids);
+ COPY_BITMAPSET_FIELD(required_relids);
COPY_BITMAPSET_FIELD(left_relids);
COPY_BITMAPSET_FIELD(right_relids);
COPY_NODE_FIELD(orclause);
return newnode;
}
-/*
- * _copyJoinInfo
- */
-static JoinInfo *
-_copyJoinInfo(JoinInfo *from)
-{
- JoinInfo *newnode = makeNode(JoinInfo);
-
- COPY_BITMAPSET_FIELD(unjoined_relids);
- COPY_NODE_FIELD(jinfo_restrictinfo);
-
- return newnode;
-}
-
/*
* _copyInClauseInfo
*/
case T_RestrictInfo:
retval = _copyRestrictInfo(from);
break;
- case T_JoinInfo:
- retval = _copyJoinInfo(from);
- break;
case T_InClauseInfo:
retval = _copyInClauseInfo(from);
break;
* Portions Copyright (c) 1994, Regents of the University of California
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/nodes/equalfuncs.c,v 1.242 2005/06/05 22:32:54 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/nodes/equalfuncs.c,v 1.243 2005/06/09 04:18:58 tgl Exp $
*
*-------------------------------------------------------------------------
*/
COMPARE_NODE_FIELD(clause);
COMPARE_SCALAR_FIELD(is_pushed_down);
COMPARE_SCALAR_FIELD(valid_everywhere);
+ COMPARE_BITMAPSET_FIELD(required_relids);
/*
* We ignore all the remaining fields, since they may not be set yet,
return true;
}
-static bool
-_equalJoinInfo(JoinInfo *a, JoinInfo *b)
-{
- COMPARE_BITMAPSET_FIELD(unjoined_relids);
- COMPARE_NODE_FIELD(jinfo_restrictinfo);
-
- return true;
-}
-
static bool
_equalInClauseInfo(InClauseInfo *a, InClauseInfo *b)
{
case T_RestrictInfo:
retval = _equalRestrictInfo(a, b);
break;
- case T_JoinInfo:
- retval = _equalJoinInfo(a, b);
- break;
case T_InClauseInfo:
retval = _equalInClauseInfo(a, b);
break;
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/nodes/outfuncs.c,v 1.254 2005/06/06 04:13:35 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/nodes/outfuncs.c,v 1.255 2005/06/09 04:18:58 tgl Exp $
*
* NOTES
* Every node type that can appear in stored rules' parsetrees *must*
WRITE_BOOL_FIELD(valid_everywhere);
WRITE_BOOL_FIELD(can_join);
WRITE_BITMAPSET_FIELD(clause_relids);
+ WRITE_BITMAPSET_FIELD(required_relids);
WRITE_BITMAPSET_FIELD(left_relids);
WRITE_BITMAPSET_FIELD(right_relids);
WRITE_NODE_FIELD(orclause);
WRITE_OID_FIELD(hashjoinoperator);
}
-static void
-_outJoinInfo(StringInfo str, JoinInfo *node)
-{
- WRITE_NODE_TYPE("JOININFO");
-
- WRITE_BITMAPSET_FIELD(unjoined_relids);
- WRITE_NODE_FIELD(jinfo_restrictinfo);
-}
-
static void
_outInnerIndexscanInfo(StringInfo str, InnerIndexscanInfo *node)
{
case T_RestrictInfo:
_outRestrictInfo(str, obj);
break;
- case T_JoinInfo:
- _outJoinInfo(str, obj);
- break;
case T_InnerIndexscanInfo:
_outInnerIndexscanInfo(str, obj);
break;
RelOptInfo.pathlist. (Actually, we discard Paths that are obviously
inferior alternatives before they ever get into the pathlist --- what
ends up in the pathlist is the cheapest way of generating each potentially
-useful sort ordering of the relation.) Also create RelOptInfo.joininfo
-nodes that list all the join clauses that involve this relation. For
-example, the WHERE clause "tab1.col1 = tab2.col1" generates a JoinInfo
-for tab1 listing tab2 as an unjoined relation, and also one for tab2
-showing tab1 as an unjoined relation.
+useful sort ordering of the relation.) Also create a RelOptInfo.joininfo
+list including all the join clauses that involve this relation. For
+example, the WHERE clause "tab1.col1 = tab2.col1" generates entries in
+both tab1 and tab2's joininfo lists.
If we have only a single base relation in the query, we are done.
Otherwise we have to figure out how to join the base relations into a
RestrictInfo - WHERE clauses, like "x = 3" or "y = z"
(note the same structure is used for restriction and
join clauses)
- JoinInfo - join clauses associated with a particular pair of relations
Path - every way to generate a RelOptInfo(sequential,index,joins)
SeqScan - a plain Path node with pathtype = T_SeqScan
* Portions Copyright (c) 1996-2005, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California
*
- * $PostgreSQL: pgsql/src/backend/optimizer/geqo/geqo_eval.c,v 1.75 2005/06/08 23:02:04 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/geqo/geqo_eval.c,v 1.76 2005/06/09 04:18:59 tgl Exp $
*
*-------------------------------------------------------------------------
*/
#include <math.h>
#include "optimizer/geqo.h"
+#include "optimizer/joininfo.h"
#include "optimizer/pathnode.h"
#include "optimizer/paths.h"
#include "utils/memutils.h"
/*
* Join if there is an applicable join clause.
*/
- foreach(l, outer_rel->joininfo)
- {
- JoinInfo *joininfo = (JoinInfo *) lfirst(l);
-
- if (bms_is_subset(joininfo->unjoined_relids, inner_rel->relids))
- return true;
- }
+ if (have_relevant_joinclause(outer_rel, inner_rel))
+ return true;
/*
* Join if the rels are members of the same IN sub-select. This is
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/path/allpaths.c,v 1.132 2005/06/06 04:13:35 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/path/allpaths.c,v 1.133 2005/06/09 04:18:59 tgl Exp $
*
*-------------------------------------------------------------------------
*/
printf("\n");
}
- foreach(l, rel->joininfo)
+ if (rel->joininfo)
{
- JoinInfo *j = (JoinInfo *) lfirst(l);
-
- printf("\tjoininfo (");
- print_relids(j->unjoined_relids);
- printf("): ");
- print_restrictclauses(root, j->jinfo_restrictinfo);
+ printf("\tjoininfo: ");
+ print_restrictclauses(root, rel->joininfo);
printf("\n");
}
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/path/indxpath.c,v 1.181 2005/06/05 22:32:55 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/path/indxpath.c,v 1.182 2005/06/09 04:18:59 tgl Exp $
*
*-------------------------------------------------------------------------
*/
static bool pred_test_recurse(Node *clause, Node *predicate);
static bool pred_test_simple_clause(Expr *predicate, Node *clause);
static Relids indexable_outerrelids(RelOptInfo *rel);
-static bool list_matches_any_index(List *clauses, RelOptInfo *rel,
- Relids outer_relids);
static bool matches_any_index(RestrictInfo *rinfo, RelOptInfo *rel,
Relids outer_relids);
static List *find_clauses_for_join(PlannerInfo *root, RelOptInfo *rel,
* classes over equi-joined attributes (i.e., if it recognized that a
* qualification such as "where a.b=c.d and a.b=5" could make use of
* an index on c.d), then we could use that equivalence class info
- * here with joininfo_list to do more complete tests for the usability
+ * here with joininfo lists to do more complete tests for the usability
* of a partial index. For now, the test only uses restriction
* clauses (those in restrictinfo_list). --Nels, Dec '92
*
Relids outer_relids = NULL;
ListCell *l;
+ /*
+ * Examine each joinclause in the joininfo list to see if it matches any
+ * key of any index. If so, add the clause's other rels to the result.
+ * (Note: we consider only actual participants, not extraneous rels
+ * possibly mentioned in required_relids.)
+ */
foreach(l, rel->joininfo)
{
- JoinInfo *joininfo = (JoinInfo *) lfirst(l);
+ RestrictInfo *joininfo = (RestrictInfo *) lfirst(l);
+ Relids other_rels;
- /*
- * Examine each joinclause in the JoinInfo node's list to see if
- * it matches any key of any index. If so, add the JoinInfo's
- * otherrels to the result. We can skip examining other
- * joinclauses in the same list as soon as we find a match, since
- * by definition they all have the same otherrels.
- */
- if (list_matches_any_index(joininfo->jinfo_restrictinfo,
- rel,
- joininfo->unjoined_relids))
- outer_relids = bms_add_members(outer_relids,
- joininfo->unjoined_relids);
+ other_rels = bms_difference(joininfo->clause_relids, rel->relids);
+ if (matches_any_index(joininfo, rel, other_rels))
+ outer_relids = bms_join(outer_relids, other_rels);
+ else
+ bms_free(other_rels);
}
return outer_relids;
}
/*
- * list_matches_any_index
- * Workhorse for indexable_outerrelids: given a list of RestrictInfos,
- * see if any of them match any index of the given rel.
- *
- * We define it like this so that we can recurse into OR subclauses.
+ * matches_any_index
+ * Workhorse for indexable_outerrelids: see if a joinclause can be
+ * matched to any index of the given rel.
*/
static bool
-list_matches_any_index(List *clauses, RelOptInfo *rel, Relids outer_relids)
+matches_any_index(RestrictInfo *rinfo, RelOptInfo *rel, Relids outer_relids)
{
ListCell *l;
- foreach(l, clauses)
- {
- RestrictInfo *rinfo = (RestrictInfo *) lfirst(l);
- ListCell *j;
-
- Assert(IsA(rinfo, RestrictInfo));
+ Assert(IsA(rinfo, RestrictInfo));
- /* RestrictInfos that aren't ORs are easy */
- if (!restriction_is_or_clause(rinfo))
- {
- if (matches_any_index(rinfo, rel, outer_relids))
- return true;
- continue;
- }
-
- foreach(j, ((BoolExpr *) rinfo->orclause)->args)
+ if (restriction_is_or_clause(rinfo))
+ {
+ foreach(l, ((BoolExpr *) rinfo->orclause)->args)
{
- Node *orarg = (Node *) lfirst(j);
+ Node *orarg = (Node *) lfirst(l);
/* OR arguments should be ANDs or sub-RestrictInfos */
if (and_clause(orarg))
{
- List *andargs = ((BoolExpr *) orarg)->args;
+ ListCell *j;
/* Recurse to examine AND items and sub-ORs */
- if (list_matches_any_index(andargs, rel, outer_relids))
- return true;
+ foreach(j, ((BoolExpr *) orarg)->args)
+ {
+ RestrictInfo *arinfo = (RestrictInfo *) lfirst(j);
+
+ if (matches_any_index(arinfo, rel, outer_relids))
+ return true;
+ }
}
else
{
+ /* Recurse to examine simple clause */
Assert(IsA(orarg, RestrictInfo));
Assert(!restriction_is_or_clause((RestrictInfo *) orarg));
if (matches_any_index((RestrictInfo *) orarg, rel,
- outer_relids))
+ outer_relids))
return true;
}
}
- }
-
- return false;
-}
-/*
- * matches_any_index
- * Workhorse for indexable_outerrelids: see if a simple joinclause can be
- * matched to any index of the given rel.
- */
-static bool
-matches_any_index(RestrictInfo *rinfo, RelOptInfo *rel, Relids outer_relids)
-{
- ListCell *l;
+ return false;
+ }
/* Normal case for a simple restriction clause */
foreach(l, rel->indexlist)
{
List *clause_list = NIL;
bool jfound = false;
- int numsources;
+ Relids join_relids;
ListCell *l;
/*
clause_list = lappend(clause_list, rinfo);
}
- /* found anything in base restrict list? */
- numsources = (clause_list != NIL) ? 1 : 0;
-
/* Look for joinclauses that are usable with given outer_relids */
+ join_relids = bms_union(rel->relids, outer_relids);
+
foreach(l, rel->joininfo)
{
- JoinInfo *joininfo = (JoinInfo *) lfirst(l);
- bool jfoundhere = false;
- ListCell *j;
+ RestrictInfo *rinfo = (RestrictInfo *) lfirst(l);
- if (!bms_is_subset(joininfo->unjoined_relids, outer_relids))
+ /* Can't use pushed-down clauses in outer join */
+ if (isouterjoin && rinfo->is_pushed_down)
+ continue;
+ if (!bms_is_subset(rinfo->required_relids, join_relids))
continue;
- foreach(j, joininfo->jinfo_restrictinfo)
- {
- RestrictInfo *rinfo = (RestrictInfo *) lfirst(j);
-
- /* Can't use pushed-down clauses in outer join */
- if (isouterjoin && rinfo->is_pushed_down)
- continue;
-
- clause_list = lappend(clause_list, rinfo);
- if (!jfoundhere)
- {
- jfoundhere = true;
- jfound = true;
- numsources++;
- }
- }
+ clause_list = lappend(clause_list, rinfo);
+ jfound = true;
}
+ bms_free(join_relids);
+
/* if no join clause was matched then forget it, per comments above */
if (!jfound)
return NIL;
/*
- * If we found clauses in more than one list, we may now have
- * clauses that are known redundant. Get rid of 'em.
+ * We may now have clauses that are known redundant. Get rid of 'em.
*/
- if (numsources > 1)
+ if (list_length(clause_list) > 1)
{
clause_list = remove_redundant_join_clauses(root,
clause_list,
{
resultquals = lappend(resultquals,
make_restrictinfo(boolqual,
- true, true));
+ true, true,
+ NULL));
continue;
}
}
elog(ERROR, "no = operator for opclass %u", opclass);
expr = make_opclause(oproid, BOOLOID, false,
(Expr *) leftop, (Expr *) prefix_const);
- result = list_make1(make_restrictinfo(expr, true, true));
+ result = list_make1(make_restrictinfo(expr, true, true, NULL));
return result;
}
elog(ERROR, "no >= operator for opclass %u", opclass);
expr = make_opclause(oproid, BOOLOID, false,
(Expr *) leftop, (Expr *) prefix_const);
- result = list_make1(make_restrictinfo(expr, true, true));
+ result = list_make1(make_restrictinfo(expr, true, true, NULL));
/*-------
* If we can create a string larger than the prefix, we can say
elog(ERROR, "no < operator for opclass %u", opclass);
expr = make_opclause(oproid, BOOLOID, false,
(Expr *) leftop, (Expr *) greaterstr);
- result = lappend(result, make_restrictinfo(expr, true, true));
+ result = lappend(result, make_restrictinfo(expr, true, true, NULL));
}
return result;
(Expr *) leftop,
(Expr *) makeConst(datatype, -1, opr1right,
false, false));
- result = list_make1(make_restrictinfo(expr, true, true));
+ result = list_make1(make_restrictinfo(expr, true, true, NULL));
/* create clause "key <= network_scan_last( rightop )" */
(Expr *) leftop,
(Expr *) makeConst(datatype, -1, opr2right,
false, false));
- result = lappend(result, make_restrictinfo(expr, true, true));
+ result = lappend(result, make_restrictinfo(expr, true, true, NULL));
return result;
}
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/path/joinrels.c,v 1.73 2005/06/05 22:32:55 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/path/joinrels.c,v 1.74 2005/06/09 04:18:59 tgl Exp $
*
*-------------------------------------------------------------------------
*/
#include "postgres.h"
+#include "optimizer/joininfo.h"
#include "optimizer/pathnode.h"
#include "optimizer/paths.h"
if (!bms_overlap(old_rel->relids, new_rel->relids))
{
- ListCell *i;
-
/*
* OK, we can build a rel of the right level from this
* pair of rels. Do so if there is at least one
* usable join clause.
*/
- foreach(i, old_rel->joininfo)
+ if (have_relevant_joinclause(old_rel, new_rel))
{
- JoinInfo *joininfo = (JoinInfo *) lfirst(i);
-
- if (bms_is_subset(joininfo->unjoined_relids,
- new_rel->relids))
- {
- RelOptInfo *jrel;
-
- jrel = make_join_rel(root, old_rel, new_rel,
- JOIN_INNER);
- /* Avoid making duplicate entries ... */
- if (jrel && !list_member_ptr(result_rels, jrel))
- result_rels = lcons(jrel, result_rels);
- break; /* need not consider more
- * joininfos */
- }
+ RelOptInfo *jrel;
+
+ jrel = make_join_rel(root, old_rel, new_rel,
+ JOIN_INNER);
+ /* Avoid making duplicate entries ... */
+ if (jrel && !list_member_ptr(result_rels, jrel))
+ result_rels = lcons(jrel, result_rels);
}
}
}
/*
* make_rels_by_clause_joins
* Build joins between the given relation 'old_rel' and other relations
- * that are mentioned within old_rel's joininfo nodes (i.e., relations
+ * that are mentioned within old_rel's joininfo list (i.e., relations
* that participate in join clauses that 'old_rel' also participates in).
* The join rel nodes are returned in a list.
*
* rels to be considered for joining
*
* Currently, this is only used with initial rels in other_rels, but it
- * will work for joining to joinrels too, if the caller ensures there is no
- * membership overlap between old_rel and the rels in other_rels. (We need
- * no extra test for overlap for initial rels, since the is_subset test can
- * only succeed when other_rel is not already part of old_rel.)
+ * will work for joining to joinrels too.
*/
static List *
make_rels_by_clause_joins(PlannerInfo *root,
ListCell *other_rels)
{
List *result = NIL;
- ListCell *i,
- *j;
+ ListCell *l;
- foreach(i, old_rel->joininfo)
+ for_each_cell(l, other_rels)
{
- JoinInfo *joininfo = (JoinInfo *) lfirst(i);
- Relids unjoined_relids = joininfo->unjoined_relids;
+ RelOptInfo *other_rel = (RelOptInfo *) lfirst(l);
- for_each_cell(j, other_rels)
+ if (!bms_overlap(old_rel->relids, other_rel->relids) &&
+ have_relevant_joinclause(old_rel, other_rel))
{
- RelOptInfo *other_rel = (RelOptInfo *) lfirst(j);
-
- if (bms_is_subset(unjoined_relids, other_rel->relids))
- {
- RelOptInfo *jrel;
-
- jrel = make_join_rel(root, old_rel, other_rel, JOIN_INNER);
+ RelOptInfo *jrel;
- /*
- * Avoid entering same joinrel into our output list more
- * than once.
- */
- if (jrel && !list_member_ptr(result, jrel))
- result = lcons(jrel, result);
- }
+ jrel = make_join_rel(root, old_rel, other_rel, JOIN_INNER);
+ if (jrel)
+ result = lcons(jrel, result);
}
}
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/path/orindxpath.c,v 1.71 2005/06/05 22:32:55 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/path/orindxpath.c,v 1.72 2005/06/09 04:18:59 tgl Exp $
*
*-------------------------------------------------------------------------
*/
*/
foreach(i, rel->joininfo)
{
- JoinInfo *joininfo = (JoinInfo *) lfirst(i);
- ListCell *j;
+ RestrictInfo *rinfo = (RestrictInfo *) lfirst(i);
- foreach(j, joininfo->jinfo_restrictinfo)
+ if (restriction_is_or_clause(rinfo) &&
+ rinfo->valid_everywhere)
{
- RestrictInfo *rinfo = (RestrictInfo *) lfirst(j);
+ /*
+ * Use the generate_bitmap_or_paths() machinery to estimate
+ * the value of each OR clause. We can use regular
+ * restriction clauses along with the OR clause contents to
+ * generate indexquals. We pass outer_relids = NULL so that
+ * sub-clauses that are actually joins will be ignored.
+ */
+ List *orpaths;
+ ListCell *k;
- if (restriction_is_or_clause(rinfo) &&
- rinfo->valid_everywhere)
- {
- /*
- * Use the generate_bitmap_or_paths() machinery to estimate
- * the value of each OR clause. We can use regular
- * restriction clauses along with the OR clause contents to
- * generate indexquals. We pass outer_relids = NULL so that
- * sub-clauses that are actually joins will be ignored.
- */
- List *orpaths;
- ListCell *k;
+ orpaths = generate_bitmap_or_paths(root, rel,
+ list_make1(rinfo),
+ rel->baserestrictinfo,
+ false, NULL);
- orpaths = generate_bitmap_or_paths(root, rel,
- list_make1(rinfo),
- rel->baserestrictinfo,
- false, NULL);
+ /* Locate the cheapest OR path */
+ foreach(k, orpaths)
+ {
+ BitmapOrPath *path = (BitmapOrPath *) lfirst(k);
- /* Locate the cheapest OR path */
- foreach(k, orpaths)
+ Assert(IsA(path, BitmapOrPath));
+ if (bestpath == NULL ||
+ path->path.total_cost < bestpath->path.total_cost)
{
- BitmapOrPath *path = (BitmapOrPath *) lfirst(k);
-
- Assert(IsA(path, BitmapOrPath));
- if (bestpath == NULL ||
- path->path.total_cost < bestpath->path.total_cost)
- {
- bestpath = path;
- bestrinfo = rinfo;
- }
+ bestpath = path;
+ bestrinfo = rinfo;
}
}
}
* Portions Copyright (c) 1994, Regents of the University of California
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/path/pathkeys.c,v 1.67 2005/06/05 22:32:55 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/path/pathkeys.c,v 1.68 2005/06/09 04:18:59 tgl Exp $
*
*-------------------------------------------------------------------------
*/
/*
* pathkeys_useful_for_merging
* Count the number of pathkeys that may be useful for mergejoins
- * above the given relation (by looking at its joininfo lists).
+ * above the given relation (by looking at its joininfo list).
*
* We consider a pathkey potentially useful if it corresponds to the merge
* ordering of either side of any joinclause for the rel. This might be
- * overoptimistic, since joinclauses that appear in different join lists
+ * overoptimistic, since joinclauses that require different other relations
* might never be usable at the same time, but trying to be exact is likely
* to be more trouble than it's worth.
*/
foreach(j, rel->joininfo)
{
- JoinInfo *joininfo = (JoinInfo *) lfirst(j);
- ListCell *k;
-
- foreach(k, joininfo->jinfo_restrictinfo)
- {
- RestrictInfo *restrictinfo = (RestrictInfo *) lfirst(k);
-
- if (restrictinfo->mergejoinoperator == InvalidOid)
- continue;
- cache_mergeclause_pathkeys(root, restrictinfo);
+ RestrictInfo *restrictinfo = (RestrictInfo *) lfirst(j);
- /*
- * We can compare canonical pathkey sublists by simple
- * pointer equality; see compare_pathkeys.
- */
- if (pathkey == restrictinfo->left_pathkey ||
- pathkey == restrictinfo->right_pathkey)
- {
- matched = true;
- break;
- }
- }
+ if (restrictinfo->mergejoinoperator == InvalidOid)
+ continue;
+ cache_mergeclause_pathkeys(root, restrictinfo);
- if (matched)
+ /*
+ * We can compare canonical pathkey sublists by simple
+ * pointer equality; see compare_pathkeys.
+ */
+ if (pathkey == restrictinfo->left_pathkey ||
+ pathkey == restrictinfo->right_pathkey)
+ {
+ matched = true;
break;
+ }
}
/*
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/plan/initsplan.c,v 1.106 2005/06/05 22:32:55 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/plan/initsplan.c,v 1.107 2005/06/09 04:18:59 tgl Exp $
*
*-------------------------------------------------------------------------
*/
/*
* distribute_quals_to_rels
* Recursively scan the query's join tree for WHERE and JOIN/ON qual
- * clauses, and add these to the appropriate RestrictInfo and JoinInfo
+ * clauses, and add these to the appropriate restrictinfo and joininfo
* lists belonging to base RelOptInfos. Also, base RelOptInfos are marked
* with outerjoinset information, to aid in proper positioning of qual
* clauses that appear above outer joins.
/*
* distribute_qual_to_rels
- * Add clause information to either the 'RestrictInfo' or 'JoinInfo' field
+ * Add clause information to either the baserestrictinfo or joininfo list
* (depending on whether the clause is a join) of each base relation
* mentioned in the clause. A RestrictInfo node is created and added to
* the appropriate list for each rel. Also, if the clause uses a
*/
restrictinfo = make_restrictinfo((Expr *) clause,
is_pushed_down,
- valid_everywhere);
+ valid_everywhere,
+ relids);
/*
* Figure out where to attach it.
/*
* If the exprs involve a single rel, we need to look at that rel's
- * baserestrictinfo list. If multiple rels, any one will have a
- * joininfo node for the rest, and we can scan any of 'em.
+ * baserestrictinfo list. If multiple rels, we can scan the joininfo
+ * list of any of 'em.
*/
if (membership == BMS_SINGLETON)
{
{
Relids other_rels;
int first_rel;
- JoinInfo *joininfo;
/* Copy relids, find and remove one member */
other_rels = bms_copy(relids);
first_rel = bms_first_member(other_rels);
+ bms_free(other_rels);
rel1 = find_base_rel(root, first_rel);
-
- /* use remaining members to find join node */
- joininfo = find_joininfo_node(rel1, other_rels);
-
- restrictlist = joininfo ? joininfo->jinfo_restrictinfo : NIL;
-
- bms_free(other_rels);
+ restrictlist = rel1->joininfo;
}
/*
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/prep/prepunion.c,v 1.122 2005/06/05 22:32:56 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/prep/prepunion.c,v 1.123 2005/06/09 04:18:59 tgl Exp $
*
*-------------------------------------------------------------------------
*/
newinfo->clause_relids = adjust_relid_set(oldinfo->clause_relids,
context->old_rt_index,
context->new_rt_index);
+ newinfo->required_relids = adjust_relid_set(oldinfo->required_relids,
+ context->old_rt_index,
+ context->new_rt_index);
newinfo->left_relids = adjust_relid_set(oldinfo->left_relids,
context->old_rt_index,
context->new_rt_index);
/*-------------------------------------------------------------------------
*
* joininfo.c
- * JoinInfo node manipulation routines
+ * joininfo list manipulation routines
*
* Portions Copyright (c) 1996-2005, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/util/joininfo.c,v 1.42 2005/06/05 22:32:56 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/util/joininfo.c,v 1.43 2005/06/09 04:19:00 tgl Exp $
*
*-------------------------------------------------------------------------
*/
/*
- * find_joininfo_node
- * Find the joininfo node within a relation entry corresponding
- * to a join between 'this_rel' and the relations in 'join_relids'.
- * If there is no such node, return NULL.
- *
- * Returns a joininfo node, or NULL.
+ * have_relevant_joinclause
+ * Detect whether there is a joinclause that can be used to join
+ * the two given relations.
*/
-JoinInfo *
-find_joininfo_node(RelOptInfo *this_rel, Relids join_relids)
+bool
+have_relevant_joinclause(RelOptInfo *rel1, RelOptInfo *rel2)
{
+ bool result = false;
+ Relids join_relids;
+ List *joininfo;
ListCell *l;
- foreach(l, this_rel->joininfo)
+ join_relids = bms_union(rel1->relids, rel2->relids);
+
+ /*
+ * We could scan either relation's joininfo list; may as well use the
+ * shorter one.
+ */
+ if (list_length(rel1->joininfo) <= list_length(rel2->joininfo))
+ joininfo = rel1->joininfo;
+ else
+ joininfo = rel2->joininfo;
+
+ foreach(l, joininfo)
{
- JoinInfo *joininfo = (JoinInfo *) lfirst(l);
+ RestrictInfo *rinfo = (RestrictInfo *) lfirst(l);
- if (bms_equal(join_relids, joininfo->unjoined_relids))
- return joininfo;
+ if (bms_is_subset(rinfo->required_relids, join_relids))
+ {
+ result = true;
+ break;
+ }
}
- return NULL;
-}
-/*
- * make_joininfo_node
- * Find the joininfo node within a relation entry corresponding
- * to a join between 'this_rel' and the relations in 'join_relids'.
- * A new node is created and added to the relation entry's joininfo
- * field if the desired one can't be found.
- *
- * Returns a joininfo node.
- */
-JoinInfo *
-make_joininfo_node(RelOptInfo *this_rel, Relids join_relids)
-{
- JoinInfo *joininfo = find_joininfo_node(this_rel, join_relids);
+ bms_free(join_relids);
- if (joininfo == NULL)
- {
- joininfo = makeNode(JoinInfo);
- joininfo->unjoined_relids = join_relids;
- joininfo->jinfo_restrictinfo = NIL;
- this_rel->joininfo = lcons(joininfo, this_rel->joininfo);
- }
- return joininfo;
+ return result;
}
/*
* add_join_clause_to_rels
- * For every relation participating in a join clause, add 'restrictinfo' to
- * the appropriate joininfo list (creating a new list and adding it to the
- * appropriate rel node if necessary).
+ * Add 'restrictinfo' to the joininfo list of each relation it requires.
*
* Note that the same copy of the restrictinfo node is linked to by all the
* lists it is in. This allows us to exploit caching of information about
Relids tmprelids;
int cur_relid;
- /* For every relid, find the joininfo, and add the proper join entries */
tmprelids = bms_copy(join_relids);
while ((cur_relid = bms_first_member(tmprelids)) >= 0)
{
- Relids unjoined_relids;
- JoinInfo *joininfo;
+ RelOptInfo *rel = find_base_rel(root, cur_relid);
- /* Get the relids not equal to the current relid */
- unjoined_relids = bms_copy(join_relids);
- unjoined_relids = bms_del_member(unjoined_relids, cur_relid);
- Assert(!bms_is_empty(unjoined_relids));
-
- /*
- * Find or make the joininfo node for this combination of rels,
- * and add the restrictinfo node to it.
- */
- joininfo = make_joininfo_node(find_base_rel(root, cur_relid),
- unjoined_relids);
- joininfo->jinfo_restrictinfo = lappend(joininfo->jinfo_restrictinfo,
- restrictinfo);
-
- /*
- * Can't bms_free(unjoined_relids) because new joininfo node may
- * link to it. We could avoid leaking memory by doing bms_copy()
- * in make_joininfo_node, but for now speed seems better.
- */
+ rel->joininfo = lappend(rel->joininfo, restrictinfo);
}
bms_free(tmprelids);
}
Relids tmprelids;
int cur_relid;
- /* For every relid, find the joininfo */
tmprelids = bms_copy(join_relids);
while ((cur_relid = bms_first_member(tmprelids)) >= 0)
{
- Relids unjoined_relids;
- JoinInfo *joininfo;
-
- /* Get the relids not equal to the current relid */
- unjoined_relids = bms_copy(join_relids);
- unjoined_relids = bms_del_member(unjoined_relids, cur_relid);
- Assert(!bms_is_empty(unjoined_relids));
-
- /*
- * Find the joininfo node for this combination of rels; it should
- * exist already, if add_join_clause_to_rels was called.
- */
- joininfo = find_joininfo_node(find_base_rel(root, cur_relid),
- unjoined_relids);
- Assert(joininfo);
+ RelOptInfo *rel = find_base_rel(root, cur_relid);
/*
* Remove the restrictinfo from the list. Pointer comparison is
* sufficient.
*/
- Assert(list_member_ptr(joininfo->jinfo_restrictinfo, restrictinfo));
- joininfo->jinfo_restrictinfo = list_delete_ptr(joininfo->jinfo_restrictinfo,
- restrictinfo);
- bms_free(unjoined_relids);
+ Assert(list_member_ptr(rel->joininfo, restrictinfo));
+ rel->joininfo = list_delete_ptr(rel->joininfo, restrictinfo);
}
bms_free(tmprelids);
}
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/util/relnode.c,v 1.69 2005/06/08 23:02:05 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/util/relnode.c,v 1.70 2005/06/09 04:19:00 tgl Exp $
*
*-------------------------------------------------------------------------
*/
*
* These routines are separate because the restriction list must be
* built afresh for each pair of input sub-relations we consider, whereas
- * the join lists need only be computed once for any join RelOptInfo.
- * The join lists are fully determined by the set of rels making up the
+ * the join list need only be computed once for any join RelOptInfo.
+ * The join list is fully determined by the set of rels making up the
* joinrel, so we should get the same results (up to ordering) from any
* candidate pair of sub-relations. But the restriction list is whatever
* is not handled in the sub-relations, so it depends on which
*
* If a join clause from an input relation refers to base rels still not
* present in the joinrel, then it is still a join clause for the joinrel;
- * we put it into an appropriate JoinInfo list for the joinrel. Otherwise,
+ * we put it into the joininfo list for the joinrel. Otherwise,
* the clause is now a restrict clause for the joined relation, and we
* return it to the caller of build_joinrel_restrictlist() to be stored in
* join paths made from this pair of sub-relations. (It will not need to
*
* build_joinrel_restrictlist() returns a list of relevant restrictinfos,
* whereas build_joinrel_joinlist() stores its results in the joinrel's
- * joininfo lists. One or the other must accept each given clause!
+ * joininfo list. One or the other must accept each given clause!
*
* NB: Formerly, we made deep(!) copies of each input RestrictInfo to pass
* up to the join relation. I believe this is no longer necessary, because
List *joininfo_list)
{
List *restrictlist = NIL;
- ListCell *xjoininfo;
+ ListCell *l;
- foreach(xjoininfo, joininfo_list)
+ foreach(l, joininfo_list)
{
- JoinInfo *joininfo = (JoinInfo *) lfirst(xjoininfo);
+ RestrictInfo *rinfo = (RestrictInfo *) lfirst(l);
- if (bms_is_subset(joininfo->unjoined_relids, joinrel->relids))
+ if (bms_is_subset(rinfo->required_relids, joinrel->relids))
{
/*
- * Clauses in this JoinInfo list become restriction clauses
- * for the joinrel, since they refer to no outside rels.
- *
- * We must copy the list to avoid disturbing the input relation,
- * but we can use a shallow copy.
+ * This clause becomes a restriction clause for the joinrel,
+ * since it refers to no outside rels. We don't bother to
+ * check for duplicates here --- build_joinrel_restrictlist
+ * will do that.
*/
- restrictlist = list_concat(restrictlist,
- list_copy(joininfo->jinfo_restrictinfo));
+ restrictlist = lappend(restrictlist, rinfo);
}
else
{
/*
- * These clauses are still join clauses at this level, so we
- * ignore them in this routine.
+ * This clause is still a join clause at this level, so we
+ * ignore it in this routine.
*/
}
}
subbuild_joinrel_joinlist(RelOptInfo *joinrel,
List *joininfo_list)
{
- ListCell *xjoininfo;
+ ListCell *l;
- foreach(xjoininfo, joininfo_list)
+ foreach(l, joininfo_list)
{
- JoinInfo *joininfo = (JoinInfo *) lfirst(xjoininfo);
- Relids new_unjoined_relids;
+ RestrictInfo *rinfo = (RestrictInfo *) lfirst(l);
- new_unjoined_relids = bms_difference(joininfo->unjoined_relids,
- joinrel->relids);
- if (bms_is_empty(new_unjoined_relids))
+ if (bms_is_subset(rinfo->required_relids, joinrel->relids))
{
/*
- * Clauses in this JoinInfo list become restriction clauses
- * for the joinrel, since they refer to no outside rels. So we
- * can ignore them in this routine.
+ * This clause becomes a restriction clause for the joinrel,
+ * since it refers to no outside rels. So we can ignore it
+ * in this routine.
*/
- bms_free(new_unjoined_relids);
}
else
{
/*
- * These clauses are still join clauses at this level, so find
- * or make the appropriate JoinInfo item for the joinrel, and
- * add the clauses to it, eliminating duplicates. (Since
- * RestrictInfo nodes are normally multiply-linked rather than
- * copied, pointer equality should be a sufficient test. If
- * two equal() nodes should happen to sneak in, no great harm
- * is done --- they'll be detected by redundant-clause testing
- * when they reach a restriction list.)
+ * This clause is still a join clause at this level, so add
+ * it to the joininfo list for the joinrel, being careful to
+ * eliminate duplicates. (Since RestrictInfo nodes are normally
+ * multiply-linked rather than copied, pointer equality should be
+ * a sufficient test. If two equal() nodes should happen to sneak
+ * in, no great harm is done --- they'll be detected by
+ * redundant-clause testing when they reach a restriction list.)
*/
- JoinInfo *new_joininfo;
-
- new_joininfo = make_joininfo_node(joinrel, new_unjoined_relids);
- new_joininfo->jinfo_restrictinfo =
- list_union_ptr(new_joininfo->jinfo_restrictinfo,
- joininfo->jinfo_restrictinfo);
+ if (!list_member_ptr(joinrel->joininfo, rinfo))
+ joinrel->joininfo = lappend(joinrel->joininfo, rinfo);
}
}
}
*
*
* IDENTIFICATION
- * $PostgreSQL: pgsql/src/backend/optimizer/util/restrictinfo.c,v 1.36 2005/06/05 22:32:56 tgl Exp $
+ * $PostgreSQL: pgsql/src/backend/optimizer/util/restrictinfo.c,v 1.37 2005/06/09 04:19:00 tgl Exp $
*
*-------------------------------------------------------------------------
*/
static RestrictInfo *make_restrictinfo_internal(Expr *clause,
Expr *orclause,
bool is_pushed_down,
- bool valid_everywhere);
+ bool valid_everywhere,
+ Relids required_relids);
static Expr *make_sub_restrictinfos(Expr *clause,
bool is_pushed_down,
bool valid_everywhere);
* Build a RestrictInfo node containing the given subexpression.
*
* The is_pushed_down and valid_everywhere flags must be supplied by the
- * caller.
+ * caller. required_relids can be NULL, in which case it defaults to the
+ * actual clause contents (i.e., clause_relids).
*
* 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 *
-make_restrictinfo(Expr *clause, bool is_pushed_down, bool valid_everywhere)
+make_restrictinfo(Expr *clause, bool is_pushed_down, bool valid_everywhere,
+ Relids required_relids)
{
/*
* If it's an OR clause, build a modified copy with RestrictInfos
Assert(!and_clause((Node *) clause));
return make_restrictinfo_internal(clause, NULL,
- is_pushed_down, valid_everywhere);
+ is_pushed_down, valid_everywhere,
+ required_relids);
}
/*
list_make1(make_restrictinfo_internal(make_orclause(withoutris),
make_orclause(withris),
is_pushed_down,
- valid_everywhere));
+ valid_everywhere,
+ NULL));
}
else if (IsA(bitmapqual, IndexPath))
{
*/
static RestrictInfo *
make_restrictinfo_internal(Expr *clause, Expr *orclause,
- bool is_pushed_down, bool valid_everywhere)
+ bool is_pushed_down, bool valid_everywhere,
+ Relids required_relids)
{
RestrictInfo *restrictinfo = makeNode(RestrictInfo);
restrictinfo->clause_relids = pull_varnos((Node *) clause);
}
+ /* required_relids defaults to clause_relids */
+ if (required_relids != NULL)
+ restrictinfo->required_relids = required_relids;
+ else
+ restrictinfo->required_relids = restrictinfo->clause_relids;
+
/*
* Fill in all the cacheable fields with "not yet set" markers. None
* of these will be computed until/unless needed. Note in particular
return (Expr *) make_restrictinfo_internal(clause,
make_orclause(orlist),
is_pushed_down,
- valid_everywhere);
+ valid_everywhere,
+ NULL);
}
else if (and_clause((Node *) clause))
{
return (Expr *) make_restrictinfo_internal(clause,
NULL,
is_pushed_down,
- valid_everywhere);
+ valid_everywhere,
+ NULL);
}
/*
* Portions Copyright (c) 1996-2005, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California
*
- * $PostgreSQL: pgsql/src/include/nodes/nodes.h,v 1.169 2005/06/05 22:32:57 tgl Exp $
+ * $PostgreSQL: pgsql/src/include/nodes/nodes.h,v 1.170 2005/06/09 04:19:00 tgl Exp $
*
*-------------------------------------------------------------------------
*/
T_UniquePath,
T_PathKeyItem,
T_RestrictInfo,
- T_JoinInfo,
T_InnerIndexscanInfo,
T_InClauseInfo,
* Portions Copyright (c) 1996-2005, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California
*
- * $PostgreSQL: pgsql/src/include/nodes/relation.h,v 1.112 2005/06/08 23:02:05 tgl Exp $
+ * $PostgreSQL: pgsql/src/include/nodes/relation.h,v 1.113 2005/06/09 04:19:00 tgl Exp $
*
*-------------------------------------------------------------------------
*/
* and joins that the relation participates in:
*
* baserestrictinfo - List of RestrictInfo nodes, containing info about
- * each qualification clause in which this relation
+ * each non-join qualification clause in which this relation
* participates (only used for base rels)
* baserestrictcost - Estimated cost of evaluating the baserestrictinfo
* clauses at a single tuple (only used for base rels)
* side of an outer join, the set of all relids
* participating in the highest such outer join; else NULL.
* Otherwise, unused.
- * joininfo - List of JoinInfo nodes, containing info about each join
- * clause in which this relation participates
+ * joininfo - List of RestrictInfo nodes, containing info about each
+ * join clause in which this relation participates
* index_outer_relids - only used for base rels; set of outer relids
* that participate in indexable joinclauses for this rel
* index_inner_paths - only used for base rels; list of InnerIndexscanInfo
* and should not be processed again at the level of {1 2 3}.) Therefore,
* the restrictinfo list in the join case appears in individual JoinPaths
* (field joinrestrictinfo), not in the parent relation. But it's OK for
- * the RelOptInfo to store the joininfo lists, because those are the same
+ * the RelOptInfo to store the joininfo list, because that is the same
* for a given rel no matter how we form it.
*
* We store baserestrictcost in the RelOptInfo (for base relations) because
* base rel) */
QualCost baserestrictcost; /* cost of evaluating the above */
Relids outerjoinset; /* set of base relids */
- List *joininfo; /* JoinInfo structures */
+ List *joininfo; /* RestrictInfo structures for join clauses
+ * involving this rel */
/* cached info about inner indexscan paths for relation: */
Relids index_outer_relids; /* other relids in indexable join
* in the baserestrictinfo list of the RelOptInfo for that base rel.
*
* If a restriction clause references more than one base rel, it will
- * appear in the JoinInfo lists of every RelOptInfo that describes a strict
- * subset of the base rels mentioned in the clause. The JoinInfo lists are
+ * appear in the joininfo list of every RelOptInfo that describes a strict
+ * subset of the base rels mentioned in the clause. The joininfo lists are
* used to drive join tree building by selecting plausible join candidates.
* The clause cannot actually be applied until we have built a join rel
* containing all the base rels it references, however.
* pushed down to a lower level than its original syntactic placement in the
* join tree would suggest. If an outer join prevents us from pushing a qual
* down to its "natural" semantic level (the level associated with just the
- * base rels used in the qual) then the qual will appear in JoinInfo lists
- * that reference more than just the base rels it actually uses. By
+ * base rels used in the qual) then we mark the qual with a "required_relids"
+ * value including more than just the base rels it actually uses. By
* pretending that the qual references all the rels appearing in the outer
* join, we prevent it from being evaluated below the outer join's joinrel.
* When we do form the outer join's joinrel, we still need to distinguish
* that appeared higher in the tree and were pushed down to the join rel
* because they used no other rels. That's what the is_pushed_down flag is
* for; it tells us that a qual came from a point above the join of the
- * specific set of base rels that it uses (or that the JoinInfo structures
- * claim it uses). A clause that originally came from WHERE will *always*
- * have its is_pushed_down flag set; a clause that came from an INNER JOIN
- * condition, but doesn't use all the rels being joined, will also have
- * is_pushed_down set because it will get attached to some lower joinrel.
+ * set of base rels listed in required_relids. A clause that originally came
+ * from WHERE will *always* have its is_pushed_down flag set; a clause that
+ * came from an INNER JOIN condition, but doesn't use all the rels being
+ * joined, will also have 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
*/
bool can_join;
- /* The set of relids (varnos) referenced in the clause: */
+ /* The set of relids (varnos) actually referenced in the clause: */
Relids clause_relids;
+ /* The set of relids required to evaluate the clause: */
+ Relids required_relids;
+
/* These fields are set for any binary opclause: */
Relids left_relids; /* relids in left side of clause */
Relids right_relids; /* relids in right side of clause */
Selectivity right_bucketsize; /* avg bucketsize of right side */
} RestrictInfo;
-/*
- * Join clause info.
- *
- * We make a list of these for each RelOptInfo, containing info about
- * all the join clauses this RelOptInfo participates in. (For this
- * purpose, a "join clause" is a WHERE clause that mentions both vars
- * belonging to this relation and vars belonging to relations not yet
- * joined to it.) We group these clauses according to the set of
- * other base relations (unjoined relations) mentioned in them.
- * There is one JoinInfo for each distinct set of unjoined_relids,
- * and its jinfo_restrictinfo lists the clause(s) that use that set
- * of other relations.
- */
-
-typedef struct JoinInfo
-{
- NodeTag type;
- Relids unjoined_relids; /* some rels not yet part of my RelOptInfo */
- List *jinfo_restrictinfo; /* relevant RestrictInfos */
-} JoinInfo;
-
/*
* Inner indexscan info.
*
* Portions Copyright (c) 1996-2005, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California
*
- * $PostgreSQL: pgsql/src/include/optimizer/joininfo.h,v 1.29 2005/06/05 22:32:58 tgl Exp $
+ * $PostgreSQL: pgsql/src/include/optimizer/joininfo.h,v 1.30 2005/06/09 04:19:00 tgl Exp $
*
*-------------------------------------------------------------------------
*/
#include "nodes/relation.h"
-extern JoinInfo *find_joininfo_node(RelOptInfo *this_rel, Relids join_relids);
-extern JoinInfo *make_joininfo_node(RelOptInfo *this_rel, Relids join_relids);
+extern bool have_relevant_joinclause(RelOptInfo *rel1, RelOptInfo *rel2);
extern void add_join_clause_to_rels(PlannerInfo *root,
RestrictInfo *restrictinfo,
* Portions Copyright (c) 1996-2005, PostgreSQL Global Development Group
* Portions Copyright (c) 1994, Regents of the University of California
*
- * $PostgreSQL: pgsql/src/include/optimizer/restrictinfo.h,v 1.30 2005/06/05 22:32:58 tgl Exp $
+ * $PostgreSQL: pgsql/src/include/optimizer/restrictinfo.h,v 1.31 2005/06/09 04:19:00 tgl Exp $
*
*-------------------------------------------------------------------------
*/
#include "nodes/relation.h"
-extern RestrictInfo *make_restrictinfo(Expr *clause, bool is_pushed_down,
- bool valid_everywhere);
+extern RestrictInfo *make_restrictinfo(Expr *clause,
+ bool is_pushed_down,
+ bool valid_everywhere,
+ Relids required_relids);
extern List *make_restrictinfo_from_bitmapqual(Path *bitmapqual,
bool is_pushed_down,
bool valid_everywhere);