PostgreSQL Source Code  git master
appendinfo.c File Reference
#include "postgres.h"
#include "access/htup_details.h"
#include "access/table.h"
#include "foreign/fdwapi.h"
#include "nodes/makefuncs.h"
#include "nodes/nodeFuncs.h"
#include "optimizer/appendinfo.h"
#include "optimizer/pathnode.h"
#include "parser/parsetree.h"
#include "utils/lsyscache.h"
#include "utils/rel.h"
#include "utils/syscache.h"
Include dependency graph for appendinfo.c:

Go to the source code of this file.

Data Structures

struct  adjust_appendrel_attrs_context
 

Functions

static void make_inh_translation_list (Relation oldrelation, Relation newrelation, Index newvarno, AppendRelInfo *appinfo)
 
static Nodeadjust_appendrel_attrs_mutator (Node *node, adjust_appendrel_attrs_context *context)
 
AppendRelInfomake_append_rel_info (Relation parentrel, Relation childrel, Index parentRTindex, Index childRTindex)
 
Nodeadjust_appendrel_attrs (PlannerInfo *root, Node *node, int nappinfos, AppendRelInfo **appinfos)
 
Nodeadjust_appendrel_attrs_multilevel (PlannerInfo *root, Node *node, RelOptInfo *childrel, RelOptInfo *parentrel)
 
Relids adjust_child_relids (Relids relids, int nappinfos, AppendRelInfo **appinfos)
 
Relids adjust_child_relids_multilevel (PlannerInfo *root, Relids relids, RelOptInfo *childrel, RelOptInfo *parentrel)
 
Listadjust_inherited_attnums (List *attnums, AppendRelInfo *context)
 
Listadjust_inherited_attnums_multilevel (PlannerInfo *root, List *attnums, Index child_relid, Index top_parent_relid)
 
void get_translated_update_targetlist (PlannerInfo *root, Index relid, List **processed_tlist, List **update_colnos)
 
AppendRelInfo ** find_appinfos_by_relids (PlannerInfo *root, Relids relids, int *nappinfos)
 
void add_row_identity_var (PlannerInfo *root, Var *orig_var, Index rtindex, const char *rowid_name)
 
void add_row_identity_columns (PlannerInfo *root, Index rtindex, RangeTblEntry *target_rte, Relation target_relation)
 
void distribute_row_identity_vars (PlannerInfo *root)
 

Function Documentation

◆ add_row_identity_columns()

void add_row_identity_columns ( PlannerInfo root,
Index  rtindex,
RangeTblEntry target_rte,
Relation  target_relation 
)

Definition at line 883 of file appendinfo.c.

886 {
887  CmdType commandType = root->parse->commandType;
888  char relkind = target_relation->rd_rel->relkind;
889  Var *var;
890 
891  Assert(commandType == CMD_UPDATE || commandType == CMD_DELETE || commandType == CMD_MERGE);
892 
893  if (commandType == CMD_MERGE ||
894  relkind == RELKIND_RELATION ||
895  relkind == RELKIND_MATVIEW ||
896  relkind == RELKIND_PARTITIONED_TABLE)
897  {
898  /*
899  * Emit CTID so that executor can find the row to merge, update or
900  * delete.
901  */
902  var = makeVar(rtindex,
904  TIDOID,
905  -1,
906  InvalidOid,
907  0);
908  add_row_identity_var(root, var, rtindex, "ctid");
909  }
910  else if (relkind == RELKIND_FOREIGN_TABLE)
911  {
912  /*
913  * Let the foreign table's FDW add whatever junk TLEs it wants.
914  */
915  FdwRoutine *fdwroutine;
916 
917  fdwroutine = GetFdwRoutineForRelation(target_relation, false);
918 
919  if (fdwroutine->AddForeignUpdateTargets != NULL)
920  fdwroutine->AddForeignUpdateTargets(root, rtindex,
921  target_rte, target_relation);
922 
923  /*
924  * For UPDATE, we need to make the FDW fetch unchanged columns by
925  * asking it to fetch a whole-row Var. That's because the top-level
926  * targetlist only contains entries for changed columns, but
927  * ExecUpdate will need to build the complete new tuple. (Actually,
928  * we only really need this in UPDATEs that are not pushed to the
929  * remote side, but it's hard to tell if that will be the case at the
930  * point when this function is called.)
931  *
932  * We will also need the whole row if there are any row triggers, so
933  * that the executor will have the "old" row to pass to the trigger.
934  * Alas, this misses system columns.
935  */
936  if (commandType == CMD_UPDATE ||
937  (target_relation->trigdesc &&
938  (target_relation->trigdesc->trig_delete_after_row ||
939  target_relation->trigdesc->trig_delete_before_row)))
940  {
941  var = makeVar(rtindex,
943  RECORDOID,
944  -1,
945  InvalidOid,
946  0);
947  add_row_identity_var(root, var, rtindex, "wholerow");
948  }
949  }
950 }
void add_row_identity_var(PlannerInfo *root, Var *orig_var, Index rtindex, const char *rowid_name)
Definition: appendinfo.c:788
#define InvalidAttrNumber
Definition: attnum.h:23
FdwRoutine * GetFdwRoutineForRelation(Relation relation, bool makecopy)
Definition: foreign.c:429
Assert(fmt[strlen(fmt) - 1] !='\n')
Var * makeVar(int varno, AttrNumber varattno, Oid vartype, int32 vartypmod, Oid varcollid, Index varlevelsup)
Definition: makefuncs.c:66
CmdType
Definition: nodes.h:274
@ CMD_MERGE
Definition: nodes.h:280
@ CMD_DELETE
Definition: nodes.h:279
@ CMD_UPDATE
Definition: nodes.h:277
#define InvalidOid
Definition: postgres_ext.h:36
AddForeignUpdateTargets_function AddForeignUpdateTargets
Definition: fdwapi.h:229
Query * parse
Definition: pathnodes.h:202
CmdType commandType
Definition: parsenodes.h:128
TriggerDesc * trigdesc
Definition: rel.h:116
Form_pg_class rd_rel
Definition: rel.h:110
bool trig_delete_before_row
Definition: reltrigger.h:66
bool trig_delete_after_row
Definition: reltrigger.h:67
Definition: primnodes.h:226
#define SelfItemPointerAttributeNumber
Definition: sysattr.h:21

References add_row_identity_var(), FdwRoutine::AddForeignUpdateTargets, Assert(), CMD_DELETE, CMD_MERGE, CMD_UPDATE, Query::commandType, GetFdwRoutineForRelation(), InvalidAttrNumber, InvalidOid, makeVar(), PlannerInfo::parse, RelationData::rd_rel, SelfItemPointerAttributeNumber, TriggerDesc::trig_delete_after_row, TriggerDesc::trig_delete_before_row, and RelationData::trigdesc.

Referenced by distribute_row_identity_vars(), expand_single_inheritance_child(), and preprocess_targetlist().

◆ add_row_identity_var()

void add_row_identity_var ( PlannerInfo root,
Var orig_var,
Index  rtindex,
const char *  rowid_name 
)

Definition at line 788 of file appendinfo.c.

790 {
791  TargetEntry *tle;
792  Var *rowid_var;
793  RowIdentityVarInfo *ridinfo;
794  ListCell *lc;
795 
796  /* For now, the argument must be just a Var of the given rtindex */
797  Assert(IsA(orig_var, Var));
798  Assert(orig_var->varno == rtindex);
799  Assert(orig_var->varlevelsup == 0);
800  Assert(orig_var->varnullingrels == NULL);
801 
802  /*
803  * If we're doing non-inherited UPDATE/DELETE/MERGE, there's little need
804  * for ROWID_VAR shenanigans. Just shove the presented Var into the
805  * processed_tlist, and we're done.
806  */
807  if (rtindex == root->parse->resultRelation)
808  {
809  tle = makeTargetEntry((Expr *) orig_var,
810  list_length(root->processed_tlist) + 1,
811  pstrdup(rowid_name),
812  true);
813  root->processed_tlist = lappend(root->processed_tlist, tle);
814  return;
815  }
816 
817  /*
818  * Otherwise, rtindex should reference a leaf target relation that's being
819  * added to the query during expand_inherited_rtentry().
820  */
821  Assert(bms_is_member(rtindex, root->leaf_result_relids));
822  Assert(root->append_rel_array[rtindex] != NULL);
823 
824  /*
825  * We have to find a matching RowIdentityVarInfo, or make one if there is
826  * none. To allow using equal() to match the vars, change the varno to
827  * ROWID_VAR, leaving all else alone.
828  */
829  rowid_var = copyObject(orig_var);
830  /* This could eventually become ChangeVarNodes() */
831  rowid_var->varno = ROWID_VAR;
832 
833  /* Look for an existing row-id column of the same name */
834  foreach(lc, root->row_identity_vars)
835  {
836  ridinfo = (RowIdentityVarInfo *) lfirst(lc);
837  if (strcmp(rowid_name, ridinfo->rowidname) != 0)
838  continue;
839  if (equal(rowid_var, ridinfo->rowidvar))
840  {
841  /* Found a match; we need only record that rtindex needs it too */
842  ridinfo->rowidrels = bms_add_member(ridinfo->rowidrels, rtindex);
843  return;
844  }
845  else
846  {
847  /* Ooops, can't handle this */
848  elog(ERROR, "conflicting uses of row-identity name \"%s\"",
849  rowid_name);
850  }
851  }
852 
853  /* No request yet, so add a new RowIdentityVarInfo */
854  ridinfo = makeNode(RowIdentityVarInfo);
855  ridinfo->rowidvar = copyObject(rowid_var);
856  /* for the moment, estimate width using just the datatype info */
857  ridinfo->rowidwidth = get_typavgwidth(exprType((Node *) rowid_var),
858  exprTypmod((Node *) rowid_var));
859  ridinfo->rowidname = pstrdup(rowid_name);
860  ridinfo->rowidrels = bms_make_singleton(rtindex);
861 
862  root->row_identity_vars = lappend(root->row_identity_vars, ridinfo);
863 
864  /* Change rowid_var into a reference to this row_identity_vars entry */
865  rowid_var->varattno = list_length(root->row_identity_vars);
866 
867  /* Push the ROWID_VAR reference variable into processed_tlist */
868  tle = makeTargetEntry((Expr *) rowid_var,
869  list_length(root->processed_tlist) + 1,
870  pstrdup(rowid_name),
871  true);
872  root->processed_tlist = lappend(root->processed_tlist, tle);
873 }
bool bms_is_member(int x, const Bitmapset *a)
Definition: bitmapset.c:444
Bitmapset * bms_make_singleton(int x)
Definition: bitmapset.c:186
Bitmapset * bms_add_member(Bitmapset *a, int x)
Definition: bitmapset.c:755
#define ERROR
Definition: elog.h:39
bool equal(const void *a, const void *b)
Definition: equalfuncs.c:223
List * lappend(List *list, void *datum)
Definition: list.c:338
int32 get_typavgwidth(Oid typid, int32 typmod)
Definition: lsyscache.c:2536
TargetEntry * makeTargetEntry(Expr *expr, AttrNumber resno, char *resname, bool resjunk)
Definition: makefuncs.c:240
char * pstrdup(const char *in)
Definition: mcxt.c:1624
Oid exprType(const Node *expr)
Definition: nodeFuncs.c:43
int32 exprTypmod(const Node *expr)
Definition: nodeFuncs.c:266
#define IsA(nodeptr, _type_)
Definition: nodes.h:179
#define copyObject(obj)
Definition: nodes.h:244
#define makeNode(_type_)
Definition: nodes.h:176
#define lfirst(lc)
Definition: pg_list.h:172
static int list_length(const List *l)
Definition: pg_list.h:152
#define ROWID_VAR
Definition: primnodes.h:217
Definition: nodes.h:129
List * processed_tlist
Definition: pathnodes.h:456
List * row_identity_vars
Definition: pathnodes.h:368
Relids leaf_result_relids
Definition: pathnodes.h:356
int varno
Definition: primnodes.h:233
Index varlevelsup
Definition: primnodes.h:258

References Assert(), bms_add_member(), bms_is_member(), bms_make_singleton(), copyObject, elog(), equal(), ERROR, exprType(), exprTypmod(), get_typavgwidth(), IsA, lappend(), PlannerInfo::leaf_result_relids, lfirst, list_length(), makeNode, makeTargetEntry(), PlannerInfo::parse, PlannerInfo::processed_tlist, pstrdup(), PlannerInfo::row_identity_vars, ROWID_VAR, RowIdentityVarInfo::rowidname, RowIdentityVarInfo::rowidrels, RowIdentityVarInfo::rowidvar, RowIdentityVarInfo::rowidwidth, Var::varattno, Var::varlevelsup, and Var::varno.

Referenced by add_row_identity_columns(), expand_single_inheritance_child(), and postgresAddForeignUpdateTargets().

◆ adjust_appendrel_attrs()

Node* adjust_appendrel_attrs ( PlannerInfo root,
Node node,
int  nappinfos,
AppendRelInfo **  appinfos 
)

Definition at line 195 of file appendinfo.c.

197 {
199 
200  context.root = root;
201  context.nappinfos = nappinfos;
202  context.appinfos = appinfos;
203 
204  /* If there's nothing to adjust, don't call this function. */
205  Assert(nappinfos >= 1 && appinfos != NULL);
206 
207  /* Should never be translating a Query tree. */
208  Assert(node == NULL || !IsA(node, Query));
209 
210  return adjust_appendrel_attrs_mutator(node, &context);
211 }
static Node * adjust_appendrel_attrs_mutator(Node *node, adjust_appendrel_attrs_context *context)
Definition: appendinfo.c:214
AppendRelInfo ** appinfos
Definition: appendinfo.c:34

References adjust_appendrel_attrs_mutator(), adjust_appendrel_attrs_context::appinfos, Assert(), IsA, adjust_appendrel_attrs_context::nappinfos, and adjust_appendrel_attrs_context::root.

Referenced by add_child_join_rel_equivalences(), add_child_rel_equivalences(), adjust_appendrel_attrs_multilevel(), apply_child_basequals(), apply_scanjoin_target_to_paths(), build_child_join_rel(), build_child_join_reltarget(), build_child_join_sjinfo(), create_partitionwise_grouping_paths(), make_partitionedrel_pruneinfo(), set_append_rel_size(), and try_partitionwise_join().

◆ adjust_appendrel_attrs_multilevel()

Node* adjust_appendrel_attrs_multilevel ( PlannerInfo root,
Node node,
RelOptInfo childrel,
RelOptInfo parentrel 
)

Definition at line 520 of file appendinfo.c.

523 {
524  AppendRelInfo **appinfos;
525  int nappinfos;
526 
527  /* Recurse if immediate parent is not the top parent. */
528  if (childrel->parent != parentrel)
529  {
530  if (childrel->parent)
531  node = adjust_appendrel_attrs_multilevel(root, node,
532  childrel->parent,
533  parentrel);
534  else
535  elog(ERROR, "childrel is not a child of parentrel");
536  }
537 
538  /* Now translate for this child. */
539  appinfos = find_appinfos_by_relids(root, childrel->relids, &nappinfos);
540 
541  node = adjust_appendrel_attrs(root, node, nappinfos, appinfos);
542 
543  pfree(appinfos);
544 
545  return node;
546 }
AppendRelInfo ** find_appinfos_by_relids(PlannerInfo *root, Relids relids, int *nappinfos)
Definition: appendinfo.c:732
Node * adjust_appendrel_attrs(PlannerInfo *root, Node *node, int nappinfos, AppendRelInfo **appinfos)
Definition: appendinfo.c:195
Node * adjust_appendrel_attrs_multilevel(PlannerInfo *root, Node *node, RelOptInfo *childrel, RelOptInfo *parentrel)
Definition: appendinfo.c:520
void pfree(void *pointer)
Definition: mcxt.c:1436
Relids relids
Definition: pathnodes.h:862

References adjust_appendrel_attrs(), elog(), ERROR, find_appinfos_by_relids(), pfree(), and RelOptInfo::relids.

Referenced by add_child_join_rel_equivalences(), add_child_rel_equivalences(), generate_join_implied_equalities_broken(), get_translated_update_targetlist(), grouping_planner(), and make_partitionedrel_pruneinfo().

◆ adjust_appendrel_attrs_mutator()

static Node * adjust_appendrel_attrs_mutator ( Node node,
adjust_appendrel_attrs_context context 
)
static

Definition at line 214 of file appendinfo.c.

216 {
217  AppendRelInfo **appinfos = context->appinfos;
218  int nappinfos = context->nappinfos;
219  int cnt;
220 
221  if (node == NULL)
222  return NULL;
223  if (IsA(node, Var))
224  {
225  Var *var = (Var *) copyObject(node);
226  AppendRelInfo *appinfo = NULL;
227 
228  if (var->varlevelsup != 0)
229  return (Node *) var; /* no changes needed */
230 
231  /*
232  * You might think we need to adjust var->varnullingrels, but that
233  * shouldn't need any changes. It will contain outer-join relids,
234  * while the transformation we are making affects only baserels.
235  * Below, we just propagate var->varnullingrels into the translated
236  * Var.
237  *
238  * If var->varnullingrels isn't empty, and the translation wouldn't be
239  * a Var, we have to fail. One could imagine wrapping the translated
240  * expression in a PlaceHolderVar, but that won't work because this is
241  * typically used after freezing placeholders. Fortunately, the case
242  * appears unreachable at the moment. We can see nonempty
243  * var->varnullingrels here, but only in cases involving partitionwise
244  * joining, and in such cases the translations will always be Vars.
245  * (Non-Var translations occur only for appendrels made by flattening
246  * UNION ALL subqueries.) Should we need to make this work in future,
247  * a possible fix is to mandate that prepjointree.c create PHVs for
248  * all non-Var outputs of such subqueries, and then we could look up
249  * the pre-existing PHV here. Or perhaps just wrap the translations
250  * that way to begin with?
251  */
252 
253  for (cnt = 0; cnt < nappinfos; cnt++)
254  {
255  if (var->varno == appinfos[cnt]->parent_relid)
256  {
257  appinfo = appinfos[cnt];
258  break;
259  }
260  }
261 
262  if (appinfo)
263  {
264  var->varno = appinfo->child_relid;
265  /* it's now a generated Var, so drop any syntactic labeling */
266  var->varnosyn = 0;
267  var->varattnosyn = 0;
268  if (var->varattno > 0)
269  {
270  Node *newnode;
271 
272  if (var->varattno > list_length(appinfo->translated_vars))
273  elog(ERROR, "attribute %d of relation \"%s\" does not exist",
274  var->varattno, get_rel_name(appinfo->parent_reloid));
275  newnode = copyObject(list_nth(appinfo->translated_vars,
276  var->varattno - 1));
277  if (newnode == NULL)
278  elog(ERROR, "attribute %d of relation \"%s\" does not exist",
279  var->varattno, get_rel_name(appinfo->parent_reloid));
280  if (IsA(newnode, Var))
281  ((Var *) newnode)->varnullingrels = var->varnullingrels;
282  else if (var->varnullingrels != NULL)
283  elog(ERROR, "failed to apply nullingrels to a non-Var");
284  return newnode;
285  }
286  else if (var->varattno == 0)
287  {
288  /*
289  * Whole-row Var: if we are dealing with named rowtypes, we
290  * can use a whole-row Var for the child table plus a coercion
291  * step to convert the tuple layout to the parent's rowtype.
292  * Otherwise we have to generate a RowExpr.
293  */
294  if (OidIsValid(appinfo->child_reltype))
295  {
296  Assert(var->vartype == appinfo->parent_reltype);
297  if (appinfo->parent_reltype != appinfo->child_reltype)
298  {
300 
301  r->arg = (Expr *) var;
302  r->resulttype = appinfo->parent_reltype;
303  r->convertformat = COERCE_IMPLICIT_CAST;
304  r->location = -1;
305  /* Make sure the Var node has the right type ID, too */
306  var->vartype = appinfo->child_reltype;
307  return (Node *) r;
308  }
309  }
310  else
311  {
312  /*
313  * Build a RowExpr containing the translated variables.
314  *
315  * In practice var->vartype will always be RECORDOID here,
316  * so we need to come up with some suitable column names.
317  * We use the parent RTE's column names.
318  *
319  * Note: we can't get here for inheritance cases, so there
320  * is no need to worry that translated_vars might contain
321  * some dummy NULLs.
322  */
323  RowExpr *rowexpr;
324  List *fields;
325  RangeTblEntry *rte;
326 
327  rte = rt_fetch(appinfo->parent_relid,
328  context->root->parse->rtable);
329  fields = copyObject(appinfo->translated_vars);
330  rowexpr = makeNode(RowExpr);
331  rowexpr->args = fields;
332  rowexpr->row_typeid = var->vartype;
333  rowexpr->row_format = COERCE_IMPLICIT_CAST;
334  rowexpr->colnames = copyObject(rte->eref->colnames);
335  rowexpr->location = -1;
336 
337  if (var->varnullingrels != NULL)
338  elog(ERROR, "failed to apply nullingrels to a non-Var");
339 
340  return (Node *) rowexpr;
341  }
342  }
343  /* system attributes don't need any other translation */
344  }
345  else if (var->varno == ROWID_VAR)
346  {
347  /*
348  * If it's a ROWID_VAR placeholder, see if we've reached a leaf
349  * target rel, for which we can translate the Var to a specific
350  * instantiation. We should never be asked to translate to a set
351  * of relids containing more than one leaf target rel, so the
352  * answer will be unique. If we're still considering non-leaf
353  * inheritance levels, return the ROWID_VAR Var as-is.
354  */
355  Relids leaf_result_relids = context->root->leaf_result_relids;
356  Index leaf_relid = 0;
357 
358  for (cnt = 0; cnt < nappinfos; cnt++)
359  {
360  if (bms_is_member(appinfos[cnt]->child_relid,
361  leaf_result_relids))
362  {
363  if (leaf_relid)
364  elog(ERROR, "cannot translate to multiple leaf relids");
365  leaf_relid = appinfos[cnt]->child_relid;
366  }
367  }
368 
369  if (leaf_relid)
370  {
372  list_nth(context->root->row_identity_vars, var->varattno - 1);
373 
374  if (bms_is_member(leaf_relid, ridinfo->rowidrels))
375  {
376  /* Substitute the Var given in the RowIdentityVarInfo */
377  var = copyObject(ridinfo->rowidvar);
378  /* ... but use the correct relid */
379  var->varno = leaf_relid;
380  /* identity vars shouldn't have nulling rels */
381  Assert(var->varnullingrels == NULL);
382  /* varnosyn in the RowIdentityVarInfo is probably wrong */
383  var->varnosyn = 0;
384  var->varattnosyn = 0;
385  }
386  else
387  {
388  /*
389  * This leaf rel can't return the desired value, so
390  * substitute a NULL of the correct type.
391  */
392  return (Node *) makeNullConst(var->vartype,
393  var->vartypmod,
394  var->varcollid);
395  }
396  }
397  }
398  return (Node *) var;
399  }
400  if (IsA(node, CurrentOfExpr))
401  {
402  CurrentOfExpr *cexpr = (CurrentOfExpr *) copyObject(node);
403 
404  for (cnt = 0; cnt < nappinfos; cnt++)
405  {
406  AppendRelInfo *appinfo = appinfos[cnt];
407 
408  if (cexpr->cvarno == appinfo->parent_relid)
409  {
410  cexpr->cvarno = appinfo->child_relid;
411  break;
412  }
413  }
414  return (Node *) cexpr;
415  }
416  if (IsA(node, PlaceHolderVar))
417  {
418  /* Copy the PlaceHolderVar node with correct mutation of subnodes */
419  PlaceHolderVar *phv;
420 
423  (void *) context);
424  /* now fix PlaceHolderVar's relid sets */
425  if (phv->phlevelsup == 0)
426  {
427  phv->phrels = adjust_child_relids(phv->phrels,
428  nappinfos, appinfos);
429  /* as above, we needn't touch phnullingrels */
430  }
431  return (Node *) phv;
432  }
433  /* Shouldn't need to handle planner auxiliary nodes here */
434  Assert(!IsA(node, SpecialJoinInfo));
435  Assert(!IsA(node, AppendRelInfo));
436  Assert(!IsA(node, PlaceHolderInfo));
437  Assert(!IsA(node, MinMaxAggInfo));
438 
439  /*
440  * We have to process RestrictInfo nodes specially. (Note: although
441  * set_append_rel_pathlist will hide RestrictInfos in the parent's
442  * baserestrictinfo list from us, it doesn't hide those in joininfo.)
443  */
444  if (IsA(node, RestrictInfo))
445  {
446  RestrictInfo *oldinfo = (RestrictInfo *) node;
447  RestrictInfo *newinfo = makeNode(RestrictInfo);
448 
449  /* Copy all flat-copiable fields, notably including rinfo_serial */
450  memcpy(newinfo, oldinfo, sizeof(RestrictInfo));
451 
452  /* Recursively fix the clause itself */
453  newinfo->clause = (Expr *)
454  adjust_appendrel_attrs_mutator((Node *) oldinfo->clause, context);
455 
456  /* and the modified version, if an OR clause */
457  newinfo->orclause = (Expr *)
458  adjust_appendrel_attrs_mutator((Node *) oldinfo->orclause, context);
459 
460  /* adjust relid sets too */
461  newinfo->clause_relids = adjust_child_relids(oldinfo->clause_relids,
462  context->nappinfos,
463  context->appinfos);
465  context->nappinfos,
466  context->appinfos);
467  newinfo->outer_relids = adjust_child_relids(oldinfo->outer_relids,
468  context->nappinfos,
469  context->appinfos);
470  newinfo->left_relids = adjust_child_relids(oldinfo->left_relids,
471  context->nappinfos,
472  context->appinfos);
473  newinfo->right_relids = adjust_child_relids(oldinfo->right_relids,
474  context->nappinfos,
475  context->appinfos);
476 
477  /*
478  * Reset cached derivative fields, since these might need to have
479  * different values when considering the child relation. Note we
480  * don't reset left_ec/right_ec: each child variable is implicitly
481  * equivalent to its parent, so still a member of the same EC if any.
482  */
483  newinfo->eval_cost.startup = -1;
484  newinfo->norm_selec = -1;
485  newinfo->outer_selec = -1;
486  newinfo->left_em = NULL;
487  newinfo->right_em = NULL;
488  newinfo->scansel_cache = NIL;
489  newinfo->left_bucketsize = -1;
490  newinfo->right_bucketsize = -1;
491  newinfo->left_mcvfreq = -1;
492  newinfo->right_mcvfreq = -1;
493 
494  return (Node *) newinfo;
495  }
496 
497  /*
498  * NOTE: we do not need to recurse into sublinks, because they should
499  * already have been converted to subplans before we see them.
500  */
501  Assert(!IsA(node, SubLink));
502  Assert(!IsA(node, Query));
503  /* We should never see these Query substructures, either. */
504  Assert(!IsA(node, RangeTblRef));
505  Assert(!IsA(node, JoinExpr));
506 
508  (void *) context);
509 }
Relids adjust_child_relids(Relids relids, int nappinfos, AppendRelInfo **appinfos)
Definition: appendinfo.c:553
unsigned int Index
Definition: c.h:598
#define OidIsValid(objectId)
Definition: c.h:759
char * get_rel_name(Oid relid)
Definition: lsyscache.c:1910
Const * makeNullConst(Oid consttype, int32 consttypmod, Oid constcollid)
Definition: makefuncs.c:339
#define expression_tree_mutator(n, m, c)
Definition: nodeFuncs.h:153
#define rt_fetch(rangetable_index, rangetable)
Definition: parsetree.h:31
#define NIL
Definition: pg_list.h:68
static void * list_nth(const List *list, int n)
Definition: pg_list.h:299
@ COERCE_IMPLICIT_CAST
Definition: primnodes.h:663
List * colnames
Definition: primnodes.h:43
Index child_relid
Definition: pathnodes.h:2904
List * translated_vars
Definition: pathnodes.h:2931
Index parent_relid
Definition: pathnodes.h:2903
Oid parent_reltype
Definition: pathnodes.h:2912
Definition: pg_list.h:54
Index phlevelsup
Definition: pathnodes.h:2740
List * rtable
Definition: parsenodes.h:175
Alias * eref
Definition: parsenodes.h:1200
Relids required_relids
Definition: pathnodes.h:2544
Relids outer_relids
Definition: pathnodes.h:2547
Expr * clause
Definition: pathnodes.h:2513
int location
Definition: primnodes.h:1360
List * args
Definition: primnodes.h:1336
AttrNumber varattno
Definition: primnodes.h:238

References adjust_child_relids(), adjust_appendrel_attrs_context::appinfos, ConvertRowtypeExpr::arg, RowExpr::args, Assert(), bms_is_member(), AppendRelInfo::child_relid, AppendRelInfo::child_reltype, RestrictInfo::clause, COERCE_IMPLICIT_CAST, Alias::colnames, copyObject, CurrentOfExpr::cvarno, elog(), RangeTblEntry::eref, ERROR, expression_tree_mutator, get_rel_name(), IsA, PlannerInfo::leaf_result_relids, list_length(), list_nth(), ConvertRowtypeExpr::location, RowExpr::location, makeNode, makeNullConst(), adjust_appendrel_attrs_context::nappinfos, NIL, OidIsValid, RestrictInfo::outer_relids, AppendRelInfo::parent_relid, AppendRelInfo::parent_reloid, AppendRelInfo::parent_reltype, PlannerInfo::parse, PlaceHolderVar::phlevelsup, RestrictInfo::required_relids, ConvertRowtypeExpr::resulttype, adjust_appendrel_attrs_context::root, PlannerInfo::row_identity_vars, ROWID_VAR, RowIdentityVarInfo::rowidrels, RowIdentityVarInfo::rowidvar, rt_fetch, Query::rtable, AppendRelInfo::translated_vars, Var::varattno, Var::varlevelsup, and Var::varno.

Referenced by adjust_appendrel_attrs().

◆ adjust_child_relids()

Relids adjust_child_relids ( Relids  relids,
int  nappinfos,
AppendRelInfo **  appinfos 
)

Definition at line 553 of file appendinfo.c.

554 {
555  Bitmapset *result = NULL;
556  int cnt;
557 
558  for (cnt = 0; cnt < nappinfos; cnt++)
559  {
560  AppendRelInfo *appinfo = appinfos[cnt];
561 
562  /* Remove parent, add child */
563  if (bms_is_member(appinfo->parent_relid, relids))
564  {
565  /* Make a copy if we are changing the set. */
566  if (!result)
567  result = bms_copy(relids);
568 
569  result = bms_del_member(result, appinfo->parent_relid);
570  result = bms_add_member(result, appinfo->child_relid);
571  }
572  }
573 
574  /* If we made any changes, return the modified copy. */
575  if (result)
576  return result;
577 
578  /* Otherwise, return the original set without modification. */
579  return relids;
580 }
Bitmapset * bms_del_member(Bitmapset *a, int x)
Definition: bitmapset.c:792
Bitmapset * bms_copy(const Bitmapset *a)
Definition: bitmapset.c:74

References bms_add_member(), bms_copy(), bms_del_member(), bms_is_member(), AppendRelInfo::child_relid, and AppendRelInfo::parent_relid.

Referenced by adjust_appendrel_attrs_mutator(), adjust_child_relids_multilevel(), and build_child_join_sjinfo().

◆ adjust_child_relids_multilevel()

Relids adjust_child_relids_multilevel ( PlannerInfo root,
Relids  relids,
RelOptInfo childrel,
RelOptInfo parentrel 
)

Definition at line 587 of file appendinfo.c.

590 {
591  AppendRelInfo **appinfos;
592  int nappinfos;
593 
594  /*
595  * If the given relids set doesn't contain any of the parent relids, it
596  * will remain unchanged.
597  */
598  if (!bms_overlap(relids, parentrel->relids))
599  return relids;
600 
601  /* Recurse if immediate parent is not the top parent. */
602  if (childrel->parent != parentrel)
603  {
604  if (childrel->parent)
605  relids = adjust_child_relids_multilevel(root, relids,
606  childrel->parent,
607  parentrel);
608  else
609  elog(ERROR, "childrel is not a child of parentrel");
610  }
611 
612  /* Now translate for this child. */
613  appinfos = find_appinfos_by_relids(root, childrel->relids, &nappinfos);
614 
615  relids = adjust_child_relids(relids, nappinfos, appinfos);
616 
617  pfree(appinfos);
618 
619  return relids;
620 }
Relids adjust_child_relids_multilevel(PlannerInfo *root, Relids relids, RelOptInfo *childrel, RelOptInfo *parentrel)
Definition: appendinfo.c:587
bool bms_overlap(const Bitmapset *a, const Bitmapset *b)
Definition: bitmapset.c:511

References adjust_child_relids(), bms_overlap(), elog(), ERROR, find_appinfos_by_relids(), pfree(), and RelOptInfo::relids.

Referenced by reparameterize_path_by_child().

◆ adjust_inherited_attnums()

List* adjust_inherited_attnums ( List attnums,
AppendRelInfo context 
)

Definition at line 627 of file appendinfo.c.

628 {
629  List *result = NIL;
630  ListCell *lc;
631 
632  /* This should only happen for an inheritance case, not UNION ALL */
633  Assert(OidIsValid(context->parent_reloid));
634 
635  /* Look up each attribute in the AppendRelInfo's translated_vars list */
636  foreach(lc, attnums)
637  {
638  AttrNumber parentattno = lfirst_int(lc);
639  Var *childvar;
640 
641  /* Look up the translation of this column: it must be a Var */
642  if (parentattno <= 0 ||
643  parentattno > list_length(context->translated_vars))
644  elog(ERROR, "attribute %d of relation \"%s\" does not exist",
645  parentattno, get_rel_name(context->parent_reloid));
646  childvar = (Var *) list_nth(context->translated_vars, parentattno - 1);
647  if (childvar == NULL || !IsA(childvar, Var))
648  elog(ERROR, "attribute %d of relation \"%s\" does not exist",
649  parentattno, get_rel_name(context->parent_reloid));
650 
651  result = lappend_int(result, childvar->varattno);
652  }
653  return result;
654 }
int16 AttrNumber
Definition: attnum.h:21
List * lappend_int(List *list, int datum)
Definition: list.c:356
#define lfirst_int(lc)
Definition: pg_list.h:173

References Assert(), elog(), ERROR, get_rel_name(), IsA, lappend_int(), lfirst_int, list_length(), list_nth(), NIL, OidIsValid, AppendRelInfo::parent_reloid, AppendRelInfo::translated_vars, and Var::varattno.

Referenced by adjust_inherited_attnums_multilevel().

◆ adjust_inherited_attnums_multilevel()

List* adjust_inherited_attnums_multilevel ( PlannerInfo root,
List attnums,
Index  child_relid,
Index  top_parent_relid 
)

Definition at line 661 of file appendinfo.c.

663 {
664  AppendRelInfo *appinfo = root->append_rel_array[child_relid];
665 
666  if (!appinfo)
667  elog(ERROR, "child rel %d not found in append_rel_array", child_relid);
668 
669  /* Recurse if immediate parent is not the top parent. */
670  if (appinfo->parent_relid != top_parent_relid)
671  attnums = adjust_inherited_attnums_multilevel(root, attnums,
672  appinfo->parent_relid,
673  top_parent_relid);
674 
675  /* Now translate for this child */
676  return adjust_inherited_attnums(attnums, appinfo);
677 }
List * adjust_inherited_attnums(List *attnums, AppendRelInfo *context)
Definition: appendinfo.c:627
List * adjust_inherited_attnums_multilevel(PlannerInfo *root, List *attnums, Index child_relid, Index top_parent_relid)
Definition: appendinfo.c:661

References adjust_inherited_attnums(), elog(), ERROR, and AppendRelInfo::parent_relid.

Referenced by get_translated_update_targetlist(), and grouping_planner().

◆ distribute_row_identity_vars()

void distribute_row_identity_vars ( PlannerInfo root)

Definition at line 965 of file appendinfo.c.

966 {
967  Query *parse = root->parse;
968  int result_relation = parse->resultRelation;
969  RangeTblEntry *target_rte;
970  RelOptInfo *target_rel;
971  ListCell *lc;
972 
973  /*
974  * There's nothing to do if this isn't an inherited UPDATE/DELETE/MERGE.
975  */
976  if (parse->commandType != CMD_UPDATE && parse->commandType != CMD_DELETE &&
977  parse->commandType != CMD_MERGE)
978  {
979  Assert(root->row_identity_vars == NIL);
980  return;
981  }
982  target_rte = rt_fetch(result_relation, parse->rtable);
983  if (!target_rte->inh)
984  {
985  Assert(root->row_identity_vars == NIL);
986  return;
987  }
988 
989  /*
990  * Ordinarily, we expect that leaf result relation(s) will have added some
991  * ROWID_VAR Vars to the query. However, it's possible that constraint
992  * exclusion suppressed every leaf relation. The executor will get upset
993  * if the plan has no row identity columns at all, even though it will
994  * certainly process no rows. Handle this edge case by re-opening the top
995  * result relation and adding the row identity columns it would have used,
996  * as preprocess_targetlist() would have done if it weren't marked "inh".
997  * (This is a bit ugly, but it seems better to confine the ugliness and
998  * extra cycles to this unusual corner case.) We needn't worry about
999  * fixing the rel's reltarget, as that won't affect the finished plan.
1000  */
1001  if (root->row_identity_vars == NIL)
1002  {
1003  Relation target_relation;
1004 
1005  target_relation = table_open(target_rte->relid, NoLock);
1006  add_row_identity_columns(root, result_relation,
1007  target_rte, target_relation);
1008  table_close(target_relation, NoLock);
1009  return;
1010  }
1011 
1012  /*
1013  * Dig through the processed_tlist to find the ROWID_VAR reference Vars,
1014  * and forcibly copy them into the reltarget list of the topmost target
1015  * relation. That's sufficient because they'll be copied to the
1016  * individual leaf target rels (with appropriate translation) later,
1017  * during appendrel expansion --- see set_append_rel_size().
1018  */
1019  target_rel = find_base_rel(root, result_relation);
1020 
1021  foreach(lc, root->processed_tlist)
1022  {
1023  TargetEntry *tle = lfirst(lc);
1024  Var *var = (Var *) tle->expr;
1025 
1026  if (var && IsA(var, Var) && var->varno == ROWID_VAR)
1027  {
1028  target_rel->reltarget->exprs =
1029  lappend(target_rel->reltarget->exprs, copyObject(var));
1030  /* reltarget cost and width will be computed later */
1031  }
1032  }
1033 }
void add_row_identity_columns(PlannerInfo *root, Index rtindex, RangeTblEntry *target_rte, Relation target_relation)
Definition: appendinfo.c:883
if(TABLE==NULL||TABLE_index==NULL)
Definition: isn.c:77
#define NoLock
Definition: lockdefs.h:34
static struct subre * parse(struct vars *v, int stopper, int type, struct state *init, struct state *final)
Definition: regcomp.c:717
RelOptInfo * find_base_rel(PlannerInfo *root, int relid)
Definition: relnode.c:404
List * exprs
Definition: pathnodes.h:1507
struct PathTarget * reltarget
Definition: pathnodes.h:884
Expr * expr
Definition: primnodes.h:1731
void table_close(Relation relation, LOCKMODE lockmode)
Definition: table.c:126
Relation table_open(Oid relationId, LOCKMODE lockmode)
Definition: table.c:40

References add_row_identity_columns(), Assert(), CMD_DELETE, CMD_MERGE, CMD_UPDATE, copyObject, TargetEntry::expr, PathTarget::exprs, find_base_rel(), if(), RangeTblEntry::inh, IsA, lappend(), lfirst, NIL, NoLock, parse(), PlannerInfo::parse, PlannerInfo::processed_tlist, RangeTblEntry::relid, RelOptInfo::reltarget, PlannerInfo::row_identity_vars, ROWID_VAR, rt_fetch, table_close(), table_open(), and Var::varno.

Referenced by query_planner().

◆ find_appinfos_by_relids()

AppendRelInfo** find_appinfos_by_relids ( PlannerInfo root,
Relids  relids,
int *  nappinfos 
)

Definition at line 732 of file appendinfo.c.

733 {
734  AppendRelInfo **appinfos;
735  int cnt = 0;
736  int i;
737 
738  /* Allocate an array that's certainly big enough */
739  appinfos = (AppendRelInfo **)
740  palloc(sizeof(AppendRelInfo *) * bms_num_members(relids));
741 
742  i = -1;
743  while ((i = bms_next_member(relids, i)) >= 0)
744  {
745  AppendRelInfo *appinfo = root->append_rel_array[i];
746 
747  if (!appinfo)
748  {
749  /* Probably i is an OJ index, but let's check */
750  if (find_base_rel_ignore_join(root, i) == NULL)
751  continue;
752  /* It's a base rel, but we lack an append_rel_array entry */
753  elog(ERROR, "child rel %d not found in append_rel_array", i);
754  }
755 
756  appinfos[cnt++] = appinfo;
757  }
758  *nappinfos = cnt;
759  return appinfos;
760 }
int bms_next_member(const Bitmapset *a, int prevbit)
Definition: bitmapset.c:1039
int bms_num_members(const Bitmapset *a)
Definition: bitmapset.c:665
int i
Definition: isn.c:73
void * palloc(Size size)
Definition: mcxt.c:1210
RelOptInfo * find_base_rel_ignore_join(PlannerInfo *root, int relid)
Definition: relnode.c:432

References bms_next_member(), bms_num_members(), elog(), ERROR, find_base_rel_ignore_join(), i, and palloc().

Referenced by adjust_appendrel_attrs_multilevel(), adjust_child_relids_multilevel(), apply_scanjoin_target_to_paths(), build_child_join_rel(), build_child_join_sjinfo(), create_partitionwise_grouping_paths(), make_partitionedrel_pruneinfo(), and try_partitionwise_join().

◆ get_translated_update_targetlist()

void get_translated_update_targetlist ( PlannerInfo root,
Index  relid,
List **  processed_tlist,
List **  update_colnos 
)

Definition at line 689 of file appendinfo.c.

691 {
692  /* This is pretty meaningless for commands other than UPDATE. */
693  Assert(root->parse->commandType == CMD_UPDATE);
694  if (relid == root->parse->resultRelation)
695  {
696  /*
697  * Non-inheritance case, so it's easy. The caller might be expecting
698  * a tree it can scribble on, though, so copy.
699  */
700  *processed_tlist = copyObject(root->processed_tlist);
701  if (update_colnos)
702  *update_colnos = copyObject(root->update_colnos);
703  }
704  else
705  {
706  Assert(bms_is_member(relid, root->all_result_relids));
707  *processed_tlist = (List *)
709  (Node *) root->processed_tlist,
710  find_base_rel(root, relid),
711  find_base_rel(root, root->parse->resultRelation));
712  if (update_colnos)
713  *update_colnos =
715  relid,
716  root->parse->resultRelation);
717  }
718 }
List * update_colnos
Definition: pathnodes.h:464
Relids all_result_relids
Definition: pathnodes.h:354

References adjust_appendrel_attrs_multilevel(), adjust_inherited_attnums_multilevel(), PlannerInfo::all_result_relids, Assert(), bms_is_member(), CMD_UPDATE, Query::commandType, copyObject, find_base_rel(), PlannerInfo::parse, PlannerInfo::processed_tlist, and PlannerInfo::update_colnos.

Referenced by postgresPlanDirectModify().

◆ make_append_rel_info()

AppendRelInfo* make_append_rel_info ( Relation  parentrel,
Relation  childrel,
Index  parentRTindex,
Index  childRTindex 
)

Definition at line 50 of file appendinfo.c.

52 {
54 
55  appinfo->parent_relid = parentRTindex;
56  appinfo->child_relid = childRTindex;
57  appinfo->parent_reltype = parentrel->rd_rel->reltype;
58  appinfo->child_reltype = childrel->rd_rel->reltype;
59  make_inh_translation_list(parentrel, childrel, childRTindex, appinfo);
60  appinfo->parent_reloid = RelationGetRelid(parentrel);
61 
62  return appinfo;
63 }
static void make_inh_translation_list(Relation oldrelation, Relation newrelation, Index newvarno, AppendRelInfo *appinfo)
Definition: appendinfo.c:79
#define RelationGetRelid(relation)
Definition: rel.h:503

References AppendRelInfo::child_relid, AppendRelInfo::child_reltype, make_inh_translation_list(), makeNode, AppendRelInfo::parent_relid, AppendRelInfo::parent_reloid, AppendRelInfo::parent_reltype, RelationData::rd_rel, and RelationGetRelid.

Referenced by expand_single_inheritance_child().

◆ make_inh_translation_list()

static void make_inh_translation_list ( Relation  oldrelation,
Relation  newrelation,
Index  newvarno,
AppendRelInfo appinfo 
)
static

Definition at line 79 of file appendinfo.c.

82 {
83  List *vars = NIL;
84  AttrNumber *pcolnos;
85  TupleDesc old_tupdesc = RelationGetDescr(oldrelation);
86  TupleDesc new_tupdesc = RelationGetDescr(newrelation);
87  Oid new_relid = RelationGetRelid(newrelation);
88  int oldnatts = old_tupdesc->natts;
89  int newnatts = new_tupdesc->natts;
90  int old_attno;
91  int new_attno = 0;
92 
93  /* Initialize reverse-translation array with all entries zero */
94  appinfo->num_child_cols = newnatts;
95  appinfo->parent_colnos = pcolnos =
96  (AttrNumber *) palloc0(newnatts * sizeof(AttrNumber));
97 
98  for (old_attno = 0; old_attno < oldnatts; old_attno++)
99  {
100  Form_pg_attribute att;
101  char *attname;
102  Oid atttypid;
103  int32 atttypmod;
104  Oid attcollation;
105 
106  att = TupleDescAttr(old_tupdesc, old_attno);
107  if (att->attisdropped)
108  {
109  /* Just put NULL into this list entry */
110  vars = lappend(vars, NULL);
111  continue;
112  }
113  attname = NameStr(att->attname);
114  atttypid = att->atttypid;
115  atttypmod = att->atttypmod;
116  attcollation = att->attcollation;
117 
118  /*
119  * When we are generating the "translation list" for the parent table
120  * of an inheritance set, no need to search for matches.
121  */
122  if (oldrelation == newrelation)
123  {
124  vars = lappend(vars, makeVar(newvarno,
125  (AttrNumber) (old_attno + 1),
126  atttypid,
127  atttypmod,
128  attcollation,
129  0));
130  pcolnos[old_attno] = old_attno + 1;
131  continue;
132  }
133 
134  /*
135  * Otherwise we have to search for the matching column by name.
136  * There's no guarantee it'll have the same column position, because
137  * of cases like ALTER TABLE ADD COLUMN and multiple inheritance.
138  * However, in simple cases, the relative order of columns is mostly
139  * the same in both relations, so try the column of newrelation that
140  * follows immediately after the one that we just found, and if that
141  * fails, let syscache handle it.
142  */
143  if (new_attno >= newnatts ||
144  (att = TupleDescAttr(new_tupdesc, new_attno))->attisdropped ||
145  strcmp(attname, NameStr(att->attname)) != 0)
146  {
147  HeapTuple newtup;
148 
149  newtup = SearchSysCacheAttName(new_relid, attname);
150  if (!HeapTupleIsValid(newtup))
151  elog(ERROR, "could not find inherited attribute \"%s\" of relation \"%s\"",
152  attname, RelationGetRelationName(newrelation));
153  new_attno = ((Form_pg_attribute) GETSTRUCT(newtup))->attnum - 1;
154  Assert(new_attno >= 0 && new_attno < newnatts);
155  ReleaseSysCache(newtup);
156 
157  att = TupleDescAttr(new_tupdesc, new_attno);
158  }
159 
160  /* Found it, check type and collation match */
161  if (atttypid != att->atttypid || atttypmod != att->atttypmod)
162  elog(ERROR, "attribute \"%s\" of relation \"%s\" does not match parent's type",
163  attname, RelationGetRelationName(newrelation));
164  if (attcollation != att->attcollation)
165  elog(ERROR, "attribute \"%s\" of relation \"%s\" does not match parent's collation",
166  attname, RelationGetRelationName(newrelation));
167 
168  vars = lappend(vars, makeVar(newvarno,
169  (AttrNumber) (new_attno + 1),
170  atttypid,
171  atttypmod,
172  attcollation,
173  0));
174  pcolnos[new_attno] = old_attno + 1;
175  new_attno++;
176  }
177 
178  appinfo->translated_vars = vars;
179 }
#define NameStr(name)
Definition: c.h:730
signed int int32
Definition: c.h:478
#define HeapTupleIsValid(tuple)
Definition: htup.h:78
#define GETSTRUCT(TUP)
Definition: htup_details.h:653
void * palloc0(Size size)
Definition: mcxt.c:1241
NameData attname
Definition: pg_attribute.h:41
int16 attnum
Definition: pg_attribute.h:83
FormData_pg_attribute * Form_pg_attribute
Definition: pg_attribute.h:207
unsigned int Oid
Definition: postgres_ext.h:31
#define RelationGetDescr(relation)
Definition: rel.h:529
#define RelationGetRelationName(relation)
Definition: rel.h:537
int num_child_cols
Definition: pathnodes.h:2939
Definition: regcomp.c:282
void ReleaseSysCache(HeapTuple tuple)
Definition: syscache.c:865
HeapTuple SearchSysCacheAttName(Oid relid, const char *attname)
Definition: syscache.c:958
#define TupleDescAttr(tupdesc, i)
Definition: tupdesc.h:92

References Assert(), attname, attnum, elog(), ERROR, GETSTRUCT, HeapTupleIsValid, lappend(), makeVar(), NameStr, TupleDescData::natts, NIL, AppendRelInfo::num_child_cols, palloc0(), RelationGetDescr, RelationGetRelationName, RelationGetRelid, ReleaseSysCache(), SearchSysCacheAttName(), AppendRelInfo::translated_vars, and TupleDescAttr.

Referenced by make_append_rel_info().