OSDN Git Service

No.S-2-3の試験のPG9.1用予測結果を更新した。
[pghintplan/pg_hint_plan.git] / core-9.1.c
1 /*-------------------------------------------------------------------------
2  *
3  * core.c
4  *        Routines copied from PostgreSQL core distribution.
5  *
6  * src/backend/optimizer/path/allpaths.c
7  *     set_append_rel_pathlist()
8  *     accumulate_append_subpath()
9  *     set_dummy_rel_pathlist()
10  *     standard_join_search()
11  *
12  * src/backend/optimizer/path/joinrels.c
13  *     join_search_one_level()
14  *     make_rels_by_clause_joins()
15  *     make_rels_by_clauseless_joins()
16  *     join_is_legal()
17  *     has_join_restriction()
18  *     is_dummy_rel()
19  *     mark_dummy_rel()
20  *     restriction_is_constant_false()
21  *
22  * Portions Copyright (c) 1996-2011, PostgreSQL Global Development Group
23  * Portions Copyright (c) 1994, Regents of the University of California
24  *
25  *-------------------------------------------------------------------------
26  */
27
28 /*
29  * set_append_rel_pathlist
30  *        Build access paths for an "append relation"
31  *
32  * The passed-in rel and RTE represent the entire append relation.      The
33  * relation's contents are computed by appending together the output of
34  * the individual member relations.  Note that in the inheritance case,
35  * the first member relation is actually the same table as is mentioned in
36  * the parent RTE ... but it has a different RTE and RelOptInfo.  This is
37  * a good thing because their outputs are not the same size.
38  */
39 static void
40 set_append_rel_pathlist(PlannerInfo *root, RelOptInfo *rel,
41                                                 Index rti, RangeTblEntry *rte)
42 {
43         int                     parentRTindex = rti;
44         List       *live_childrels = NIL;
45         List       *subpaths = NIL;
46         List       *all_child_pathkeys = NIL;
47         double          parent_rows;
48         double          parent_size;
49         double     *parent_attrsizes;
50         int                     nattrs;
51         ListCell   *l;
52
53         /*
54          * Initialize to compute size estimates for whole append relation.
55          *
56          * We handle width estimates by weighting the widths of different child
57          * rels proportionally to their number of rows.  This is sensible because
58          * the use of width estimates is mainly to compute the total relation
59          * "footprint" if we have to sort or hash it.  To do this, we sum the
60          * total equivalent size (in "double" arithmetic) and then divide by the
61          * total rowcount estimate.  This is done separately for the total rel
62          * width and each attribute.
63          *
64          * Note: if you consider changing this logic, beware that child rels could
65          * have zero rows and/or width, if they were excluded by constraints.
66          */
67         parent_rows = 0;
68         parent_size = 0;
69         nattrs = rel->max_attr - rel->min_attr + 1;
70         parent_attrsizes = (double *) palloc0(nattrs * sizeof(double));
71
72         /*
73          * Generate access paths for each member relation, and pick the cheapest
74          * path for each one.
75          */
76         foreach(l, root->append_rel_list)
77         {
78                 AppendRelInfo *appinfo = (AppendRelInfo *) lfirst(l);
79                 int                     childRTindex;
80                 RangeTblEntry *childRTE;
81                 RelOptInfo *childrel;
82                 List       *childquals;
83                 Node       *childqual;
84                 ListCell   *lcp;
85                 ListCell   *parentvars;
86                 ListCell   *childvars;
87
88                 /* append_rel_list contains all append rels; ignore others */
89                 if (appinfo->parent_relid != parentRTindex)
90                         continue;
91
92                 childRTindex = appinfo->child_relid;
93                 childRTE = root->simple_rte_array[childRTindex];
94
95                 /*
96                  * The child rel's RelOptInfo was already created during
97                  * add_base_rels_to_query.
98                  */
99                 childrel = find_base_rel(root, childRTindex);
100                 Assert(childrel->reloptkind == RELOPT_OTHER_MEMBER_REL);
101
102                 /*
103                  * We have to copy the parent's targetlist and quals to the child,
104                  * with appropriate substitution of variables.  However, only the
105                  * baserestrictinfo quals are needed before we can check for
106                  * constraint exclusion; so do that first and then check to see if we
107                  * can disregard this child.
108                  *
109                  * As of 8.4, the child rel's targetlist might contain non-Var
110                  * expressions, which means that substitution into the quals could
111                  * produce opportunities for const-simplification, and perhaps even
112                  * pseudoconstant quals.  To deal with this, we strip the RestrictInfo
113                  * nodes, do the substitution, do const-simplification, and then
114                  * reconstitute the RestrictInfo layer.
115                  */
116                 childquals = get_all_actual_clauses(rel->baserestrictinfo);
117                 childquals = (List *) adjust_appendrel_attrs((Node *) childquals,
118                                                                                                          appinfo);
119                 childqual = eval_const_expressions(root, (Node *)
120                                                                                    make_ands_explicit(childquals));
121                 if (childqual && IsA(childqual, Const) &&
122                         (((Const *) childqual)->constisnull ||
123                          !DatumGetBool(((Const *) childqual)->constvalue)))
124                 {
125                         /*
126                          * Restriction reduces to constant FALSE or constant NULL after
127                          * substitution, so this child need not be scanned.
128                          */
129                         set_dummy_rel_pathlist(childrel);
130                         continue;
131                 }
132                 childquals = make_ands_implicit((Expr *) childqual);
133                 childquals = make_restrictinfos_from_actual_clauses(root,
134                                                                                                                         childquals);
135                 childrel->baserestrictinfo = childquals;
136
137                 if (relation_excluded_by_constraints(root, childrel, childRTE))
138                 {
139                         /*
140                          * This child need not be scanned, so we can omit it from the
141                          * appendrel.  Mark it with a dummy cheapest-path though, in case
142                          * best_appendrel_indexscan() looks at it later.
143                          */
144                         set_dummy_rel_pathlist(childrel);
145                         continue;
146                 }
147
148                 /*
149                  * CE failed, so finish copying/modifying targetlist and join quals.
150                  *
151                  * Note: the resulting childrel->reltargetlist may contain arbitrary
152                  * expressions, which normally would not occur in a reltargetlist.
153                  * That is okay because nothing outside of this routine will look at
154                  * the child rel's reltargetlist.  We do have to cope with the case
155                  * while constructing attr_widths estimates below, though.
156                  */
157                 childrel->joininfo = (List *)
158                         adjust_appendrel_attrs((Node *) rel->joininfo,
159                                                                    appinfo);
160                 childrel->reltargetlist = (List *)
161                         adjust_appendrel_attrs((Node *) rel->reltargetlist,
162                                                                    appinfo);
163
164                 /*
165                  * We have to make child entries in the EquivalenceClass data
166                  * structures as well.  This is needed either if the parent
167                  * participates in some eclass joins (because we will want to consider
168                  * inner-indexscan joins on the individual children) or if the parent
169                  * has useful pathkeys (because we should try to build MergeAppend
170                  * paths that produce those sort orderings).
171                  */
172                 if (rel->has_eclass_joins || has_useful_pathkeys(root, rel))
173                         add_child_rel_equivalences(root, appinfo, rel, childrel);
174                 childrel->has_eclass_joins = rel->has_eclass_joins;
175
176                 /*
177                  * Note: we could compute appropriate attr_needed data for the child's
178                  * variables, by transforming the parent's attr_needed through the
179                  * translated_vars mapping.  However, currently there's no need
180                  * because attr_needed is only examined for base relations not
181                  * otherrels.  So we just leave the child's attr_needed empty.
182                  */
183
184                 /* Remember which childrels are live, for MergeAppend logic below */
185                 live_childrels = lappend(live_childrels, childrel);
186
187                 /*
188                  * Compute the child's access paths, and add the cheapest one to the
189                  * Append path we are constructing for the parent.
190                  */
191                 set_rel_pathlist(root, childrel, childRTindex, childRTE);
192
193                 subpaths = accumulate_append_subpath(subpaths,
194                                                                                          childrel->cheapest_total_path);
195
196                 /*
197                  * Collect a list of all the available path orderings for all the
198                  * children.  We use this as a heuristic to indicate which sort
199                  * orderings we should build MergeAppend paths for.
200                  */
201                 foreach(lcp, childrel->pathlist)
202                 {
203                         Path       *childpath = (Path *) lfirst(lcp);
204                         List       *childkeys = childpath->pathkeys;
205                         ListCell   *lpk;
206                         bool            found = false;
207
208                         /* Ignore unsorted paths */
209                         if (childkeys == NIL)
210                                 continue;
211
212                         /* Have we already seen this ordering? */
213                         foreach(lpk, all_child_pathkeys)
214                         {
215                                 List       *existing_pathkeys = (List *) lfirst(lpk);
216
217                                 if (compare_pathkeys(existing_pathkeys,
218                                                                          childkeys) == PATHKEYS_EQUAL)
219                                 {
220                                         found = true;
221                                         break;
222                                 }
223                         }
224                         if (!found)
225                         {
226                                 /* No, so add it to all_child_pathkeys */
227                                 all_child_pathkeys = lappend(all_child_pathkeys, childkeys);
228                         }
229                 }
230
231                 /*
232                  * Accumulate size information from each child.
233                  */
234                 if (childrel->rows > 0)
235                 {
236                         parent_rows += childrel->rows;
237                         parent_size += childrel->width * childrel->rows;
238
239                         /*
240                          * Accumulate per-column estimates too.  We need not do anything
241                          * for PlaceHolderVars in the parent list.  If child expression
242                          * isn't a Var, or we didn't record a width estimate for it, we
243                          * have to fall back on a datatype-based estimate.
244                          *
245                          * By construction, child's reltargetlist is 1-to-1 with parent's.
246                          */
247                         forboth(parentvars, rel->reltargetlist,
248                                         childvars, childrel->reltargetlist)
249                         {
250                                 Var                *parentvar = (Var *) lfirst(parentvars);
251                                 Node       *childvar = (Node *) lfirst(childvars);
252
253                                 if (IsA(parentvar, Var))
254                                 {
255                                         int                     pndx = parentvar->varattno - rel->min_attr;
256                                         int32           child_width = 0;
257
258                                         if (IsA(childvar, Var))
259                                         {
260                                                 int             cndx = ((Var *) childvar)->varattno - childrel->min_attr;
261
262                                                 child_width = childrel->attr_widths[cndx];
263                                         }
264                                         if (child_width <= 0)
265                                                 child_width = get_typavgwidth(exprType(childvar),
266                                                                                                           exprTypmod(childvar));
267                                         Assert(child_width > 0);
268                                         parent_attrsizes[pndx] += child_width * childrel->rows;
269                                 }
270                         }
271                 }
272         }
273
274         /*
275          * Save the finished size estimates.
276          */
277         rel->rows = parent_rows;
278         if (parent_rows > 0)
279         {
280                 int                     i;
281
282                 rel->width = rint(parent_size / parent_rows);
283                 for (i = 0; i < nattrs; i++)
284                         rel->attr_widths[i] = rint(parent_attrsizes[i] / parent_rows);
285         }
286         else
287                 rel->width = 0;                 /* attr_widths should be zero already */
288
289         /*
290          * Set "raw tuples" count equal to "rows" for the appendrel; needed
291          * because some places assume rel->tuples is valid for any baserel.
292          */
293         rel->tuples = parent_rows;
294
295         pfree(parent_attrsizes);
296
297         /*
298          * Next, build an unordered Append path for the rel.  (Note: this is
299          * correct even if we have zero or one live subpath due to constraint
300          * exclusion.)
301          */
302         add_path(rel, (Path *) create_append_path(rel, subpaths));
303
304         /*
305          * Next, build MergeAppend paths based on the collected list of child
306          * pathkeys.  We consider both cheapest-startup and cheapest-total cases,
307          * ie, for each interesting ordering, collect all the cheapest startup
308          * subpaths and all the cheapest total paths, and build a MergeAppend path
309          * for each list.
310          */
311         foreach(l, all_child_pathkeys)
312         {
313                 List       *pathkeys = (List *) lfirst(l);
314                 List       *startup_subpaths = NIL;
315                 List       *total_subpaths = NIL;
316                 bool            startup_neq_total = false;
317                 ListCell   *lcr;
318
319                 /* Select the child paths for this ordering... */
320                 foreach(lcr, live_childrels)
321                 {
322                         RelOptInfo *childrel = (RelOptInfo *) lfirst(lcr);
323                         Path       *cheapest_startup,
324                                            *cheapest_total;
325
326                         /* Locate the right paths, if they are available. */
327                         cheapest_startup =
328                                 get_cheapest_path_for_pathkeys(childrel->pathlist,
329                                                                                            pathkeys,
330                                                                                            STARTUP_COST);
331                         cheapest_total =
332                                 get_cheapest_path_for_pathkeys(childrel->pathlist,
333                                                                                            pathkeys,
334                                                                                            TOTAL_COST);
335
336                         /*
337                          * If we can't find any paths with the right order just add the
338                          * cheapest-total path; we'll have to sort it.
339                          */
340                         if (cheapest_startup == NULL)
341                                 cheapest_startup = childrel->cheapest_total_path;
342                         if (cheapest_total == NULL)
343                                 cheapest_total = childrel->cheapest_total_path;
344
345                         /*
346                          * Notice whether we actually have different paths for the
347                          * "cheapest" and "total" cases; frequently there will be no point
348                          * in two create_merge_append_path() calls.
349                          */
350                         if (cheapest_startup != cheapest_total)
351                                 startup_neq_total = true;
352
353                         startup_subpaths =
354                                 accumulate_append_subpath(startup_subpaths, cheapest_startup);
355                         total_subpaths =
356                                 accumulate_append_subpath(total_subpaths, cheapest_total);
357                 }
358
359                 /* ... and build the MergeAppend paths */
360                 add_path(rel, (Path *) create_merge_append_path(root,
361                                                                                                                 rel,
362                                                                                                                 startup_subpaths,
363                                                                                                                 pathkeys));
364                 if (startup_neq_total)
365                         add_path(rel, (Path *) create_merge_append_path(root,
366                                                                                                                         rel,
367                                                                                                                         total_subpaths,
368                                                                                                                         pathkeys));
369         }
370
371         /* Select cheapest path */
372         set_cheapest(rel);
373 }
374
375 /*
376  * accumulate_append_subpath
377  *              Add a subpath to the list being built for an Append or MergeAppend
378  *
379  * It's possible that the child is itself an Append path, in which case
380  * we can "cut out the middleman" and just add its child paths to our
381  * own list.  (We don't try to do this earlier because we need to
382  * apply both levels of transformation to the quals.)
383  */
384 static List *
385 accumulate_append_subpath(List *subpaths, Path *path)
386 {
387         if (IsA(path, AppendPath))
388         {
389                 AppendPath *apath = (AppendPath *) path;
390
391                 /* list_copy is important here to avoid sharing list substructure */
392                 return list_concat(subpaths, list_copy(apath->subpaths));
393         }
394         else
395                 return lappend(subpaths, path);
396 }
397
398 /*
399  * set_dummy_rel_pathlist
400  *        Build a dummy path for a relation that's been excluded by constraints
401  *
402  * Rather than inventing a special "dummy" path type, we represent this as an
403  * AppendPath with no members (see also IS_DUMMY_PATH macro).
404  */
405 static void
406 set_dummy_rel_pathlist(RelOptInfo *rel)
407 {
408         /* Set dummy size estimates --- we leave attr_widths[] as zeroes */
409         rel->rows = 0;
410         rel->width = 0;
411
412         add_path(rel, (Path *) create_append_path(rel, NIL));
413
414         /* Select cheapest path (pretty easy in this case...) */
415         set_cheapest(rel);
416 }
417
418 /*
419  * standard_join_search
420  *        Find possible joinpaths for a query by successively finding ways
421  *        to join component relations into join relations.
422  *
423  * 'levels_needed' is the number of iterations needed, ie, the number of
424  *              independent jointree items in the query.  This is > 1.
425  *
426  * 'initial_rels' is a list of RelOptInfo nodes for each independent
427  *              jointree item.  These are the components to be joined together.
428  *              Note that levels_needed == list_length(initial_rels).
429  *
430  * Returns the final level of join relations, i.e., the relation that is
431  * the result of joining all the original relations together.
432  * At least one implementation path must be provided for this relation and
433  * all required sub-relations.
434  *
435  * To support loadable plugins that modify planner behavior by changing the
436  * join searching algorithm, we provide a hook variable that lets a plugin
437  * replace or supplement this function.  Any such hook must return the same
438  * final join relation as the standard code would, but it might have a
439  * different set of implementation paths attached, and only the sub-joinrels
440  * needed for these paths need have been instantiated.
441  *
442  * Note to plugin authors: the functions invoked during standard_join_search()
443  * modify root->join_rel_list and root->join_rel_hash.  If you want to do more
444  * than one join-order search, you'll probably need to save and restore the
445  * original states of those data structures.  See geqo_eval() for an example.
446  */
447 RelOptInfo *
448 standard_join_search(PlannerInfo *root, int levels_needed, List *initial_rels)
449 {
450         int                     lev;
451         RelOptInfo *rel;
452
453         /*
454          * This function cannot be invoked recursively within any one planning
455          * problem, so join_rel_level[] can't be in use already.
456          */
457         Assert(root->join_rel_level == NULL);
458
459         /*
460          * We employ a simple "dynamic programming" algorithm: we first find all
461          * ways to build joins of two jointree items, then all ways to build joins
462          * of three items (from two-item joins and single items), then four-item
463          * joins, and so on until we have considered all ways to join all the
464          * items into one rel.
465          *
466          * root->join_rel_level[j] is a list of all the j-item rels.  Initially we
467          * set root->join_rel_level[1] to represent all the single-jointree-item
468          * relations.
469          */
470         root->join_rel_level = (List **) palloc0((levels_needed + 1) * sizeof(List *));
471
472         root->join_rel_level[1] = initial_rels;
473
474         for (lev = 2; lev <= levels_needed; lev++)
475         {
476                 ListCell   *lc;
477
478                 /*
479                  * Determine all possible pairs of relations to be joined at this
480                  * level, and build paths for making each one from every available
481                  * pair of lower-level relations.
482                  */
483                 join_search_one_level(root, lev);
484
485                 /*
486                  * Do cleanup work on each just-processed rel.
487                  */
488                 foreach(lc, root->join_rel_level[lev])
489                 {
490                         rel = (RelOptInfo *) lfirst(lc);
491
492                         /* Find and save the cheapest paths for this rel */
493                         set_cheapest(rel);
494
495 #ifdef OPTIMIZER_DEBUG
496                         debug_print_rel(root, rel);
497 #endif
498                 }
499         }
500
501         /*
502          * We should have a single rel at the final level.
503          */
504         if (root->join_rel_level[levels_needed] == NIL)
505                 elog(ERROR, "failed to build any %d-way joins", levels_needed);
506         Assert(list_length(root->join_rel_level[levels_needed]) == 1);
507
508         rel = (RelOptInfo *) linitial(root->join_rel_level[levels_needed]);
509
510         root->join_rel_level = NULL;
511
512         return rel;
513 }
514
515 /*
516  * join_search_one_level
517  *        Consider ways to produce join relations containing exactly 'level'
518  *        jointree items.  (This is one step of the dynamic-programming method
519  *        embodied in standard_join_search.)  Join rel nodes for each feasible
520  *        combination of lower-level rels are created and returned in a list.
521  *        Implementation paths are created for each such joinrel, too.
522  *
523  * level: level of rels we want to make this time
524  * root->join_rel_level[j], 1 <= j < level, is a list of rels containing j items
525  *
526  * The result is returned in root->join_rel_level[level].
527  */
528 void
529 join_search_one_level(PlannerInfo *root, int level)
530 {
531         List      **joinrels = root->join_rel_level;
532         ListCell   *r;
533         int                     k;
534
535         Assert(joinrels[level] == NIL);
536
537         /* Set join_cur_level so that new joinrels are added to proper list */
538         root->join_cur_level = level;
539
540         /*
541          * First, consider left-sided and right-sided plans, in which rels of
542          * exactly level-1 member relations are joined against initial relations.
543          * We prefer to join using join clauses, but if we find a rel of level-1
544          * members that has no join clauses, we will generate Cartesian-product
545          * joins against all initial rels not already contained in it.
546          *
547          * In the first pass (level == 2), we try to join each initial rel to each
548          * initial rel that appears later in joinrels[1].  (The mirror-image joins
549          * are handled automatically by make_join_rel.)  In later passes, we try
550          * to join rels of size level-1 from joinrels[level-1] to each initial rel
551          * in joinrels[1].
552          */
553         foreach(r, joinrels[level - 1])
554         {
555                 RelOptInfo *old_rel = (RelOptInfo *) lfirst(r);
556                 ListCell   *other_rels;
557
558                 if (level == 2)
559                         other_rels = lnext(r);          /* only consider remaining initial
560                                                                                  * rels */
561                 else
562                         other_rels = list_head(joinrels[1]);            /* consider all initial
563                                                                                                                  * rels */
564
565                 if (old_rel->joininfo != NIL || old_rel->has_eclass_joins ||
566                         has_join_restriction(root, old_rel))
567                 {
568                         /*
569                          * Note that if all available join clauses for this rel require
570                          * more than one other rel, we will fail to make any joins against
571                          * it here.  In most cases that's OK; it'll be considered by
572                          * "bushy plan" join code in a higher-level pass where we have
573                          * those other rels collected into a join rel.
574                          *
575                          * See also the last-ditch case below.
576                          */
577                         make_rels_by_clause_joins(root,
578                                                                           old_rel,
579                                                                           other_rels);
580                 }
581                 else
582                 {
583                         /*
584                          * Oops, we have a relation that is not joined to any other
585                          * relation, either directly or by join-order restrictions.
586                          * Cartesian product time.
587                          */
588                         make_rels_by_clauseless_joins(root,
589                                                                                   old_rel,
590                                                                                   other_rels);
591                 }
592         }
593
594         /*
595          * Now, consider "bushy plans" in which relations of k initial rels are
596          * joined to relations of level-k initial rels, for 2 <= k <= level-2.
597          *
598          * We only consider bushy-plan joins for pairs of rels where there is a
599          * suitable join clause (or join order restriction), in order to avoid
600          * unreasonable growth of planning time.
601          */
602         for (k = 2;; k++)
603         {
604                 int                     other_level = level - k;
605
606                 /*
607                  * Since make_join_rel(x, y) handles both x,y and y,x cases, we only
608                  * need to go as far as the halfway point.
609                  */
610                 if (k > other_level)
611                         break;
612
613                 foreach(r, joinrels[k])
614                 {
615                         RelOptInfo *old_rel = (RelOptInfo *) lfirst(r);
616                         ListCell   *other_rels;
617                         ListCell   *r2;
618
619                         /*
620                          * We can ignore clauseless joins here, *except* when they
621                          * participate in join-order restrictions --- then we might have
622                          * to force a bushy join plan.
623                          */
624                         if (old_rel->joininfo == NIL && !old_rel->has_eclass_joins &&
625                                 !has_join_restriction(root, old_rel))
626                                 continue;
627
628                         if (k == other_level)
629                                 other_rels = lnext(r);  /* only consider remaining rels */
630                         else
631                                 other_rels = list_head(joinrels[other_level]);
632
633                         for_each_cell(r2, other_rels)
634                         {
635                                 RelOptInfo *new_rel = (RelOptInfo *) lfirst(r2);
636
637                                 if (!bms_overlap(old_rel->relids, new_rel->relids))
638                                 {
639                                         /*
640                                          * OK, we can build a rel of the right level from this
641                                          * pair of rels.  Do so if there is at least one usable
642                                          * join clause or a relevant join restriction.
643                                          */
644                                         if (have_relevant_joinclause(root, old_rel, new_rel) ||
645                                                 have_join_order_restriction(root, old_rel, new_rel))
646                                         {
647                                                 (void) make_join_rel(root, old_rel, new_rel);
648                                         }
649                                 }
650                         }
651                 }
652         }
653
654         /*
655          * Last-ditch effort: if we failed to find any usable joins so far, force
656          * a set of cartesian-product joins to be generated.  This handles the
657          * special case where all the available rels have join clauses but we
658          * cannot use any of those clauses yet.  An example is
659          *
660          * SELECT * FROM a,b,c WHERE (a.f1 + b.f2 + c.f3) = 0;
661          *
662          * The join clause will be usable at level 3, but at level 2 we have no
663          * choice but to make cartesian joins.  We consider only left-sided and
664          * right-sided cartesian joins in this case (no bushy).
665          */
666         if (joinrels[level] == NIL)
667         {
668                 /*
669                  * This loop is just like the first one, except we always call
670                  * make_rels_by_clauseless_joins().
671                  */
672                 foreach(r, joinrels[level - 1])
673                 {
674                         RelOptInfo *old_rel = (RelOptInfo *) lfirst(r);
675                         ListCell   *other_rels;
676
677                         if (level == 2)
678                                 other_rels = lnext(r);  /* only consider remaining initial
679                                                                                  * rels */
680                         else
681                                 other_rels = list_head(joinrels[1]);    /* consider all initial
682                                                                                                                  * rels */
683
684                         make_rels_by_clauseless_joins(root,
685                                                                                   old_rel,
686                                                                                   other_rels);
687                 }
688
689                 /*----------
690                  * When special joins are involved, there may be no legal way
691                  * to make an N-way join for some values of N.  For example consider
692                  *
693                  * SELECT ... FROM t1 WHERE
694                  *       x IN (SELECT ... FROM t2,t3 WHERE ...) AND
695                  *       y IN (SELECT ... FROM t4,t5 WHERE ...)
696                  *
697                  * We will flatten this query to a 5-way join problem, but there are
698                  * no 4-way joins that join_is_legal() will consider legal.  We have
699                  * to accept failure at level 4 and go on to discover a workable
700                  * bushy plan at level 5.
701                  *
702                  * However, if there are no special joins then join_is_legal() should
703                  * never fail, and so the following sanity check is useful.
704                  *----------
705                  */
706                 if (joinrels[level] == NIL && root->join_info_list == NIL)
707                         elog(ERROR, "failed to build any %d-way joins", level);
708         }
709 }
710
711 /*
712  * make_rels_by_clause_joins
713  *        Build joins between the given relation 'old_rel' and other relations
714  *        that participate in join clauses that 'old_rel' also participates in
715  *        (or participate in join-order restrictions with it).
716  *        The join rels are returned in root->join_rel_level[join_cur_level].
717  *
718  * Note: at levels above 2 we will generate the same joined relation in
719  * multiple ways --- for example (a join b) join c is the same RelOptInfo as
720  * (b join c) join a, though the second case will add a different set of Paths
721  * to it.  This is the reason for using the join_rel_level mechanism, which
722  * automatically ensures that each new joinrel is only added to the list once.
723  *
724  * 'old_rel' is the relation entry for the relation to be joined
725  * 'other_rels': the first cell in a linked list containing the other
726  * rels to be considered for joining
727  *
728  * Currently, this is only used with initial rels in other_rels, but it
729  * will work for joining to joinrels too.
730  */
731 static void
732 make_rels_by_clause_joins(PlannerInfo *root,
733                                                   RelOptInfo *old_rel,
734                                                   ListCell *other_rels)
735 {
736         ListCell   *l;
737
738         for_each_cell(l, other_rels)
739         {
740                 RelOptInfo *other_rel = (RelOptInfo *) lfirst(l);
741
742                 if (!bms_overlap(old_rel->relids, other_rel->relids) &&
743                         (have_relevant_joinclause(root, old_rel, other_rel) ||
744                          have_join_order_restriction(root, old_rel, other_rel)))
745                 {
746                         (void) make_join_rel(root, old_rel, other_rel);
747                 }
748         }
749 }
750
751 /*
752  * make_rels_by_clauseless_joins
753  *        Given a relation 'old_rel' and a list of other relations
754  *        'other_rels', create a join relation between 'old_rel' and each
755  *        member of 'other_rels' that isn't already included in 'old_rel'.
756  *        The join rels are returned in root->join_rel_level[join_cur_level].
757  *
758  * 'old_rel' is the relation entry for the relation to be joined
759  * 'other_rels': the first cell of a linked list containing the
760  * other rels to be considered for joining
761  *
762  * Currently, this is only used with initial rels in other_rels, but it would
763  * work for joining to joinrels too.
764  */
765 static void
766 make_rels_by_clauseless_joins(PlannerInfo *root,
767                                                           RelOptInfo *old_rel,
768                                                           ListCell *other_rels)
769 {
770         ListCell   *l;
771
772         for_each_cell(l, other_rels)
773         {
774                 RelOptInfo *other_rel = (RelOptInfo *) lfirst(l);
775
776                 if (!bms_overlap(other_rel->relids, old_rel->relids))
777                 {
778                         (void) make_join_rel(root, old_rel, other_rel);
779                 }
780         }
781 }
782
783 /*
784  * join_is_legal
785  *         Determine whether a proposed join is legal given the query's
786  *         join order constraints; and if it is, determine the join type.
787  *
788  * Caller must supply not only the two rels, but the union of their relids.
789  * (We could simplify the API by computing joinrelids locally, but this
790  * would be redundant work in the normal path through make_join_rel.)
791  *
792  * On success, *sjinfo_p is set to NULL if this is to be a plain inner join,
793  * else it's set to point to the associated SpecialJoinInfo node.  Also,
794  * *reversed_p is set TRUE if the given relations need to be swapped to
795  * match the SpecialJoinInfo node.
796  */
797 static bool
798 join_is_legal(PlannerInfo *root, RelOptInfo *rel1, RelOptInfo *rel2,
799                           Relids joinrelids,
800                           SpecialJoinInfo **sjinfo_p, bool *reversed_p)
801 {
802         SpecialJoinInfo *match_sjinfo;
803         bool            reversed;
804         bool            unique_ified;
805         bool            is_valid_inner;
806         ListCell   *l;
807
808         /*
809          * Ensure output params are set on failure return.      This is just to
810          * suppress uninitialized-variable warnings from overly anal compilers.
811          */
812         *sjinfo_p = NULL;
813         *reversed_p = false;
814
815         /*
816          * If we have any special joins, the proposed join might be illegal; and
817          * in any case we have to determine its join type.      Scan the join info
818          * list for conflicts.
819          */
820         match_sjinfo = NULL;
821         reversed = false;
822         unique_ified = false;
823         is_valid_inner = true;
824
825         foreach(l, root->join_info_list)
826         {
827                 SpecialJoinInfo *sjinfo = (SpecialJoinInfo *) lfirst(l);
828
829                 /*
830                  * This special join is not relevant unless its RHS overlaps the
831                  * proposed join.  (Check this first as a fast path for dismissing
832                  * most irrelevant SJs quickly.)
833                  */
834                 if (!bms_overlap(sjinfo->min_righthand, joinrelids))
835                         continue;
836
837                 /*
838                  * Also, not relevant if proposed join is fully contained within RHS
839                  * (ie, we're still building up the RHS).
840                  */
841                 if (bms_is_subset(joinrelids, sjinfo->min_righthand))
842                         continue;
843
844                 /*
845                  * Also, not relevant if SJ is already done within either input.
846                  */
847                 if (bms_is_subset(sjinfo->min_lefthand, rel1->relids) &&
848                         bms_is_subset(sjinfo->min_righthand, rel1->relids))
849                         continue;
850                 if (bms_is_subset(sjinfo->min_lefthand, rel2->relids) &&
851                         bms_is_subset(sjinfo->min_righthand, rel2->relids))
852                         continue;
853
854                 /*
855                  * If it's a semijoin and we already joined the RHS to any other rels
856                  * within either input, then we must have unique-ified the RHS at that
857                  * point (see below).  Therefore the semijoin is no longer relevant in
858                  * this join path.
859                  */
860                 if (sjinfo->jointype == JOIN_SEMI)
861                 {
862                         if (bms_is_subset(sjinfo->syn_righthand, rel1->relids) &&
863                                 !bms_equal(sjinfo->syn_righthand, rel1->relids))
864                                 continue;
865                         if (bms_is_subset(sjinfo->syn_righthand, rel2->relids) &&
866                                 !bms_equal(sjinfo->syn_righthand, rel2->relids))
867                                 continue;
868                 }
869
870                 /*
871                  * If one input contains min_lefthand and the other contains
872                  * min_righthand, then we can perform the SJ at this join.
873                  *
874                  * Barf if we get matches to more than one SJ (is that possible?)
875                  */
876                 if (bms_is_subset(sjinfo->min_lefthand, rel1->relids) &&
877                         bms_is_subset(sjinfo->min_righthand, rel2->relids))
878                 {
879                         if (match_sjinfo)
880                                 return false;   /* invalid join path */
881                         match_sjinfo = sjinfo;
882                         reversed = false;
883                 }
884                 else if (bms_is_subset(sjinfo->min_lefthand, rel2->relids) &&
885                                  bms_is_subset(sjinfo->min_righthand, rel1->relids))
886                 {
887                         if (match_sjinfo)
888                                 return false;   /* invalid join path */
889                         match_sjinfo = sjinfo;
890                         reversed = true;
891                 }
892                 else if (sjinfo->jointype == JOIN_SEMI &&
893                                  bms_equal(sjinfo->syn_righthand, rel2->relids) &&
894                                  create_unique_path(root, rel2, rel2->cheapest_total_path,
895                                                                         sjinfo) != NULL)
896                 {
897                         /*----------
898                          * For a semijoin, we can join the RHS to anything else by
899                          * unique-ifying the RHS (if the RHS can be unique-ified).
900                          * We will only get here if we have the full RHS but less
901                          * than min_lefthand on the LHS.
902                          *
903                          * The reason to consider such a join path is exemplified by
904                          *      SELECT ... FROM a,b WHERE (a.x,b.y) IN (SELECT c1,c2 FROM c)
905                          * If we insist on doing this as a semijoin we will first have
906                          * to form the cartesian product of A*B.  But if we unique-ify
907                          * C then the semijoin becomes a plain innerjoin and we can join
908                          * in any order, eg C to A and then to B.  When C is much smaller
909                          * than A and B this can be a huge win.  So we allow C to be
910                          * joined to just A or just B here, and then make_join_rel has
911                          * to handle the case properly.
912                          *
913                          * Note that actually we'll allow unique-ified C to be joined to
914                          * some other relation D here, too.  That is legal, if usually not
915                          * very sane, and this routine is only concerned with legality not
916                          * with whether the join is good strategy.
917                          *----------
918                          */
919                         if (match_sjinfo)
920                                 return false;   /* invalid join path */
921                         match_sjinfo = sjinfo;
922                         reversed = false;
923                         unique_ified = true;
924                 }
925                 else if (sjinfo->jointype == JOIN_SEMI &&
926                                  bms_equal(sjinfo->syn_righthand, rel1->relids) &&
927                                  create_unique_path(root, rel1, rel1->cheapest_total_path,
928                                                                         sjinfo) != NULL)
929                 {
930                         /* Reversed semijoin case */
931                         if (match_sjinfo)
932                                 return false;   /* invalid join path */
933                         match_sjinfo = sjinfo;
934                         reversed = true;
935                         unique_ified = true;
936                 }
937                 else
938                 {
939                         /*----------
940                          * Otherwise, the proposed join overlaps the RHS but isn't
941                          * a valid implementation of this SJ.  It might still be
942                          * a legal join, however.  If both inputs overlap the RHS,
943                          * assume that it's OK.  Since the inputs presumably got past
944                          * this function's checks previously, they can't overlap the
945                          * LHS and their violations of the RHS boundary must represent
946                          * SJs that have been determined to commute with this one.
947                          * We have to allow this to work correctly in cases like
948                          *              (a LEFT JOIN (b JOIN (c LEFT JOIN d)))
949                          * when the c/d join has been determined to commute with the join
950                          * to a, and hence d is not part of min_righthand for the upper
951                          * join.  It should be legal to join b to c/d but this will appear
952                          * as a violation of the upper join's RHS.
953                          * Furthermore, if one input overlaps the RHS and the other does
954                          * not, we should still allow the join if it is a valid
955                          * implementation of some other SJ.  We have to allow this to
956                          * support the associative identity
957                          *              (a LJ b on Pab) LJ c ON Pbc = a LJ (b LJ c ON Pbc) on Pab
958                          * since joining B directly to C violates the lower SJ's RHS.
959                          * We assume that make_outerjoininfo() set things up correctly
960                          * so that we'll only match to some SJ if the join is valid.
961                          * Set flag here to check at bottom of loop.
962                          *----------
963                          */
964                         if (sjinfo->jointype != JOIN_SEMI &&
965                                 bms_overlap(rel1->relids, sjinfo->min_righthand) &&
966                                 bms_overlap(rel2->relids, sjinfo->min_righthand))
967                         {
968                                 /* seems OK */
969                                 Assert(!bms_overlap(joinrelids, sjinfo->min_lefthand));
970                         }
971                         else
972                                 is_valid_inner = false;
973                 }
974         }
975
976         /*
977          * Fail if violated some SJ's RHS and didn't match to another SJ. However,
978          * "matching" to a semijoin we are implementing by unique-ification
979          * doesn't count (think: it's really an inner join).
980          */
981         if (!is_valid_inner &&
982                 (match_sjinfo == NULL || unique_ified))
983                 return false;                   /* invalid join path */
984
985         /* Otherwise, it's a valid join */
986         *sjinfo_p = match_sjinfo;
987         *reversed_p = reversed;
988         return true;
989 }
990
991 /*
992  * has_join_restriction
993  *              Detect whether the specified relation has join-order restrictions
994  *              due to being inside an outer join or an IN (sub-SELECT).
995  *
996  * Essentially, this tests whether have_join_order_restriction() could
997  * succeed with this rel and some other one.  It's OK if we sometimes
998  * say "true" incorrectly.      (Therefore, we don't bother with the relatively
999  * expensive has_legal_joinclause test.)
1000  */
1001 static bool
1002 has_join_restriction(PlannerInfo *root, RelOptInfo *rel)
1003 {
1004         ListCell   *l;
1005
1006         foreach(l, root->join_info_list)
1007         {
1008                 SpecialJoinInfo *sjinfo = (SpecialJoinInfo *) lfirst(l);
1009
1010                 /* ignore full joins --- other mechanisms preserve their ordering */
1011                 if (sjinfo->jointype == JOIN_FULL)
1012                         continue;
1013
1014                 /* ignore if SJ is already contained in rel */
1015                 if (bms_is_subset(sjinfo->min_lefthand, rel->relids) &&
1016                         bms_is_subset(sjinfo->min_righthand, rel->relids))
1017                         continue;
1018
1019                 /* restricted if it overlaps LHS or RHS, but doesn't contain SJ */
1020                 if (bms_overlap(sjinfo->min_lefthand, rel->relids) ||
1021                         bms_overlap(sjinfo->min_righthand, rel->relids))
1022                         return true;
1023         }
1024
1025         return false;
1026 }
1027
1028 /*
1029  * is_dummy_rel --- has relation been proven empty?
1030  *
1031  * If so, it will have a single path that is dummy.
1032  */
1033 static bool
1034 is_dummy_rel(RelOptInfo *rel)
1035 {
1036         return (rel->cheapest_total_path != NULL &&
1037                         IS_DUMMY_PATH(rel->cheapest_total_path));
1038 }
1039
1040 /*
1041  * Mark a relation as proven empty.
1042  *
1043  * During GEQO planning, this can get invoked more than once on the same
1044  * baserel struct, so it's worth checking to see if the rel is already marked
1045  * dummy.
1046  *
1047  * Also, when called during GEQO join planning, we are in a short-lived
1048  * memory context.      We must make sure that the dummy path attached to a
1049  * baserel survives the GEQO cycle, else the baserel is trashed for future
1050  * GEQO cycles.  On the other hand, when we are marking a joinrel during GEQO,
1051  * we don't want the dummy path to clutter the main planning context.  Upshot
1052  * is that the best solution is to explicitly make the dummy path in the same
1053  * context the given RelOptInfo is in.
1054  */
1055 static void
1056 mark_dummy_rel(RelOptInfo *rel)
1057 {
1058         MemoryContext oldcontext;
1059
1060         /* Already marked? */
1061         if (is_dummy_rel(rel))
1062                 return;
1063
1064         /* No, so choose correct context to make the dummy path in */
1065         oldcontext = MemoryContextSwitchTo(GetMemoryChunkContext(rel));
1066
1067         /* Set dummy size estimate */
1068         rel->rows = 0;
1069
1070         /* Evict any previously chosen paths */
1071         rel->pathlist = NIL;
1072
1073         /* Set up the dummy path */
1074         add_path(rel, (Path *) create_append_path(rel, NIL));
1075
1076         /* Set or update cheapest_total_path */
1077         set_cheapest(rel);
1078
1079         MemoryContextSwitchTo(oldcontext);
1080 }
1081
1082 /*
1083  * restriction_is_constant_false --- is a restrictlist just FALSE?
1084  *
1085  * In cases where a qual is provably constant FALSE, eval_const_expressions
1086  * will generally have thrown away anything that's ANDed with it.  In outer
1087  * join situations this will leave us computing cartesian products only to
1088  * decide there's no match for an outer row, which is pretty stupid.  So,
1089  * we need to detect the case.
1090  *
1091  * If only_pushed_down is TRUE, then consider only pushed-down quals.
1092  */
1093 static bool
1094 restriction_is_constant_false(List *restrictlist, bool only_pushed_down)
1095 {
1096         ListCell   *lc;
1097
1098         /*
1099          * Despite the above comment, the restriction list we see here might
1100          * possibly have other members besides the FALSE constant, since other
1101          * quals could get "pushed down" to the outer join level.  So we check
1102          * each member of the list.
1103          */
1104         foreach(lc, restrictlist)
1105         {
1106                 RestrictInfo *rinfo = (RestrictInfo *) lfirst(lc);
1107
1108                 Assert(IsA(rinfo, RestrictInfo));
1109                 if (only_pushed_down && !rinfo->is_pushed_down)
1110                         continue;
1111
1112                 if (rinfo->clause && IsA(rinfo->clause, Const))
1113                 {
1114                         Const      *con = (Const *) rinfo->clause;
1115
1116                         /* constant NULL is as good as constant FALSE for our purposes */
1117                         if (con->constisnull)
1118                                 return true;
1119                         if (!DatumGetBool(con->constvalue))
1120                                 return true;
1121                 }
1122         }
1123         return false;
1124 }