]> granicus.if.org Git - postgresql/blob - src/backend/optimizer/plan/planner.c
Make the behavior of HAVING without GROUP BY conform to the SQL spec.
[postgresql] / src / backend / optimizer / plan / planner.c
1 /*-------------------------------------------------------------------------
2  *
3  * planner.c
4  *        The query optimizer external interface.
5  *
6  * Portions Copyright (c) 1996-2005, PostgreSQL Global Development Group
7  * Portions Copyright (c) 1994, Regents of the University of California
8  *
9  *
10  * IDENTIFICATION
11  *        $PostgreSQL: pgsql/src/backend/optimizer/plan/planner.c,v 1.179 2005/03/10 23:21:22 tgl Exp $
12  *
13  *-------------------------------------------------------------------------
14  */
15
16 #include "postgres.h"
17
18 #include <limits.h>
19
20 #include "catalog/pg_operator.h"
21 #include "catalog/pg_type.h"
22 #include "executor/executor.h"
23 #include "executor/nodeAgg.h"
24 #include "miscadmin.h"
25 #include "nodes/makefuncs.h"
26 #ifdef OPTIMIZER_DEBUG
27 #include "nodes/print.h"
28 #endif
29 #include "optimizer/clauses.h"
30 #include "optimizer/cost.h"
31 #include "optimizer/pathnode.h"
32 #include "optimizer/paths.h"
33 #include "optimizer/planmain.h"
34 #include "optimizer/planner.h"
35 #include "optimizer/prep.h"
36 #include "optimizer/subselect.h"
37 #include "optimizer/tlist.h"
38 #include "optimizer/var.h"
39 #include "parser/analyze.h"
40 #include "parser/parsetree.h"
41 #include "parser/parse_expr.h"
42 #include "parser/parse_oper.h"
43 #include "utils/selfuncs.h"
44 #include "utils/syscache.h"
45
46
47 ParamListInfo PlannerBoundParamList = NULL;             /* current boundParams */
48
49
50 /* Expression kind codes for preprocess_expression */
51 #define EXPRKIND_QUAL   0
52 #define EXPRKIND_TARGET 1
53 #define EXPRKIND_RTFUNC 2
54 #define EXPRKIND_LIMIT  3
55 #define EXPRKIND_ININFO 4
56
57
58 static Node *preprocess_expression(Query *parse, Node *expr, int kind);
59 static void preprocess_qual_conditions(Query *parse, Node *jtnode);
60 static Plan *inheritance_planner(Query *parse, List *inheritlist);
61 static Plan *grouping_planner(Query *parse, double tuple_fraction);
62 static bool hash_safe_grouping(Query *parse);
63 static List *make_subplanTargetList(Query *parse, List *tlist,
64                                            AttrNumber **groupColIdx, bool *need_tlist_eval);
65 static void locate_grouping_columns(Query *parse,
66                                                 List *tlist,
67                                                 List *sub_tlist,
68                                                 AttrNumber *groupColIdx);
69 static List *postprocess_setop_tlist(List *new_tlist, List *orig_tlist);
70
71
72 /*****************************************************************************
73  *
74  *         Query optimizer entry point
75  *
76  *****************************************************************************/
77 Plan *
78 planner(Query *parse, bool isCursor, int cursorOptions,
79                 ParamListInfo boundParams)
80 {
81         double          tuple_fraction;
82         Plan       *result_plan;
83         Index           save_PlannerQueryLevel;
84         List       *save_PlannerParamList;
85         ParamListInfo save_PlannerBoundParamList;
86
87         /*
88          * The planner can be called recursively (an example is when
89          * eval_const_expressions tries to pre-evaluate an SQL function). So,
90          * these global state variables must be saved and restored.
91          *
92          * Query level and the param list cannot be moved into the Query
93          * structure since their whole purpose is communication across
94          * multiple sub-Queries. Also, boundParams is explicitly info from
95          * outside the Query, and so is likewise better handled as a global
96          * variable.
97          *
98          * Note we do NOT save and restore PlannerPlanId: it exists to assign
99          * unique IDs to SubPlan nodes, and we want those IDs to be unique for
100          * the life of a backend.  Also, PlannerInitPlan is saved/restored in
101          * subquery_planner, not here.
102          */
103         save_PlannerQueryLevel = PlannerQueryLevel;
104         save_PlannerParamList = PlannerParamList;
105         save_PlannerBoundParamList = PlannerBoundParamList;
106
107         /* Initialize state for handling outer-level references and params */
108         PlannerQueryLevel = 0;          /* will be 1 in top-level subquery_planner */
109         PlannerParamList = NIL;
110         PlannerBoundParamList = boundParams;
111
112         /* Determine what fraction of the plan is likely to be scanned */
113         if (isCursor)
114         {
115                 /*
116                  * We have no real idea how many tuples the user will ultimately
117                  * FETCH from a cursor, but it seems a good bet that he doesn't
118                  * want 'em all.  Optimize for 10% retrieval (you gotta better
119                  * number?      Should this be a SETtable parameter?)
120                  */
121                 tuple_fraction = 0.10;
122         }
123         else
124         {
125                 /* Default assumption is we need all the tuples */
126                 tuple_fraction = 0.0;
127         }
128
129         /* primary planning entry point (may recurse for subqueries) */
130         result_plan = subquery_planner(parse, tuple_fraction);
131
132         Assert(PlannerQueryLevel == 0);
133
134         /*
135          * If creating a plan for a scrollable cursor, make sure it can run
136          * backwards on demand.  Add a Material node at the top at need.
137          */
138         if (isCursor && (cursorOptions & CURSOR_OPT_SCROLL))
139         {
140                 if (!ExecSupportsBackwardScan(result_plan))
141                         result_plan = materialize_finished_plan(result_plan);
142         }
143
144         /* executor wants to know total number of Params used overall */
145         result_plan->nParamExec = list_length(PlannerParamList);
146
147         /* final cleanup of the plan */
148         set_plan_references(result_plan, parse->rtable);
149
150         /* restore state for outer planner, if any */
151         PlannerQueryLevel = save_PlannerQueryLevel;
152         PlannerParamList = save_PlannerParamList;
153         PlannerBoundParamList = save_PlannerBoundParamList;
154
155         return result_plan;
156 }
157
158
159 /*--------------------
160  * subquery_planner
161  *        Invokes the planner on a subquery.  We recurse to here for each
162  *        sub-SELECT found in the query tree.
163  *
164  * parse is the querytree produced by the parser & rewriter.
165  * tuple_fraction is the fraction of tuples we expect will be retrieved.
166  * tuple_fraction is interpreted as explained for grouping_planner, below.
167  *
168  * Basically, this routine does the stuff that should only be done once
169  * per Query object.  It then calls grouping_planner.  At one time,
170  * grouping_planner could be invoked recursively on the same Query object;
171  * that's not currently true, but we keep the separation between the two
172  * routines anyway, in case we need it again someday.
173  *
174  * subquery_planner will be called recursively to handle sub-Query nodes
175  * found within the query's expressions and rangetable.
176  *
177  * Returns a query plan.
178  *--------------------
179  */
180 Plan *
181 subquery_planner(Query *parse, double tuple_fraction)
182 {
183         List       *saved_initplan = PlannerInitPlan;
184         int                     saved_planid = PlannerPlanId;
185         bool            hasOuterJoins;
186         Plan       *plan;
187         List       *newHaving;
188         List       *lst;
189         ListCell   *l;
190
191         /* Set up for a new level of subquery */
192         PlannerQueryLevel++;
193         PlannerInitPlan = NIL;
194
195         /*
196          * Look for IN clauses at the top level of WHERE, and transform them
197          * into joins.  Note that this step only handles IN clauses originally
198          * at top level of WHERE; if we pull up any subqueries in the next
199          * step, their INs are processed just before pulling them up.
200          */
201         parse->in_info_list = NIL;
202         if (parse->hasSubLinks)
203                 parse->jointree->quals = pull_up_IN_clauses(parse,
204                                                                                                  parse->jointree->quals);
205
206         /*
207          * Check to see if any subqueries in the rangetable can be merged into
208          * this query.
209          */
210         parse->jointree = (FromExpr *)
211                 pull_up_subqueries(parse, (Node *) parse->jointree, false);
212
213         /*
214          * Detect whether any rangetable entries are RTE_JOIN kind; if not, we
215          * can avoid the expense of doing flatten_join_alias_vars().  Also
216          * check for outer joins --- if none, we can skip
217          * reduce_outer_joins(). This must be done after we have done
218          * pull_up_subqueries, of course.
219          */
220         parse->hasJoinRTEs = false;
221         hasOuterJoins = false;
222         foreach(l, parse->rtable)
223         {
224                 RangeTblEntry *rte = (RangeTblEntry *) lfirst(l);
225
226                 if (rte->rtekind == RTE_JOIN)
227                 {
228                         parse->hasJoinRTEs = true;
229                         if (IS_OUTER_JOIN(rte->jointype))
230                         {
231                                 hasOuterJoins = true;
232                                 /* Can quit scanning once we find an outer join */
233                                 break;
234                         }
235                 }
236         }
237
238         /*
239          * Set hasHavingQual to remember if HAVING clause is present.  Needed
240          * because preprocess_expression will reduce a constant-true condition
241          * to an empty qual list ... but "HAVING TRUE" is not a semantic no-op.
242          */
243         parse->hasHavingQual = (parse->havingQual != NULL);
244
245         /*
246          * Do expression preprocessing on targetlist and quals.
247          */
248         parse->targetList = (List *)
249                 preprocess_expression(parse, (Node *) parse->targetList,
250                                                           EXPRKIND_TARGET);
251
252         preprocess_qual_conditions(parse, (Node *) parse->jointree);
253
254         parse->havingQual = preprocess_expression(parse, parse->havingQual,
255                                                                                           EXPRKIND_QUAL);
256
257         parse->limitOffset = preprocess_expression(parse, parse->limitOffset,
258                                                                                            EXPRKIND_LIMIT);
259         parse->limitCount = preprocess_expression(parse, parse->limitCount,
260                                                                                           EXPRKIND_LIMIT);
261
262         parse->in_info_list = (List *)
263                 preprocess_expression(parse, (Node *) parse->in_info_list,
264                                                           EXPRKIND_ININFO);
265
266         /* Also need to preprocess expressions for function RTEs */
267         foreach(l, parse->rtable)
268         {
269                 RangeTblEntry *rte = (RangeTblEntry *) lfirst(l);
270
271                 if (rte->rtekind == RTE_FUNCTION)
272                         rte->funcexpr = preprocess_expression(parse, rte->funcexpr,
273                                                                                                   EXPRKIND_RTFUNC);
274         }
275
276         /*
277          * In some cases we may want to transfer a HAVING clause into WHERE.
278          * We cannot do so if the HAVING clause contains aggregates (obviously)
279          * or volatile functions (since a HAVING clause is supposed to be executed
280          * only once per group).  Also, it may be that the clause is so expensive
281          * to execute that we're better off doing it only once per group, despite
282          * the loss of selectivity.  This is hard to estimate short of doing the
283          * entire planning process twice, so we use a heuristic: clauses
284          * containing subplans are left in HAVING.  Otherwise, we move or copy
285          * the HAVING clause into WHERE, in hopes of eliminating tuples before
286          * aggregation instead of after.
287          *
288          * If the query has explicit grouping then we can simply move such a
289          * clause into WHERE; any group that fails the clause will not be
290          * in the output because none of its tuples will reach the grouping
291          * or aggregation stage.  Otherwise we must have a degenerate
292          * (variable-free) HAVING clause, which we put in WHERE so that
293          * query_planner() can use it in a gating Result node, but also keep
294          * in HAVING to ensure that we don't emit a bogus aggregated row.
295          * (This could be done better, but it seems not worth optimizing.)
296          *
297          * Note that both havingQual and parse->jointree->quals are in
298          * implicitly-ANDed-list form at this point, even though they are
299          * declared as Node *.
300          */
301         newHaving = NIL;
302         foreach(l, (List *) parse->havingQual)
303         {
304                 Node       *havingclause = (Node *) lfirst(l);
305
306                 if (contain_agg_clause(havingclause) ||
307                         contain_volatile_functions(havingclause) ||
308                         contain_subplans(havingclause))
309                 {
310                         /* keep it in HAVING */
311                         newHaving = lappend(newHaving, havingclause);
312                 }
313                 else if (parse->groupClause)
314                 {
315                         /* move it to WHERE */
316                         parse->jointree->quals = (Node *)
317                                 lappend((List *) parse->jointree->quals, havingclause);
318                 }
319                 else
320                 {
321                         /* put a copy in WHERE, keep it in HAVING */
322                         parse->jointree->quals = (Node *)
323                                 lappend((List *) parse->jointree->quals,
324                                                 copyObject(havingclause));
325                         newHaving = lappend(newHaving, havingclause);
326                 }
327         }
328         parse->havingQual = (Node *) newHaving;
329
330         /*
331          * If we have any outer joins, try to reduce them to plain inner
332          * joins. This step is most easily done after we've done expression
333          * preprocessing.
334          */
335         if (hasOuterJoins)
336                 reduce_outer_joins(parse);
337
338         /*
339          * See if we can simplify the jointree; opportunities for this may
340          * come from having pulled up subqueries, or from flattening explicit
341          * JOIN syntax.  We must do this after flattening JOIN alias
342          * variables, since eliminating explicit JOIN nodes from the jointree
343          * will cause get_relids_for_join() to fail.  But it should happen
344          * after reduce_outer_joins, anyway.
345          */
346         parse->jointree = (FromExpr *)
347                 simplify_jointree(parse, (Node *) parse->jointree);
348
349         /*
350          * Do the main planning.  If we have an inherited target relation,
351          * that needs special processing, else go straight to
352          * grouping_planner.
353          */
354         if (parse->resultRelation &&
355                 (lst = expand_inherited_rtentry(parse, parse->resultRelation)) != NIL)
356                 plan = inheritance_planner(parse, lst);
357         else
358                 plan = grouping_planner(parse, tuple_fraction);
359
360         /*
361          * If any subplans were generated, or if we're inside a subplan, build
362          * initPlan list and extParam/allParam sets for plan nodes.
363          */
364         if (PlannerPlanId != saved_planid || PlannerQueryLevel > 1)
365         {
366                 Cost            initplan_cost = 0;
367
368                 /* Prepare extParam/allParam sets for all nodes in tree */
369                 SS_finalize_plan(plan, parse->rtable);
370
371                 /*
372                  * SS_finalize_plan doesn't handle initPlans, so we have to
373                  * manually attach them to the topmost plan node, and add their
374                  * extParams to the topmost node's, too.
375                  *
376                  * We also add the total_cost of each initPlan to the startup cost of
377                  * the top node.  This is a conservative overestimate, since in
378                  * fact each initPlan might be executed later than plan startup,
379                  * or even not at all.
380                  */
381                 plan->initPlan = PlannerInitPlan;
382
383                 foreach(l, plan->initPlan)
384                 {
385                         SubPlan    *initplan = (SubPlan *) lfirst(l);
386
387                         plan->extParam = bms_add_members(plan->extParam,
388                                                                                          initplan->plan->extParam);
389                         /* allParam must include all members of extParam */
390                         plan->allParam = bms_add_members(plan->allParam,
391                                                                                          plan->extParam);
392                         initplan_cost += initplan->plan->total_cost;
393                 }
394
395                 plan->startup_cost += initplan_cost;
396                 plan->total_cost += initplan_cost;
397         }
398
399         /* Return to outer subquery context */
400         PlannerQueryLevel--;
401         PlannerInitPlan = saved_initplan;
402         /* we do NOT restore PlannerPlanId; that's not an oversight! */
403
404         return plan;
405 }
406
407 /*
408  * preprocess_expression
409  *              Do subquery_planner's preprocessing work for an expression,
410  *              which can be a targetlist, a WHERE clause (including JOIN/ON
411  *              conditions), or a HAVING clause.
412  */
413 static Node *
414 preprocess_expression(Query *parse, Node *expr, int kind)
415 {
416         /*
417          * If the query has any join RTEs, replace join alias variables with
418          * base-relation variables. We must do this before sublink processing,
419          * else sublinks expanded out from join aliases wouldn't get
420          * processed.
421          */
422         if (parse->hasJoinRTEs)
423                 expr = flatten_join_alias_vars(parse, expr);
424
425         /*
426          * If it's a qual or havingQual, canonicalize it.  It seems most
427          * useful to do this before applying eval_const_expressions, since the
428          * latter can optimize flattened AND/ORs better than unflattened ones.
429          *
430          * Note: all processing of a qual expression after this point must be
431          * careful to maintain AND/OR flatness --- that is, do not generate a
432          * tree with AND directly under AND, nor OR directly under OR.
433          */
434         if (kind == EXPRKIND_QUAL)
435         {
436                 expr = (Node *) canonicalize_qual((Expr *) expr);
437
438 #ifdef OPTIMIZER_DEBUG
439                 printf("After canonicalize_qual()\n");
440                 pprint(expr);
441 #endif
442         }
443
444         /*
445          * Simplify constant expressions.
446          */
447         expr = eval_const_expressions(expr);
448
449         /* Expand SubLinks to SubPlans */
450         if (parse->hasSubLinks)
451                 expr = SS_process_sublinks(expr, (kind == EXPRKIND_QUAL));
452
453         /*
454          * XXX do not insert anything here unless you have grokked the
455          * comments in SS_replace_correlation_vars ...
456          */
457
458         /* Replace uplevel vars with Param nodes */
459         if (PlannerQueryLevel > 1)
460                 expr = SS_replace_correlation_vars(expr);
461
462         /*
463          * If it's a qual or havingQual, convert it to implicit-AND format.
464          * (We don't want to do this before eval_const_expressions, since the
465          * latter would be unable to simplify a top-level AND correctly. Also,
466          * SS_process_sublinks expects explicit-AND format.)
467          */
468         if (kind == EXPRKIND_QUAL)
469                 expr = (Node *) make_ands_implicit((Expr *) expr);
470
471         return expr;
472 }
473
474 /*
475  * preprocess_qual_conditions
476  *              Recursively scan the query's jointree and do subquery_planner's
477  *              preprocessing work on each qual condition found therein.
478  */
479 static void
480 preprocess_qual_conditions(Query *parse, Node *jtnode)
481 {
482         if (jtnode == NULL)
483                 return;
484         if (IsA(jtnode, RangeTblRef))
485         {
486                 /* nothing to do here */
487         }
488         else if (IsA(jtnode, FromExpr))
489         {
490                 FromExpr   *f = (FromExpr *) jtnode;
491                 ListCell   *l;
492
493                 foreach(l, f->fromlist)
494                         preprocess_qual_conditions(parse, lfirst(l));
495
496                 f->quals = preprocess_expression(parse, f->quals, EXPRKIND_QUAL);
497         }
498         else if (IsA(jtnode, JoinExpr))
499         {
500                 JoinExpr   *j = (JoinExpr *) jtnode;
501
502                 preprocess_qual_conditions(parse, j->larg);
503                 preprocess_qual_conditions(parse, j->rarg);
504
505                 j->quals = preprocess_expression(parse, j->quals, EXPRKIND_QUAL);
506         }
507         else
508                 elog(ERROR, "unrecognized node type: %d",
509                          (int) nodeTag(jtnode));
510 }
511
512 /*--------------------
513  * inheritance_planner
514  *        Generate a plan in the case where the result relation is an
515  *        inheritance set.
516  *
517  * We have to handle this case differently from cases where a source
518  * relation is an inheritance set.      Source inheritance is expanded at
519  * the bottom of the plan tree (see allpaths.c), but target inheritance
520  * has to be expanded at the top.  The reason is that for UPDATE, each
521  * target relation needs a different targetlist matching its own column
522  * set.  (This is not so critical for DELETE, but for simplicity we treat
523  * inherited DELETE the same way.)      Fortunately, the UPDATE/DELETE target
524  * can never be the nullable side of an outer join, so it's OK to generate
525  * the plan this way.
526  *
527  * parse is the querytree produced by the parser & rewriter.
528  * inheritlist is an integer list of RT indexes for the result relation set.
529  *
530  * Returns a query plan.
531  *--------------------
532  */
533 static Plan *
534 inheritance_planner(Query *parse, List *inheritlist)
535 {
536         int                     parentRTindex = parse->resultRelation;
537         Oid                     parentOID = getrelid(parentRTindex, parse->rtable);
538         int                     mainrtlength = list_length(parse->rtable);
539         List       *subplans = NIL;
540         List       *tlist = NIL;
541         ListCell   *l;
542
543         foreach(l, inheritlist)
544         {
545                 int                     childRTindex = lfirst_int(l);
546                 Oid                     childOID = getrelid(childRTindex, parse->rtable);
547                 Query      *subquery;
548                 Plan       *subplan;
549
550                 /* Generate modified query with this rel as target */
551                 subquery = (Query *) adjust_inherited_attrs((Node *) parse,
552                                                                                                 parentRTindex, parentOID,
553                                                                                                  childRTindex, childOID);
554                 /* Generate plan */
555                 subplan = grouping_planner(subquery, 0.0 /* retrieve all tuples */ );
556                 subplans = lappend(subplans, subplan);
557
558                 /*
559                  * XXX my goodness this next bit is ugly.  Really need to think about
560                  * ways to rein in planner's habit of scribbling on its input.
561                  *
562                  * Planning of the subquery might have modified the rangetable,
563                  * either by addition of RTEs due to expansion of inherited source
564                  * tables, or by changes of the Query structures inside subquery
565                  * RTEs.  We have to ensure that this gets propagated back to the
566                  * master copy.  However, if we aren't done planning yet, we also
567                  * need to ensure that subsequent calls to grouping_planner have
568                  * virgin sub-Queries to work from.  So, if we are at the last
569                  * list entry, just copy the subquery rangetable back to the master
570                  * copy; if we are not, then extend the master copy by adding
571                  * whatever the subquery added.  (We assume these added entries
572                  * will go untouched by the future grouping_planner calls.  We are
573                  * also effectively assuming that sub-Queries will get planned
574                  * identically each time, or at least that the impacts on their
575                  * rangetables will be the same each time.  Did I say this is ugly?)
576                  */
577                 if (lnext(l) == NULL)
578                         parse->rtable = subquery->rtable;
579                 else
580                 {
581                         int             subrtlength = list_length(subquery->rtable);
582
583                         if (subrtlength > mainrtlength)
584                         {
585                                 List       *subrt;
586
587                                 subrt = list_copy_tail(subquery->rtable, mainrtlength);
588                                 parse->rtable = list_concat(parse->rtable, subrt);
589                                 mainrtlength = subrtlength;
590                         }
591                 }
592
593                 /* Save preprocessed tlist from first rel for use in Append */
594                 if (tlist == NIL)
595                         tlist = subplan->targetlist;
596         }
597
598         /* Save the target-relations list for the executor, too */
599         parse->resultRelations = inheritlist;
600
601         /* Mark result as unordered (probably unnecessary) */
602         parse->query_pathkeys = NIL;
603
604         return (Plan *) make_append(subplans, true, tlist);
605 }
606
607 /*--------------------
608  * grouping_planner
609  *        Perform planning steps related to grouping, aggregation, etc.
610  *        This primarily means adding top-level processing to the basic
611  *        query plan produced by query_planner.
612  *
613  * parse is the querytree produced by the parser & rewriter.
614  * tuple_fraction is the fraction of tuples we expect will be retrieved
615  *
616  * tuple_fraction is interpreted as follows:
617  *        0: expect all tuples to be retrieved (normal case)
618  *        0 < tuple_fraction < 1: expect the given fraction of tuples available
619  *              from the plan to be retrieved
620  *        tuple_fraction >= 1: tuple_fraction is the absolute number of tuples
621  *              expected to be retrieved (ie, a LIMIT specification)
622  *
623  * Returns a query plan.  Also, parse->query_pathkeys is returned as the
624  * actual output ordering of the plan (in pathkey format).
625  *--------------------
626  */
627 static Plan *
628 grouping_planner(Query *parse, double tuple_fraction)
629 {
630         List       *tlist = parse->targetList;
631         Plan       *result_plan;
632         List       *current_pathkeys;
633         List       *sort_pathkeys;
634
635         if (parse->setOperations)
636         {
637                 List       *set_sortclauses;
638
639                 /*
640                  * Construct the plan for set operations.  The result will not
641                  * need any work except perhaps a top-level sort and/or LIMIT.
642                  */
643                 result_plan = plan_set_operations(parse,
644                                                                                   &set_sortclauses);
645
646                 /*
647                  * Calculate pathkeys representing the sort order (if any) of the
648                  * set operation's result.  We have to do this before overwriting
649                  * the sort key information...
650                  */
651                 current_pathkeys = make_pathkeys_for_sortclauses(set_sortclauses,
652                                                                                                 result_plan->targetlist);
653                 current_pathkeys = canonicalize_pathkeys(parse, current_pathkeys);
654
655                 /*
656                  * We should not need to call preprocess_targetlist, since we must
657                  * be in a SELECT query node.  Instead, use the targetlist
658                  * returned by plan_set_operations (since this tells whether it
659                  * returned any resjunk columns!), and transfer any sort key
660                  * information from the original tlist.
661                  */
662                 Assert(parse->commandType == CMD_SELECT);
663
664                 tlist = postprocess_setop_tlist(result_plan->targetlist, tlist);
665
666                 /*
667                  * Can't handle FOR UPDATE here (parser should have checked
668                  * already, but let's make sure).
669                  */
670                 if (parse->rowMarks)
671                         ereport(ERROR,
672                                         (errcode(ERRCODE_FEATURE_NOT_SUPPORTED),
673                                          errmsg("SELECT FOR UPDATE is not allowed with UNION/INTERSECT/EXCEPT")));
674
675                 /*
676                  * Calculate pathkeys that represent result ordering requirements
677                  */
678                 sort_pathkeys = make_pathkeys_for_sortclauses(parse->sortClause,
679                                                                                                           tlist);
680                 sort_pathkeys = canonicalize_pathkeys(parse, sort_pathkeys);
681         }
682         else
683         {
684                 /* No set operations, do regular planning */
685                 List       *sub_tlist;
686                 List       *group_pathkeys;
687                 AttrNumber *groupColIdx = NULL;
688                 bool            need_tlist_eval = true;
689                 QualCost        tlist_cost;
690                 double          sub_tuple_fraction;
691                 Path       *cheapest_path;
692                 Path       *sorted_path;
693                 double          dNumGroups = 0;
694                 long            numGroups = 0;
695                 AggClauseCounts agg_counts;
696                 int                     numGroupCols = list_length(parse->groupClause);
697                 bool            use_hashed_grouping = false;
698
699                 MemSet(&agg_counts, 0, sizeof(AggClauseCounts));
700
701                 /* Preprocess targetlist in case we are inside an INSERT/UPDATE. */
702                 tlist = preprocess_targetlist(tlist,
703                                                                           parse->commandType,
704                                                                           parse->resultRelation,
705                                                                           parse->rtable);
706
707                 /*
708                  * Add TID targets for rels selected FOR UPDATE (should this be
709                  * done in preprocess_targetlist?).  The executor uses the TID to
710                  * know which rows to lock, much as for UPDATE or DELETE.
711                  */
712                 if (parse->rowMarks)
713                 {
714                         ListCell   *l;
715
716                         /*
717                          * We've got trouble if the FOR UPDATE appears inside
718                          * grouping, since grouping renders a reference to individual
719                          * tuple CTIDs invalid.  This is also checked at parse time,
720                          * but that's insufficient because of rule substitution, query
721                          * pullup, etc.
722                          */
723                         CheckSelectForUpdate(parse);
724
725                         /*
726                          * Currently the executor only supports FOR UPDATE at top
727                          * level
728                          */
729                         if (PlannerQueryLevel > 1)
730                                 ereport(ERROR,
731                                                 (errcode(ERRCODE_FEATURE_NOT_SUPPORTED),
732                                                  errmsg("SELECT FOR UPDATE is not allowed in subqueries")));
733
734                         foreach(l, parse->rowMarks)
735                         {
736                                 Index           rti = lfirst_int(l);
737                                 char       *resname;
738                                 Resdom     *resdom;
739                                 Var                *var;
740                                 TargetEntry *ctid;
741
742                                 resname = (char *) palloc(32);
743                                 snprintf(resname, 32, "ctid%u", rti);
744                                 resdom = makeResdom(list_length(tlist) + 1,
745                                                                         TIDOID,
746                                                                         -1,
747                                                                         resname,
748                                                                         true);
749
750                                 var = makeVar(rti,
751                                                           SelfItemPointerAttributeNumber,
752                                                           TIDOID,
753                                                           -1,
754                                                           0);
755
756                                 ctid = makeTargetEntry(resdom, (Expr *) var);
757                                 tlist = lappend(tlist, ctid);
758                         }
759                 }
760
761                 /*
762                  * Generate appropriate target list for subplan; may be different
763                  * from tlist if grouping or aggregation is needed.
764                  */
765                 sub_tlist = make_subplanTargetList(parse, tlist,
766                                                                                  &groupColIdx, &need_tlist_eval);
767
768                 /*
769                  * Calculate pathkeys that represent grouping/ordering
770                  * requirements
771                  */
772                 group_pathkeys = make_pathkeys_for_sortclauses(parse->groupClause,
773                                                                                                            tlist);
774                 sort_pathkeys = make_pathkeys_for_sortclauses(parse->sortClause,
775                                                                                                           tlist);
776
777                 /*
778                  * Will need actual number of aggregates for estimating costs.
779                  *
780                  * Note: we do not attempt to detect duplicate aggregates here; a
781                  * somewhat-overestimated count is okay for our present purposes.
782                  *
783                  * Note: think not that we can turn off hasAggs if we find no aggs.
784                  * It is possible for constant-expression simplification to remove
785                  * all explicit references to aggs, but we still have to follow
786                  * the aggregate semantics (eg, producing only one output row).
787                  */
788                 if (parse->hasAggs)
789                 {
790                         count_agg_clauses((Node *) tlist, &agg_counts);
791                         count_agg_clauses(parse->havingQual, &agg_counts);
792                 }
793
794                 /*
795                  * Figure out whether we need a sorted result from query_planner.
796                  *
797                  * If we have a GROUP BY clause, then we want a result sorted
798                  * properly for grouping.  Otherwise, if there is an ORDER BY
799                  * clause, we want to sort by the ORDER BY clause.      (Note: if we
800                  * have both, and ORDER BY is a superset of GROUP BY, it would be
801                  * tempting to request sort by ORDER BY --- but that might just
802                  * leave us failing to exploit an available sort order at all.
803                  * Needs more thought...)
804                  */
805                 if (parse->groupClause)
806                         parse->query_pathkeys = group_pathkeys;
807                 else if (parse->sortClause)
808                         parse->query_pathkeys = sort_pathkeys;
809                 else
810                         parse->query_pathkeys = NIL;
811
812                 /*
813                  * Adjust tuple_fraction if we see that we are going to apply
814                  * limiting/grouping/aggregation/etc.  This is not overridable by
815                  * the caller, since it reflects plan actions that this routine
816                  * will certainly take, not assumptions about context.
817                  */
818                 if (parse->limitCount != NULL)
819                 {
820                         /*
821                          * A LIMIT clause limits the absolute number of tuples
822                          * returned. However, if it's not a constant LIMIT then we
823                          * have to punt; for lack of a better idea, assume 10% of the
824                          * plan's result is wanted.
825                          */
826                         double          limit_fraction = 0.0;
827
828                         if (IsA(parse->limitCount, Const))
829                         {
830                                 Const      *limitc = (Const *) parse->limitCount;
831                                 int32           count = DatumGetInt32(limitc->constvalue);
832
833                                 /*
834                                  * A NULL-constant LIMIT represents "LIMIT ALL", which we
835                                  * treat the same as no limit (ie, expect to retrieve all
836                                  * the tuples).
837                                  */
838                                 if (!limitc->constisnull && count > 0)
839                                 {
840                                         limit_fraction = (double) count;
841                                         /* We must also consider the OFFSET, if present */
842                                         if (parse->limitOffset != NULL)
843                                         {
844                                                 if (IsA(parse->limitOffset, Const))
845                                                 {
846                                                         int32           offset;
847
848                                                         limitc = (Const *) parse->limitOffset;
849                                                         offset = DatumGetInt32(limitc->constvalue);
850                                                         if (!limitc->constisnull && offset > 0)
851                                                                 limit_fraction += (double) offset;
852                                                 }
853                                                 else
854                                                 {
855                                                         /* OFFSET is an expression ... punt ... */
856                                                         limit_fraction = 0.10;
857                                                 }
858                                         }
859                                 }
860                         }
861                         else
862                         {
863                                 /* LIMIT is an expression ... punt ... */
864                                 limit_fraction = 0.10;
865                         }
866
867                         if (limit_fraction > 0.0)
868                         {
869                                 /*
870                                  * If we have absolute limits from both caller and LIMIT,
871                                  * use the smaller value; if one is fractional and the
872                                  * other absolute, treat the fraction as a fraction of the
873                                  * absolute value; else we can multiply the two fractions
874                                  * together.
875                                  */
876                                 if (tuple_fraction >= 1.0)
877                                 {
878                                         if (limit_fraction >= 1.0)
879                                         {
880                                                 /* both absolute */
881                                                 tuple_fraction = Min(tuple_fraction, limit_fraction);
882                                         }
883                                         else
884                                         {
885                                                 /* caller absolute, limit fractional */
886                                                 tuple_fraction *= limit_fraction;
887                                                 if (tuple_fraction < 1.0)
888                                                         tuple_fraction = 1.0;
889                                         }
890                                 }
891                                 else if (tuple_fraction > 0.0)
892                                 {
893                                         if (limit_fraction >= 1.0)
894                                         {
895                                                 /* caller fractional, limit absolute */
896                                                 tuple_fraction *= limit_fraction;
897                                                 if (tuple_fraction < 1.0)
898                                                         tuple_fraction = 1.0;
899                                         }
900                                         else
901                                         {
902                                                 /* both fractional */
903                                                 tuple_fraction *= limit_fraction;
904                                         }
905                                 }
906                                 else
907                                 {
908                                         /* no info from caller, just use limit */
909                                         tuple_fraction = limit_fraction;
910                                 }
911                         }
912                 }
913
914                 /*
915                  * With grouping or aggregation, the tuple fraction to pass to
916                  * query_planner() may be different from what it is at top level.
917                  */
918                 sub_tuple_fraction = tuple_fraction;
919
920                 if (parse->groupClause)
921                 {
922                         /*
923                          * In GROUP BY mode, we have the little problem that we don't
924                          * really know how many input tuples will be needed to make a
925                          * group, so we can't translate an output LIMIT count into an
926                          * input count.  For lack of a better idea, assume 25% of the
927                          * input data will be processed if there is any output limit.
928                          * However, if the caller gave us a fraction rather than an
929                          * absolute count, we can keep using that fraction (which
930                          * amounts to assuming that all the groups are about the same
931                          * size).
932                          */
933                         if (sub_tuple_fraction >= 1.0)
934                                 sub_tuple_fraction = 0.25;
935
936                         /*
937                          * If both GROUP BY and ORDER BY are specified, we will need
938                          * two levels of sort --- and, therefore, certainly need to
939                          * read all the input tuples --- unless ORDER BY is a subset
940                          * of GROUP BY.  (We have not yet canonicalized the pathkeys,
941                          * so must use the slower noncanonical comparison method.)
942                          */
943                         if (parse->groupClause && parse->sortClause &&
944                                 !noncanonical_pathkeys_contained_in(sort_pathkeys,
945                                                                                                         group_pathkeys))
946                                 sub_tuple_fraction = 0.0;
947                 }
948                 else if (parse->hasAggs)
949                 {
950                         /*
951                          * Ungrouped aggregate will certainly want all the input
952                          * tuples.
953                          */
954                         sub_tuple_fraction = 0.0;
955                 }
956                 else if (parse->distinctClause)
957                 {
958                         /*
959                          * SELECT DISTINCT, like GROUP, will absorb an unpredictable
960                          * number of input tuples per output tuple.  Handle the same
961                          * way.
962                          */
963                         if (sub_tuple_fraction >= 1.0)
964                                 sub_tuple_fraction = 0.25;
965                 }
966
967                 /*
968                  * Generate the best unsorted and presorted paths for this Query
969                  * (but note there may not be any presorted path).
970                  */
971                 query_planner(parse, sub_tlist, sub_tuple_fraction,
972                                           &cheapest_path, &sorted_path);
973
974                 /*
975                  * We couldn't canonicalize group_pathkeys and sort_pathkeys
976                  * before running query_planner(), so do it now.
977                  */
978                 group_pathkeys = canonicalize_pathkeys(parse, group_pathkeys);
979                 sort_pathkeys = canonicalize_pathkeys(parse, sort_pathkeys);
980
981                 /*
982                  * Consider whether we might want to use hashed grouping.
983                  */
984                 if (parse->groupClause)
985                 {
986                         List       *groupExprs;
987                         double          cheapest_path_rows;
988                         int                     cheapest_path_width;
989
990                         /*
991                          * Beware in this section of the possibility that
992                          * cheapest_path->parent is NULL.  This could happen if user
993                          * does something silly like SELECT 'foo' GROUP BY 1;
994                          */
995                         if (cheapest_path->parent)
996                         {
997                                 cheapest_path_rows = cheapest_path->parent->rows;
998                                 cheapest_path_width = cheapest_path->parent->width;
999                         }
1000                         else
1001                         {
1002                                 cheapest_path_rows = 1; /* assume non-set result */
1003                                 cheapest_path_width = 100;              /* arbitrary */
1004                         }
1005
1006                         /*
1007                          * Always estimate the number of groups.  We can't do this
1008                          * until after running query_planner(), either.
1009                          */
1010                         groupExprs = get_sortgrouplist_exprs(parse->groupClause,
1011                                                                                                  parse->targetList);
1012                         dNumGroups = estimate_num_groups(parse,
1013                                                                                          groupExprs,
1014                                                                                          cheapest_path_rows);
1015                         /* Also want it as a long int --- but 'ware overflow! */
1016                         numGroups = (long) Min(dNumGroups, (double) LONG_MAX);
1017
1018                         /*
1019                          * Check can't-do-it conditions, including whether the
1020                          * grouping operators are hashjoinable.
1021                          *
1022                          * Executor doesn't support hashed aggregation with DISTINCT
1023                          * aggregates.  (Doing so would imply storing *all* the input
1024                          * values in the hash table, which seems like a certain
1025                          * loser.)
1026                          */
1027                         if (!enable_hashagg || !hash_safe_grouping(parse))
1028                                 use_hashed_grouping = false;
1029                         else if (agg_counts.numDistinctAggs != 0)
1030                                 use_hashed_grouping = false;
1031                         else
1032                         {
1033                                 /*
1034                                  * Use hashed grouping if (a) we think we can fit the
1035                                  * hashtable into work_mem, *and* (b) the estimated cost
1036                                  * is no more than doing it the other way.      While avoiding
1037                                  * the need for sorted input is usually a win, the fact
1038                                  * that the output won't be sorted may be a loss; so we
1039                                  * need to do an actual cost comparison.
1040                                  */
1041                                 Size            hashentrysize;
1042
1043                                 /* Estimate per-hash-entry space at tuple width... */
1044                                 hashentrysize = cheapest_path_width;
1045                                 /* plus space for pass-by-ref transition values... */
1046                                 hashentrysize += agg_counts.transitionSpace;
1047                                 /* plus the per-hash-entry overhead */
1048                                 hashentrysize += hash_agg_entry_size(agg_counts.numAggs);
1049
1050                                 if (hashentrysize * dNumGroups <= work_mem * 1024L)
1051                                 {
1052                                         /*
1053                                          * Okay, do the cost comparison.  We need to consider
1054                                          * cheapest_path + hashagg [+ final sort] versus
1055                                          * either cheapest_path [+ sort] + group or agg [+
1056                                          * final sort] or presorted_path + group or agg [+
1057                                          * final sort] where brackets indicate a step that may
1058                                          * not be needed. We assume query_planner() will have
1059                                          * returned a presorted path only if it's a winner
1060                                          * compared to cheapest_path for this purpose.
1061                                          *
1062                                          * These path variables are dummies that just hold cost
1063                                          * fields; we don't make actual Paths for these steps.
1064                                          */
1065                                         Path            hashed_p;
1066                                         Path            sorted_p;
1067
1068                                         cost_agg(&hashed_p, parse,
1069                                                          AGG_HASHED, agg_counts.numAggs,
1070                                                          numGroupCols, dNumGroups,
1071                                                          cheapest_path->startup_cost,
1072                                                          cheapest_path->total_cost,
1073                                                          cheapest_path_rows);
1074                                         /* Result of hashed agg is always unsorted */
1075                                         if (sort_pathkeys)
1076                                                 cost_sort(&hashed_p, parse, sort_pathkeys,
1077                                                                   hashed_p.total_cost,
1078                                                                   dNumGroups,
1079                                                                   cheapest_path_width);
1080
1081                                         if (sorted_path)
1082                                         {
1083                                                 sorted_p.startup_cost = sorted_path->startup_cost;
1084                                                 sorted_p.total_cost = sorted_path->total_cost;
1085                                                 current_pathkeys = sorted_path->pathkeys;
1086                                         }
1087                                         else
1088                                         {
1089                                                 sorted_p.startup_cost = cheapest_path->startup_cost;
1090                                                 sorted_p.total_cost = cheapest_path->total_cost;
1091                                                 current_pathkeys = cheapest_path->pathkeys;
1092                                         }
1093                                         if (!pathkeys_contained_in(group_pathkeys,
1094                                                                                            current_pathkeys))
1095                                         {
1096                                                 cost_sort(&sorted_p, parse, group_pathkeys,
1097                                                                   sorted_p.total_cost,
1098                                                                   cheapest_path_rows,
1099                                                                   cheapest_path_width);
1100                                                 current_pathkeys = group_pathkeys;
1101                                         }
1102                                         if (parse->hasAggs)
1103                                                 cost_agg(&sorted_p, parse,
1104                                                                  AGG_SORTED, agg_counts.numAggs,
1105                                                                  numGroupCols, dNumGroups,
1106                                                                  sorted_p.startup_cost,
1107                                                                  sorted_p.total_cost,
1108                                                                  cheapest_path_rows);
1109                                         else
1110                                                 cost_group(&sorted_p, parse,
1111                                                                    numGroupCols, dNumGroups,
1112                                                                    sorted_p.startup_cost,
1113                                                                    sorted_p.total_cost,
1114                                                                    cheapest_path_rows);
1115                                         /* The Agg or Group node will preserve ordering */
1116                                         if (sort_pathkeys &&
1117                                                 !pathkeys_contained_in(sort_pathkeys,
1118                                                                                            current_pathkeys))
1119                                         {
1120                                                 cost_sort(&sorted_p, parse, sort_pathkeys,
1121                                                                   sorted_p.total_cost,
1122                                                                   dNumGroups,
1123                                                                   cheapest_path_width);
1124                                         }
1125
1126                                         /*
1127                                          * Now make the decision using the top-level tuple
1128                                          * fraction.  First we have to convert an absolute
1129                                          * count (LIMIT) into fractional form.
1130                                          */
1131                                         if (tuple_fraction >= 1.0)
1132                                                 tuple_fraction /= dNumGroups;
1133
1134                                         if (compare_fractional_path_costs(&hashed_p, &sorted_p,
1135                                                                                                           tuple_fraction) < 0)
1136                                         {
1137                                                 /* Hashed is cheaper, so use it */
1138                                                 use_hashed_grouping = true;
1139                                         }
1140                                 }
1141                         }
1142                 }
1143
1144                 /*
1145                  * Select the best path and create a plan to execute it.
1146                  *
1147                  * If we are doing hashed grouping, we will always read all the input
1148                  * tuples, so use the cheapest-total path.      Otherwise, trust
1149                  * query_planner's decision about which to use.
1150                  */
1151                 if (sorted_path && !use_hashed_grouping)
1152                 {
1153                         result_plan = create_plan(parse, sorted_path);
1154                         current_pathkeys = sorted_path->pathkeys;
1155                 }
1156                 else
1157                 {
1158                         result_plan = create_plan(parse, cheapest_path);
1159                         current_pathkeys = cheapest_path->pathkeys;
1160                 }
1161
1162                 /*
1163                  * create_plan() returns a plan with just a "flat" tlist of
1164                  * required Vars.  Usually we need to insert the sub_tlist as the
1165                  * tlist of the top plan node.  However, we can skip that if we
1166                  * determined that whatever query_planner chose to return will be
1167                  * good enough.
1168                  */
1169                 if (need_tlist_eval)
1170                 {
1171                         /*
1172                          * If the top-level plan node is one that cannot do expression
1173                          * evaluation, we must insert a Result node to project the
1174                          * desired tlist.
1175                          */
1176                         if (!is_projection_capable_plan(result_plan))
1177                         {
1178                                 result_plan = (Plan *) make_result(sub_tlist, NULL,
1179                                                                                                    result_plan);
1180                         }
1181                         else
1182                         {
1183                                 /*
1184                                  * Otherwise, just replace the subplan's flat tlist with
1185                                  * the desired tlist.
1186                                  */
1187                                 result_plan->targetlist = sub_tlist;
1188                         }
1189
1190                         /*
1191                          * Also, account for the cost of evaluation of the sub_tlist.
1192                          *
1193                          * Up to now, we have only been dealing with "flat" tlists,
1194                          * containing just Vars.  So their evaluation cost is zero
1195                          * according to the model used by cost_qual_eval() (or if you
1196                          * prefer, the cost is factored into cpu_tuple_cost).  Thus we
1197                          * can avoid accounting for tlist cost throughout
1198                          * query_planner() and subroutines.  But now we've inserted a
1199                          * tlist that might contain actual operators, sub-selects, etc
1200                          * --- so we'd better account for its cost.
1201                          *
1202                          * Below this point, any tlist eval cost for added-on nodes
1203                          * should be accounted for as we create those nodes.
1204                          * Presently, of the node types we can add on, only Agg and
1205                          * Group project new tlists (the rest just copy their input
1206                          * tuples) --- so make_agg() and make_group() are responsible
1207                          * for computing the added cost.
1208                          */
1209                         cost_qual_eval(&tlist_cost, sub_tlist);
1210                         result_plan->startup_cost += tlist_cost.startup;
1211                         result_plan->total_cost += tlist_cost.startup +
1212                                 tlist_cost.per_tuple * result_plan->plan_rows;
1213                 }
1214                 else
1215                 {
1216                         /*
1217                          * Since we're using query_planner's tlist and not the one
1218                          * make_subplanTargetList calculated, we have to refigure any
1219                          * grouping-column indexes make_subplanTargetList computed.
1220                          */
1221                         locate_grouping_columns(parse, tlist, result_plan->targetlist,
1222                                                                         groupColIdx);
1223                 }
1224
1225                 /*
1226                  * Insert AGG or GROUP node if needed, plus an explicit sort step
1227                  * if necessary.
1228                  *
1229                  * HAVING clause, if any, becomes qual of the Agg or Group node.
1230                  */
1231                 if (use_hashed_grouping)
1232                 {
1233                         /* Hashed aggregate plan --- no sort needed */
1234                         result_plan = (Plan *) make_agg(parse,
1235                                                                                         tlist,
1236                                                                                         (List *) parse->havingQual,
1237                                                                                         AGG_HASHED,
1238                                                                                         numGroupCols,
1239                                                                                         groupColIdx,
1240                                                                                         numGroups,
1241                                                                                         agg_counts.numAggs,
1242                                                                                         result_plan);
1243                         /* Hashed aggregation produces randomly-ordered results */
1244                         current_pathkeys = NIL;
1245                 }
1246                 else if (parse->hasAggs)
1247                 {
1248                         /* Plain aggregate plan --- sort if needed */
1249                         AggStrategy aggstrategy;
1250
1251                         if (parse->groupClause)
1252                         {
1253                                 if (!pathkeys_contained_in(group_pathkeys, current_pathkeys))
1254                                 {
1255                                         result_plan = (Plan *)
1256                                                 make_sort_from_groupcols(parse,
1257                                                                                                  parse->groupClause,
1258                                                                                                  groupColIdx,
1259                                                                                                  result_plan);
1260                                         current_pathkeys = group_pathkeys;
1261                                 }
1262                                 aggstrategy = AGG_SORTED;
1263
1264                                 /*
1265                                  * The AGG node will not change the sort ordering of its
1266                                  * groups, so current_pathkeys describes the result too.
1267                                  */
1268                         }
1269                         else
1270                         {
1271                                 aggstrategy = AGG_PLAIN;
1272                                 /* Result will be only one row anyway; no sort order */
1273                                 current_pathkeys = NIL;
1274                         }
1275
1276                         result_plan = (Plan *) make_agg(parse,
1277                                                                                         tlist,
1278                                                                                         (List *) parse->havingQual,
1279                                                                                         aggstrategy,
1280                                                                                         numGroupCols,
1281                                                                                         groupColIdx,
1282                                                                                         numGroups,
1283                                                                                         agg_counts.numAggs,
1284                                                                                         result_plan);
1285                 }
1286                 else if (parse->groupClause)
1287                 {
1288                         /*
1289                          * GROUP BY without aggregation, so insert a group node (plus the
1290                          * appropriate sort node, if necessary).
1291                          *
1292                          * Add an explicit sort if we couldn't make the path come
1293                          * out the way the GROUP node needs it.
1294                          */
1295                         if (!pathkeys_contained_in(group_pathkeys, current_pathkeys))
1296                         {
1297                                 result_plan = (Plan *)
1298                                         make_sort_from_groupcols(parse,
1299                                                                                          parse->groupClause,
1300                                                                                          groupColIdx,
1301                                                                                          result_plan);
1302                                 current_pathkeys = group_pathkeys;
1303                         }
1304
1305                         result_plan = (Plan *) make_group(parse,
1306                                                                                           tlist,
1307                                                                                           (List *) parse->havingQual,
1308                                                                                           numGroupCols,
1309                                                                                           groupColIdx,
1310                                                                                           dNumGroups,
1311                                                                                           result_plan);
1312                         /* The Group node won't change sort ordering */
1313                 }
1314                 else if (parse->hasHavingQual)
1315                 {
1316                         /*
1317                          * No aggregates, and no GROUP BY, but we have a HAVING qual.
1318                          * This is a degenerate case in which we are supposed to emit
1319                          * either 0 or 1 row depending on whether HAVING succeeds.
1320                          * Furthermore, there cannot be any variables in either HAVING
1321                          * or the targetlist, so we actually do not need the FROM table
1322                          * at all!  We can just throw away the plan-so-far and generate
1323                          * a Result node.  This is a sufficiently unusual corner case
1324                          * that it's not worth contorting the structure of this routine
1325                          * to avoid having to generate the plan in the first place.
1326                          */
1327                         result_plan = (Plan *) make_result(tlist,
1328                                                                                            parse->havingQual,
1329                                                                                            NULL);
1330                 }
1331         }                                                       /* end of if (setOperations) */
1332
1333         /*
1334          * If we were not able to make the plan come out in the right order,
1335          * add an explicit sort step.
1336          */
1337         if (parse->sortClause)
1338         {
1339                 if (!pathkeys_contained_in(sort_pathkeys, current_pathkeys))
1340                 {
1341                         result_plan = (Plan *)
1342                                 make_sort_from_sortclauses(parse,
1343                                                                                    parse->sortClause,
1344                                                                                    result_plan);
1345                         current_pathkeys = sort_pathkeys;
1346                 }
1347         }
1348
1349         /*
1350          * If there is a DISTINCT clause, add the UNIQUE node.
1351          */
1352         if (parse->distinctClause)
1353         {
1354                 result_plan = (Plan *) make_unique(result_plan, parse->distinctClause);
1355
1356                 /*
1357                  * If there was grouping or aggregation, leave plan_rows as-is
1358                  * (ie, assume the result was already mostly unique).  If not,
1359                  * it's reasonable to assume the UNIQUE filter has effects
1360                  * comparable to GROUP BY.
1361                  */
1362                 if (!parse->groupClause && !parse->hasHavingQual && !parse->hasAggs)
1363                 {
1364                         List       *distinctExprs;
1365
1366                         distinctExprs = get_sortgrouplist_exprs(parse->distinctClause,
1367                                                                                                         parse->targetList);
1368                         result_plan->plan_rows = estimate_num_groups(parse,
1369                                                                                                                  distinctExprs,
1370                                                                                                  result_plan->plan_rows);
1371                 }
1372         }
1373
1374         /*
1375          * Finally, if there is a LIMIT/OFFSET clause, add the LIMIT node.
1376          */
1377         if (parse->limitOffset || parse->limitCount)
1378         {
1379                 result_plan = (Plan *) make_limit(result_plan,
1380                                                                                   parse->limitOffset,
1381                                                                                   parse->limitCount);
1382         }
1383
1384         /*
1385          * Return the actual output ordering in query_pathkeys for possible
1386          * use by an outer query level.
1387          */
1388         parse->query_pathkeys = current_pathkeys;
1389
1390         return result_plan;
1391 }
1392
1393 /*
1394  * hash_safe_grouping - are grouping operators hashable?
1395  *
1396  * We assume hashed aggregation will work if the datatype's equality operator
1397  * is marked hashjoinable.
1398  */
1399 static bool
1400 hash_safe_grouping(Query *parse)
1401 {
1402         ListCell   *gl;
1403
1404         foreach(gl, parse->groupClause)
1405         {
1406                 GroupClause *grpcl = (GroupClause *) lfirst(gl);
1407                 TargetEntry *tle = get_sortgroupclause_tle(grpcl, parse->targetList);
1408                 Operator        optup;
1409                 bool            oprcanhash;
1410
1411                 optup = equality_oper(tle->resdom->restype, true);
1412                 if (!optup)
1413                         return false;
1414                 oprcanhash = ((Form_pg_operator) GETSTRUCT(optup))->oprcanhash;
1415                 ReleaseSysCache(optup);
1416                 if (!oprcanhash)
1417                         return false;
1418         }
1419         return true;
1420 }
1421
1422 /*---------------
1423  * make_subplanTargetList
1424  *        Generate appropriate target list when grouping is required.
1425  *
1426  * When grouping_planner inserts Aggregate, Group, or Result plan nodes
1427  * above the result of query_planner, we typically want to pass a different
1428  * target list to query_planner than the outer plan nodes should have.
1429  * This routine generates the correct target list for the subplan.
1430  *
1431  * The initial target list passed from the parser already contains entries
1432  * for all ORDER BY and GROUP BY expressions, but it will not have entries
1433  * for variables used only in HAVING clauses; so we need to add those
1434  * variables to the subplan target list.  Also, we flatten all expressions
1435  * except GROUP BY items into their component variables; the other expressions
1436  * will be computed by the inserted nodes rather than by the subplan.
1437  * For example, given a query like
1438  *              SELECT a+b,SUM(c+d) FROM table GROUP BY a+b;
1439  * we want to pass this targetlist to the subplan:
1440  *              a,b,c,d,a+b
1441  * where the a+b target will be used by the Sort/Group steps, and the
1442  * other targets will be used for computing the final results.  (In the
1443  * above example we could theoretically suppress the a and b targets and
1444  * pass down only c,d,a+b, but it's not really worth the trouble to
1445  * eliminate simple var references from the subplan.  We will avoid doing
1446  * the extra computation to recompute a+b at the outer level; see
1447  * replace_vars_with_subplan_refs() in setrefs.c.)
1448  *
1449  * If we are grouping or aggregating, *and* there are no non-Var grouping
1450  * expressions, then the returned tlist is effectively dummy; we do not
1451  * need to force it to be evaluated, because all the Vars it contains
1452  * should be present in the output of query_planner anyway.
1453  *
1454  * 'parse' is the query being processed.
1455  * 'tlist' is the query's target list.
1456  * 'groupColIdx' receives an array of column numbers for the GROUP BY
1457  *                      expressions (if there are any) in the subplan's target list.
1458  * 'need_tlist_eval' is set true if we really need to evaluate the
1459  *                      result tlist.
1460  *
1461  * The result is the targetlist to be passed to the subplan.
1462  *---------------
1463  */
1464 static List *
1465 make_subplanTargetList(Query *parse,
1466                                            List *tlist,
1467                                            AttrNumber **groupColIdx,
1468                                            bool *need_tlist_eval)
1469 {
1470         List       *sub_tlist;
1471         List       *extravars;
1472         int                     numCols;
1473
1474         *groupColIdx = NULL;
1475
1476         /*
1477          * If we're not grouping or aggregating, there's nothing to do here;
1478          * query_planner should receive the unmodified target list.
1479          */
1480         if (!parse->hasAggs && !parse->groupClause && !parse->hasHavingQual)
1481         {
1482                 *need_tlist_eval = true;
1483                 return tlist;
1484         }
1485
1486         /*
1487          * Otherwise, start with a "flattened" tlist (having just the vars
1488          * mentioned in the targetlist and HAVING qual --- but not upper-
1489          * level Vars; they will be replaced by Params later on).
1490          */
1491         sub_tlist = flatten_tlist(tlist);
1492         extravars = pull_var_clause(parse->havingQual, false);
1493         sub_tlist = add_to_flat_tlist(sub_tlist, extravars);
1494         list_free(extravars);
1495         *need_tlist_eval = false;       /* only eval if not flat tlist */
1496
1497         /*
1498          * If grouping, create sub_tlist entries for all GROUP BY expressions
1499          * (GROUP BY items that are simple Vars should be in the list
1500          * already), and make an array showing where the group columns are in
1501          * the sub_tlist.
1502          */
1503         numCols = list_length(parse->groupClause);
1504         if (numCols > 0)
1505         {
1506                 int                     keyno = 0;
1507                 AttrNumber *grpColIdx;
1508                 ListCell   *gl;
1509
1510                 grpColIdx = (AttrNumber *) palloc(sizeof(AttrNumber) * numCols);
1511                 *groupColIdx = grpColIdx;
1512
1513                 foreach(gl, parse->groupClause)
1514                 {
1515                         GroupClause *grpcl = (GroupClause *) lfirst(gl);
1516                         Node       *groupexpr = get_sortgroupclause_expr(grpcl, tlist);
1517                         TargetEntry *te = NULL;
1518                         ListCell   *sl;
1519
1520                         /* Find or make a matching sub_tlist entry */
1521                         foreach(sl, sub_tlist)
1522                         {
1523                                 te = (TargetEntry *) lfirst(sl);
1524                                 if (equal(groupexpr, te->expr))
1525                                         break;
1526                         }
1527                         if (!sl)
1528                         {
1529                                 te = makeTargetEntry(makeResdom(list_length(sub_tlist) + 1,
1530                                                                                                 exprType(groupexpr),
1531                                                                                                 exprTypmod(groupexpr),
1532                                                                                                 NULL,
1533                                                                                                 false),
1534                                                                          (Expr *) groupexpr);
1535                                 sub_tlist = lappend(sub_tlist, te);
1536                                 *need_tlist_eval = true;                /* it's not flat anymore */
1537                         }
1538
1539                         /* and save its resno */
1540                         grpColIdx[keyno++] = te->resdom->resno;
1541                 }
1542         }
1543
1544         return sub_tlist;
1545 }
1546
1547 /*
1548  * locate_grouping_columns
1549  *              Locate grouping columns in the tlist chosen by query_planner.
1550  *
1551  * This is only needed if we don't use the sub_tlist chosen by
1552  * make_subplanTargetList.      We have to forget the column indexes found
1553  * by that routine and re-locate the grouping vars in the real sub_tlist.
1554  */
1555 static void
1556 locate_grouping_columns(Query *parse,
1557                                                 List *tlist,
1558                                                 List *sub_tlist,
1559                                                 AttrNumber *groupColIdx)
1560 {
1561         int                     keyno = 0;
1562         ListCell   *gl;
1563
1564         /*
1565          * No work unless grouping.
1566          */
1567         if (!parse->groupClause)
1568         {
1569                 Assert(groupColIdx == NULL);
1570                 return;
1571         }
1572         Assert(groupColIdx != NULL);
1573
1574         foreach(gl, parse->groupClause)
1575         {
1576                 GroupClause *grpcl = (GroupClause *) lfirst(gl);
1577                 Node       *groupexpr = get_sortgroupclause_expr(grpcl, tlist);
1578                 TargetEntry *te = NULL;
1579                 ListCell   *sl;
1580
1581                 foreach(sl, sub_tlist)
1582                 {
1583                         te = (TargetEntry *) lfirst(sl);
1584                         if (equal(groupexpr, te->expr))
1585                                 break;
1586                 }
1587                 if (!sl)
1588                         elog(ERROR, "failed to locate grouping columns");
1589
1590                 groupColIdx[keyno++] = te->resdom->resno;
1591         }
1592 }
1593
1594 /*
1595  * postprocess_setop_tlist
1596  *        Fix up targetlist returned by plan_set_operations().
1597  *
1598  * We need to transpose sort key info from the orig_tlist into new_tlist.
1599  * NOTE: this would not be good enough if we supported resjunk sort keys
1600  * for results of set operations --- then, we'd need to project a whole
1601  * new tlist to evaluate the resjunk columns.  For now, just ereport if we
1602  * find any resjunk columns in orig_tlist.
1603  */
1604 static List *
1605 postprocess_setop_tlist(List *new_tlist, List *orig_tlist)
1606 {
1607         ListCell   *l;
1608         ListCell   *orig_tlist_item = list_head(orig_tlist);
1609
1610         foreach(l, new_tlist)
1611         {
1612                 TargetEntry *new_tle = (TargetEntry *) lfirst(l);
1613                 TargetEntry *orig_tle;
1614
1615                 /* ignore resjunk columns in setop result */
1616                 if (new_tle->resdom->resjunk)
1617                         continue;
1618
1619                 Assert(orig_tlist_item != NULL);
1620                 orig_tle = (TargetEntry *) lfirst(orig_tlist_item);
1621                 orig_tlist_item = lnext(orig_tlist_item);
1622                 if (orig_tle->resdom->resjunk)  /* should not happen */
1623                         elog(ERROR, "resjunk output columns are not implemented");
1624                 Assert(new_tle->resdom->resno == orig_tle->resdom->resno);
1625                 Assert(new_tle->resdom->restype == orig_tle->resdom->restype);
1626                 new_tle->resdom->ressortgroupref = orig_tle->resdom->ressortgroupref;
1627         }
1628         if (orig_tlist_item != NULL)
1629                 elog(ERROR, "resjunk output columns are not implemented");
1630         return new_tlist;
1631 }