]> granicus.if.org Git - postgresql/blob - src/backend/parser/parse_utilcmd.c
Reduce lock levels of CREATE TRIGGER and some ALTER TABLE, CREATE RULE actions.
[postgresql] / src / backend / parser / parse_utilcmd.c
1 /*-------------------------------------------------------------------------
2  *
3  * parse_utilcmd.c
4  *        Perform parse analysis work for various utility commands
5  *
6  * Formerly we did this work during parse_analyze() in analyze.c.  However
7  * that is fairly unsafe in the presence of querytree caching, since any
8  * database state that we depend on in making the transformations might be
9  * obsolete by the time the utility command is executed; and utility commands
10  * have no infrastructure for holding locks or rechecking plan validity.
11  * Hence these functions are now called at the start of execution of their
12  * respective utility commands.
13  *
14  * NOTE: in general we must avoid scribbling on the passed-in raw parse
15  * tree, since it might be in a plan cache.  The simplest solution is
16  * a quick copyObject() call before manipulating the query tree.
17  *
18  *
19  * Portions Copyright (c) 1996-2010, PostgreSQL Global Development Group
20  * Portions Copyright (c) 1994, Regents of the University of California
21  *
22  *      $PostgreSQL: pgsql/src/backend/parser/parse_utilcmd.c,v 2.41 2010/07/28 05:22:24 sriggs Exp $
23  *
24  *-------------------------------------------------------------------------
25  */
26
27 #include "postgres.h"
28
29 #include "access/genam.h"
30 #include "access/heapam.h"
31 #include "access/reloptions.h"
32 #include "catalog/dependency.h"
33 #include "catalog/heap.h"
34 #include "catalog/index.h"
35 #include "catalog/namespace.h"
36 #include "catalog/pg_constraint.h"
37 #include "catalog/pg_opclass.h"
38 #include "catalog/pg_operator.h"
39 #include "catalog/pg_type.h"
40 #include "commands/comment.h"
41 #include "commands/defrem.h"
42 #include "commands/tablecmds.h"
43 #include "commands/tablespace.h"
44 #include "miscadmin.h"
45 #include "nodes/makefuncs.h"
46 #include "nodes/nodeFuncs.h"
47 #include "parser/analyze.h"
48 #include "parser/parse_clause.h"
49 #include "parser/parse_expr.h"
50 #include "parser/parse_relation.h"
51 #include "parser/parse_target.h"
52 #include "parser/parse_type.h"
53 #include "parser/parse_utilcmd.h"
54 #include "parser/parser.h"
55 #include "rewrite/rewriteManip.h"
56 #include "storage/lock.h"
57 #include "utils/acl.h"
58 #include "utils/builtins.h"
59 #include "utils/lsyscache.h"
60 #include "utils/relcache.h"
61 #include "utils/syscache.h"
62 #include "utils/typcache.h"
63
64
65 /* State shared by transformCreateStmt and its subroutines */
66 typedef struct
67 {
68         const char *stmtType;           /* "CREATE TABLE" or "ALTER TABLE" */
69         RangeVar   *relation;           /* relation to create */
70         Relation        rel;                    /* opened/locked rel, if ALTER */
71         List       *inhRelations;       /* relations to inherit from */
72         bool            isalter;                /* true if altering existing table */
73         bool            hasoids;                /* does relation have an OID column? */
74         List       *columns;            /* ColumnDef items */
75         List       *ckconstraints;      /* CHECK constraints */
76         List       *fkconstraints;      /* FOREIGN KEY constraints */
77         List       *ixconstraints;      /* index-creating constraints */
78         List       *inh_indexes;        /* cloned indexes from INCLUDING INDEXES */
79         List       *blist;                      /* "before list" of things to do before
80                                                                  * creating the table */
81         List       *alist;                      /* "after list" of things to do after creating
82                                                                  * the table */
83         IndexStmt  *pkey;                       /* PRIMARY KEY index, if any */
84 } CreateStmtContext;
85
86 /* State shared by transformCreateSchemaStmt and its subroutines */
87 typedef struct
88 {
89         const char *stmtType;           /* "CREATE SCHEMA" or "ALTER SCHEMA" */
90         char       *schemaname;         /* name of schema */
91         char       *authid;                     /* owner of schema */
92         List       *sequences;          /* CREATE SEQUENCE items */
93         List       *tables;                     /* CREATE TABLE items */
94         List       *views;                      /* CREATE VIEW items */
95         List       *indexes;            /* CREATE INDEX items */
96         List       *triggers;           /* CREATE TRIGGER items */
97         List       *grants;                     /* GRANT items */
98 } CreateSchemaStmtContext;
99
100
101 static void transformColumnDefinition(ParseState *pstate,
102                                                   CreateStmtContext *cxt,
103                                                   ColumnDef *column);
104 static void transformTableConstraint(ParseState *pstate,
105                                                  CreateStmtContext *cxt,
106                                                  Constraint *constraint);
107 static void transformInhRelation(ParseState *pstate, CreateStmtContext *cxt,
108                                          InhRelation *inhrelation);
109 static void transformOfType(ParseState *pstate, CreateStmtContext *cxt,
110                                 TypeName *ofTypename);
111 static char *chooseIndexName(const RangeVar *relation, IndexStmt *index_stmt);
112 static IndexStmt *generateClonedIndexStmt(CreateStmtContext *cxt,
113                                                 Relation parent_index, AttrNumber *attmap);
114 static List *get_opclass(Oid opclass, Oid actual_datatype);
115 static void transformIndexConstraints(ParseState *pstate,
116                                                   CreateStmtContext *cxt);
117 static IndexStmt *transformIndexConstraint(Constraint *constraint,
118                                                  CreateStmtContext *cxt);
119 static void transformFKConstraints(ParseState *pstate,
120                                            CreateStmtContext *cxt,
121                                            bool skipValidation,
122                                            bool isAddConstraint);
123 static void transformConstraintAttrs(ParseState *pstate, List *constraintList);
124 static void transformColumnType(ParseState *pstate, ColumnDef *column);
125 static void setSchemaName(char *context_schema, char **stmt_schema_name);
126
127
128 /*
129  * transformCreateStmt -
130  *        parse analysis for CREATE TABLE
131  *
132  * Returns a List of utility commands to be done in sequence.  One of these
133  * will be the transformed CreateStmt, but there may be additional actions
134  * to be done before and after the actual DefineRelation() call.
135  *
136  * SQL92 allows constraints to be scattered all over, so thumb through
137  * the columns and collect all constraints into one place.
138  * If there are any implied indices (e.g. UNIQUE or PRIMARY KEY)
139  * then expand those into multiple IndexStmt blocks.
140  *        - thomas 1997-12-02
141  */
142 List *
143 transformCreateStmt(CreateStmt *stmt, const char *queryString)
144 {
145         ParseState *pstate;
146         CreateStmtContext cxt;
147         List       *result;
148         List       *save_alist;
149         ListCell   *elements;
150
151         /*
152          * We must not scribble on the passed-in CreateStmt, so copy it.  (This is
153          * overkill, but easy.)
154          */
155         stmt = (CreateStmt *) copyObject(stmt);
156
157         /*
158          * If the target relation name isn't schema-qualified, make it so.  This
159          * prevents some corner cases in which added-on rewritten commands might
160          * think they should apply to other relations that have the same name and
161          * are earlier in the search path.      "istemp" is equivalent to a
162          * specification of pg_temp, so no need for anything extra in that case.
163          */
164         if (stmt->relation->schemaname == NULL && !stmt->relation->istemp)
165         {
166                 Oid                     namespaceid = RangeVarGetCreationNamespace(stmt->relation);
167
168                 stmt->relation->schemaname = get_namespace_name(namespaceid);
169         }
170
171         /* Set up pstate */
172         pstate = make_parsestate(NULL);
173         pstate->p_sourcetext = queryString;
174
175         cxt.stmtType = "CREATE TABLE";
176         cxt.relation = stmt->relation;
177         cxt.rel = NULL;
178         cxt.inhRelations = stmt->inhRelations;
179         cxt.isalter = false;
180         cxt.columns = NIL;
181         cxt.ckconstraints = NIL;
182         cxt.fkconstraints = NIL;
183         cxt.ixconstraints = NIL;
184         cxt.inh_indexes = NIL;
185         cxt.blist = NIL;
186         cxt.alist = NIL;
187         cxt.pkey = NULL;
188         cxt.hasoids = interpretOidsOption(stmt->options);
189
190         Assert(!stmt->ofTypename || !stmt->inhRelations);       /* grammar enforces */
191
192         if (stmt->ofTypename)
193                 transformOfType(pstate, &cxt, stmt->ofTypename);
194
195         /*
196          * Run through each primary element in the table creation clause. Separate
197          * column defs from constraints, and do preliminary analysis.
198          */
199         foreach(elements, stmt->tableElts)
200         {
201                 Node       *element = lfirst(elements);
202
203                 switch (nodeTag(element))
204                 {
205                         case T_ColumnDef:
206                                 transformColumnDefinition(pstate, &cxt,
207                                                                                   (ColumnDef *) element);
208                                 break;
209
210                         case T_Constraint:
211                                 transformTableConstraint(pstate, &cxt,
212                                                                                  (Constraint *) element);
213                                 break;
214
215                         case T_InhRelation:
216                                 transformInhRelation(pstate, &cxt,
217                                                                          (InhRelation *) element);
218                                 break;
219
220                         default:
221                                 elog(ERROR, "unrecognized node type: %d",
222                                          (int) nodeTag(element));
223                                 break;
224                 }
225         }
226
227         /*
228          * transformIndexConstraints wants cxt.alist to contain only index
229          * statements, so transfer anything we already have into save_alist.
230          */
231         save_alist = cxt.alist;
232         cxt.alist = NIL;
233
234         Assert(stmt->constraints == NIL);
235
236         /*
237          * Postprocess constraints that give rise to index definitions.
238          */
239         transformIndexConstraints(pstate, &cxt);
240
241         /*
242          * Postprocess foreign-key constraints.
243          */
244         transformFKConstraints(pstate, &cxt, true, false);
245
246         /*
247          * Output results.
248          */
249         stmt->tableElts = cxt.columns;
250         stmt->constraints = cxt.ckconstraints;
251
252         result = lappend(cxt.blist, stmt);
253         result = list_concat(result, cxt.alist);
254         result = list_concat(result, save_alist);
255
256         return result;
257 }
258
259 /*
260  * transformColumnDefinition -
261  *              transform a single ColumnDef within CREATE TABLE
262  *              Also used in ALTER TABLE ADD COLUMN
263  */
264 static void
265 transformColumnDefinition(ParseState *pstate, CreateStmtContext *cxt,
266                                                   ColumnDef *column)
267 {
268         bool            is_serial;
269         bool            saw_nullable;
270         bool            saw_default;
271         Constraint *constraint;
272         ListCell   *clist;
273
274         cxt->columns = lappend(cxt->columns, column);
275
276         /* Check for SERIAL pseudo-types */
277         is_serial = false;
278         if (column->typeName
279                 && list_length(column->typeName->names) == 1
280                 && !column->typeName->pct_type)
281         {
282                 char       *typname = strVal(linitial(column->typeName->names));
283
284                 if (strcmp(typname, "serial") == 0 ||
285                         strcmp(typname, "serial4") == 0)
286                 {
287                         is_serial = true;
288                         column->typeName->names = NIL;
289                         column->typeName->typeOid = INT4OID;
290                 }
291                 else if (strcmp(typname, "bigserial") == 0 ||
292                                  strcmp(typname, "serial8") == 0)
293                 {
294                         is_serial = true;
295                         column->typeName->names = NIL;
296                         column->typeName->typeOid = INT8OID;
297                 }
298
299                 /*
300                  * We have to reject "serial[]" explicitly, because once we've set
301                  * typeid, LookupTypeName won't notice arrayBounds.  We don't need any
302                  * special coding for serial(typmod) though.
303                  */
304                 if (is_serial && column->typeName->arrayBounds != NIL)
305                         ereport(ERROR,
306                                         (errcode(ERRCODE_FEATURE_NOT_SUPPORTED),
307                                          errmsg("array of serial is not implemented"),
308                                          parser_errposition(pstate, column->typeName->location)));
309         }
310
311         /* Do necessary work on the column type declaration */
312         if (column->typeName)
313                 transformColumnType(pstate, column);
314
315         /* Special actions for SERIAL pseudo-types */
316         if (is_serial)
317         {
318                 Oid                     snamespaceid;
319                 char       *snamespace;
320                 char       *sname;
321                 char       *qstring;
322                 A_Const    *snamenode;
323                 TypeCast   *castnode;
324                 FuncCall   *funccallnode;
325                 CreateSeqStmt *seqstmt;
326                 AlterSeqStmt *altseqstmt;
327                 List       *attnamelist;
328
329                 /*
330                  * Determine namespace and name to use for the sequence.
331                  *
332                  * Although we use ChooseRelationName, it's not guaranteed that the
333                  * selected sequence name won't conflict; given sufficiently long
334                  * field names, two different serial columns in the same table could
335                  * be assigned the same sequence name, and we'd not notice since we
336                  * aren't creating the sequence quite yet.  In practice this seems
337                  * quite unlikely to be a problem, especially since few people would
338                  * need two serial columns in one table.
339                  */
340                 if (cxt->rel)
341                         snamespaceid = RelationGetNamespace(cxt->rel);
342                 else
343                         snamespaceid = RangeVarGetCreationNamespace(cxt->relation);
344                 snamespace = get_namespace_name(snamespaceid);
345                 sname = ChooseRelationName(cxt->relation->relname,
346                                                                    column->colname,
347                                                                    "seq",
348                                                                    snamespaceid);
349
350                 ereport(NOTICE,
351                                 (errmsg("%s will create implicit sequence \"%s\" for serial column \"%s.%s\"",
352                                                 cxt->stmtType, sname,
353                                                 cxt->relation->relname, column->colname)));
354
355                 /*
356                  * Build a CREATE SEQUENCE command to create the sequence object, and
357                  * add it to the list of things to be done before this CREATE/ALTER
358                  * TABLE.
359                  */
360                 seqstmt = makeNode(CreateSeqStmt);
361                 seqstmt->sequence = makeRangeVar(snamespace, sname, -1);
362                 seqstmt->options = NIL;
363
364                 cxt->blist = lappend(cxt->blist, seqstmt);
365
366                 /*
367                  * Build an ALTER SEQUENCE ... OWNED BY command to mark the sequence
368                  * as owned by this column, and add it to the list of things to be
369                  * done after this CREATE/ALTER TABLE.
370                  */
371                 altseqstmt = makeNode(AlterSeqStmt);
372                 altseqstmt->sequence = makeRangeVar(snamespace, sname, -1);
373                 attnamelist = list_make3(makeString(snamespace),
374                                                                  makeString(cxt->relation->relname),
375                                                                  makeString(column->colname));
376                 altseqstmt->options = list_make1(makeDefElem("owned_by",
377                                                                                                          (Node *) attnamelist));
378
379                 cxt->alist = lappend(cxt->alist, altseqstmt);
380
381                 /*
382                  * Create appropriate constraints for SERIAL.  We do this in full,
383                  * rather than shortcutting, so that we will detect any conflicting
384                  * constraints the user wrote (like a different DEFAULT).
385                  *
386                  * Create an expression tree representing the function call
387                  * nextval('sequencename').  We cannot reduce the raw tree to cooked
388                  * form until after the sequence is created, but there's no need to do
389                  * so.
390                  */
391                 qstring = quote_qualified_identifier(snamespace, sname);
392                 snamenode = makeNode(A_Const);
393                 snamenode->val.type = T_String;
394                 snamenode->val.val.str = qstring;
395                 snamenode->location = -1;
396                 castnode = makeNode(TypeCast);
397                 castnode->typeName = SystemTypeName("regclass");
398                 castnode->arg = (Node *) snamenode;
399                 castnode->location = -1;
400                 funccallnode = makeNode(FuncCall);
401                 funccallnode->funcname = SystemFuncName("nextval");
402                 funccallnode->args = list_make1(castnode);
403                 funccallnode->agg_order = NIL;
404                 funccallnode->agg_star = false;
405                 funccallnode->agg_distinct = false;
406                 funccallnode->func_variadic = false;
407                 funccallnode->over = NULL;
408                 funccallnode->location = -1;
409
410                 constraint = makeNode(Constraint);
411                 constraint->contype = CONSTR_DEFAULT;
412                 constraint->location = -1;
413                 constraint->raw_expr = (Node *) funccallnode;
414                 constraint->cooked_expr = NULL;
415                 column->constraints = lappend(column->constraints, constraint);
416
417                 constraint = makeNode(Constraint);
418                 constraint->contype = CONSTR_NOTNULL;
419                 constraint->location = -1;
420                 column->constraints = lappend(column->constraints, constraint);
421         }
422
423         /* Process column constraints, if any... */
424         transformConstraintAttrs(pstate, column->constraints);
425
426         saw_nullable = false;
427         saw_default = false;
428
429         foreach(clist, column->constraints)
430         {
431                 constraint = lfirst(clist);
432                 Assert(IsA(constraint, Constraint));
433
434                 switch (constraint->contype)
435                 {
436                         case CONSTR_NULL:
437                                 if (saw_nullable && column->is_not_null)
438                                         ereport(ERROR,
439                                                         (errcode(ERRCODE_SYNTAX_ERROR),
440                                                          errmsg("conflicting NULL/NOT NULL declarations for column \"%s\" of table \"%s\"",
441                                                                         column->colname, cxt->relation->relname),
442                                                          parser_errposition(pstate,
443                                                                                                 constraint->location)));
444                                 column->is_not_null = FALSE;
445                                 saw_nullable = true;
446                                 break;
447
448                         case CONSTR_NOTNULL:
449                                 if (saw_nullable && !column->is_not_null)
450                                         ereport(ERROR,
451                                                         (errcode(ERRCODE_SYNTAX_ERROR),
452                                                          errmsg("conflicting NULL/NOT NULL declarations for column \"%s\" of table \"%s\"",
453                                                                         column->colname, cxt->relation->relname),
454                                                          parser_errposition(pstate,
455                                                                                                 constraint->location)));
456                                 column->is_not_null = TRUE;
457                                 saw_nullable = true;
458                                 break;
459
460                         case CONSTR_DEFAULT:
461                                 if (saw_default)
462                                         ereport(ERROR,
463                                                         (errcode(ERRCODE_SYNTAX_ERROR),
464                                                          errmsg("multiple default values specified for column \"%s\" of table \"%s\"",
465                                                                         column->colname, cxt->relation->relname),
466                                                          parser_errposition(pstate,
467                                                                                                 constraint->location)));
468                                 column->raw_default = constraint->raw_expr;
469                                 Assert(constraint->cooked_expr == NULL);
470                                 saw_default = true;
471                                 break;
472
473                         case CONSTR_CHECK:
474                                 cxt->ckconstraints = lappend(cxt->ckconstraints, constraint);
475                                 break;
476
477                         case CONSTR_PRIMARY:
478                         case CONSTR_UNIQUE:
479                                 if (constraint->keys == NIL)
480                                         constraint->keys = list_make1(makeString(column->colname));
481                                 cxt->ixconstraints = lappend(cxt->ixconstraints, constraint);
482                                 break;
483
484                         case CONSTR_EXCLUSION:
485                                 /* grammar does not allow EXCLUDE as a column constraint */
486                                 elog(ERROR, "column exclusion constraints are not supported");
487                                 break;
488
489                         case CONSTR_FOREIGN:
490
491                                 /*
492                                  * Fill in the current attribute's name and throw it into the
493                                  * list of FK constraints to be processed later.
494                                  */
495                                 constraint->fk_attrs = list_make1(makeString(column->colname));
496                                 cxt->fkconstraints = lappend(cxt->fkconstraints, constraint);
497                                 break;
498
499                         case CONSTR_ATTR_DEFERRABLE:
500                         case CONSTR_ATTR_NOT_DEFERRABLE:
501                         case CONSTR_ATTR_DEFERRED:
502                         case CONSTR_ATTR_IMMEDIATE:
503                                 /* transformConstraintAttrs took care of these */
504                                 break;
505
506                         default:
507                                 elog(ERROR, "unrecognized constraint type: %d",
508                                          constraint->contype);
509                                 break;
510                 }
511         }
512 }
513
514 /*
515  * transformTableConstraint
516  *              transform a Constraint node within CREATE TABLE or ALTER TABLE
517  */
518 static void
519 transformTableConstraint(ParseState *pstate, CreateStmtContext *cxt,
520                                                  Constraint *constraint)
521 {
522         switch (constraint->contype)
523         {
524                 case CONSTR_PRIMARY:
525                 case CONSTR_UNIQUE:
526                 case CONSTR_EXCLUSION:
527                         cxt->ixconstraints = lappend(cxt->ixconstraints, constraint);
528                         break;
529
530                 case CONSTR_CHECK:
531                         cxt->ckconstraints = lappend(cxt->ckconstraints, constraint);
532                         break;
533
534                 case CONSTR_FOREIGN:
535                         cxt->fkconstraints = lappend(cxt->fkconstraints, constraint);
536                         break;
537
538                 case CONSTR_NULL:
539                 case CONSTR_NOTNULL:
540                 case CONSTR_DEFAULT:
541                 case CONSTR_ATTR_DEFERRABLE:
542                 case CONSTR_ATTR_NOT_DEFERRABLE:
543                 case CONSTR_ATTR_DEFERRED:
544                 case CONSTR_ATTR_IMMEDIATE:
545                         elog(ERROR, "invalid context for constraint type %d",
546                                  constraint->contype);
547                         break;
548
549                 default:
550                         elog(ERROR, "unrecognized constraint type: %d",
551                                  constraint->contype);
552                         break;
553         }
554 }
555
556 /*
557  * transformInhRelation
558  *
559  * Change the LIKE <subtable> portion of a CREATE TABLE statement into
560  * column definitions which recreate the user defined column portions of
561  * <subtable>.
562  */
563 static void
564 transformInhRelation(ParseState *pstate, CreateStmtContext *cxt,
565                                          InhRelation *inhRelation)
566 {
567         AttrNumber      parent_attno;
568         Relation        relation;
569         TupleDesc       tupleDesc;
570         TupleConstr *constr;
571         AclResult       aclresult;
572         char       *comment;
573
574         relation = parserOpenTable(pstate, inhRelation->relation, AccessShareLock);
575
576         if (relation->rd_rel->relkind != RELKIND_RELATION)
577                 ereport(ERROR,
578                                 (errcode(ERRCODE_WRONG_OBJECT_TYPE),
579                                  errmsg("inherited relation \"%s\" is not a table",
580                                                 inhRelation->relation->relname)));
581
582         /*
583          * Check for SELECT privilages
584          */
585         aclresult = pg_class_aclcheck(RelationGetRelid(relation), GetUserId(),
586                                                                   ACL_SELECT);
587         if (aclresult != ACLCHECK_OK)
588                 aclcheck_error(aclresult, ACL_KIND_CLASS,
589                                            RelationGetRelationName(relation));
590
591         tupleDesc = RelationGetDescr(relation);
592         constr = tupleDesc->constr;
593
594         /*
595          * Insert the copied attributes into the cxt for the new table definition.
596          */
597         for (parent_attno = 1; parent_attno <= tupleDesc->natts;
598                  parent_attno++)
599         {
600                 Form_pg_attribute attribute = tupleDesc->attrs[parent_attno - 1];
601                 char       *attributeName = NameStr(attribute->attname);
602                 ColumnDef  *def;
603
604                 /*
605                  * Ignore dropped columns in the parent.
606                  */
607                 if (attribute->attisdropped)
608                         continue;
609
610                 /*
611                  * Create a new column, which is marked as NOT inherited.
612                  *
613                  * For constraints, ONLY the NOT NULL constraint is inherited by the
614                  * new column definition per SQL99.
615                  */
616                 def = makeNode(ColumnDef);
617                 def->colname = pstrdup(attributeName);
618                 def->typeName = makeTypeNameFromOid(attribute->atttypid,
619                                                                                         attribute->atttypmod);
620                 def->inhcount = 0;
621                 def->is_local = true;
622                 def->is_not_null = attribute->attnotnull;
623                 def->raw_default = NULL;
624                 def->cooked_default = NULL;
625                 def->constraints = NIL;
626
627                 /*
628                  * Add to column list
629                  */
630                 cxt->columns = lappend(cxt->columns, def);
631
632                 /*
633                  * Copy default, if present and the default has been requested
634                  */
635                 if (attribute->atthasdef &&
636                         (inhRelation->options & CREATE_TABLE_LIKE_DEFAULTS))
637                 {
638                         Node       *this_default = NULL;
639                         AttrDefault *attrdef;
640                         int                     i;
641
642                         /* Find default in constraint structure */
643                         Assert(constr != NULL);
644                         attrdef = constr->defval;
645                         for (i = 0; i < constr->num_defval; i++)
646                         {
647                                 if (attrdef[i].adnum == parent_attno)
648                                 {
649                                         this_default = stringToNode(attrdef[i].adbin);
650                                         break;
651                                 }
652                         }
653                         Assert(this_default != NULL);
654
655                         /*
656                          * If default expr could contain any vars, we'd need to fix 'em,
657                          * but it can't; so default is ready to apply to child.
658                          */
659
660                         def->cooked_default = this_default;
661                 }
662
663                 /* Likewise, copy storage if requested */
664                 if (inhRelation->options & CREATE_TABLE_LIKE_STORAGE)
665                         def->storage = attribute->attstorage;
666                 else
667                         def->storage = 0;
668
669                 /* Likewise, copy comment if requested */
670                 if ((inhRelation->options & CREATE_TABLE_LIKE_COMMENTS) &&
671                         (comment = GetComment(attribute->attrelid,
672                                                                   RelationRelationId,
673                                                                   attribute->attnum)) != NULL)
674                 {
675                         CommentStmt *stmt = makeNode(CommentStmt);
676
677                         stmt->objtype = OBJECT_COLUMN;
678                         stmt->objname = list_make3(makeString(cxt->relation->schemaname),
679                                                                            makeString(cxt->relation->relname),
680                                                                            makeString(def->colname));
681                         stmt->objargs = NIL;
682                         stmt->comment = comment;
683
684                         cxt->alist = lappend(cxt->alist, stmt);
685                 }
686         }
687
688         /*
689          * Copy CHECK constraints if requested, being careful to adjust attribute
690          * numbers
691          */
692         if ((inhRelation->options & CREATE_TABLE_LIKE_CONSTRAINTS) &&
693                 tupleDesc->constr)
694         {
695                 AttrNumber *attmap = varattnos_map_schema(tupleDesc, cxt->columns);
696                 int                     ccnum;
697
698                 for (ccnum = 0; ccnum < tupleDesc->constr->num_check; ccnum++)
699                 {
700                         char       *ccname = tupleDesc->constr->check[ccnum].ccname;
701                         char       *ccbin = tupleDesc->constr->check[ccnum].ccbin;
702                         Node       *ccbin_node = stringToNode(ccbin);
703                         Constraint *n = makeNode(Constraint);
704
705                         change_varattnos_of_a_node(ccbin_node, attmap);
706
707                         n->contype = CONSTR_CHECK;
708                         n->location = -1;
709                         n->conname = pstrdup(ccname);
710                         n->raw_expr = NULL;
711                         n->cooked_expr = nodeToString(ccbin_node);
712                         cxt->ckconstraints = lappend(cxt->ckconstraints, n);
713
714                         /* Copy comment on constraint */
715                         if ((inhRelation->options & CREATE_TABLE_LIKE_COMMENTS) &&
716                                 (comment = GetComment(GetConstraintByName(RelationGetRelid(relation),
717                                                                                                                   n->conname),
718                                                                           ConstraintRelationId,
719                                                                           0)) != NULL)
720                         {
721                                 CommentStmt *stmt = makeNode(CommentStmt);
722
723                                 stmt->objtype = OBJECT_CONSTRAINT;
724                                 stmt->objname = list_make3(makeString(cxt->relation->schemaname),
725                                                                                    makeString(cxt->relation->relname),
726                                                                                    makeString(n->conname));
727                                 stmt->objargs = NIL;
728                                 stmt->comment = comment;
729
730                                 cxt->alist = lappend(cxt->alist, stmt);
731                         }
732                 }
733         }
734
735         /*
736          * Likewise, copy indexes if requested
737          */
738         if ((inhRelation->options & CREATE_TABLE_LIKE_INDEXES) &&
739                 relation->rd_rel->relhasindex)
740         {
741                 AttrNumber *attmap = varattnos_map_schema(tupleDesc, cxt->columns);
742                 List       *parent_indexes;
743                 ListCell   *l;
744
745                 parent_indexes = RelationGetIndexList(relation);
746
747                 foreach(l, parent_indexes)
748                 {
749                         Oid                     parent_index_oid = lfirst_oid(l);
750                         Relation        parent_index;
751                         IndexStmt  *index_stmt;
752
753                         parent_index = index_open(parent_index_oid, AccessShareLock);
754
755                         /* Build CREATE INDEX statement to recreate the parent_index */
756                         index_stmt = generateClonedIndexStmt(cxt, parent_index, attmap);
757
758                         /* Copy comment on index */
759                         if (inhRelation->options & CREATE_TABLE_LIKE_COMMENTS)
760                         {
761                                 comment = GetComment(parent_index_oid, RelationRelationId, 0);
762
763                                 if (comment != NULL)
764                                 {
765                                         CommentStmt *stmt;
766
767                                         /*
768                                          * We have to assign the index a name now, so that we can
769                                          * reference it in CommentStmt.
770                                          */
771                                         if (index_stmt->idxname == NULL)
772                                                 index_stmt->idxname = chooseIndexName(cxt->relation,
773                                                                                                                           index_stmt);
774
775                                         stmt = makeNode(CommentStmt);
776                                         stmt->objtype = OBJECT_INDEX;
777                                         stmt->objname =
778                                                 list_make2(makeString(cxt->relation->schemaname),
779                                                                    makeString(index_stmt->idxname));
780                                         stmt->objargs = NIL;
781                                         stmt->comment = comment;
782
783                                         cxt->alist = lappend(cxt->alist, stmt);
784                                 }
785                         }
786
787                         /* Save it in the inh_indexes list for the time being */
788                         cxt->inh_indexes = lappend(cxt->inh_indexes, index_stmt);
789
790                         index_close(parent_index, AccessShareLock);
791                 }
792         }
793
794         /*
795          * Close the parent rel, but keep our AccessShareLock on it until xact
796          * commit.      That will prevent someone else from deleting or ALTERing the
797          * parent before the child is committed.
798          */
799         heap_close(relation, NoLock);
800 }
801
802 static void
803 transformOfType(ParseState *pstate, CreateStmtContext *cxt, TypeName *ofTypename)
804 {
805         HeapTuple       tuple;
806         Form_pg_type typ;
807         TupleDesc       tupdesc;
808         int                     i;
809         Oid                     ofTypeId;
810
811         AssertArg(ofTypename);
812
813         tuple = typenameType(NULL, ofTypename, NULL);
814         typ = (Form_pg_type) GETSTRUCT(tuple);
815         ofTypeId = HeapTupleGetOid(tuple);
816         ofTypename->typeOid = ofTypeId;         /* cached for later */
817
818         if (typ->typtype != TYPTYPE_COMPOSITE)
819                 ereport(ERROR,
820                                 (errcode(ERRCODE_WRONG_OBJECT_TYPE),
821                                  errmsg("type %s is not a composite type",
822                                                 format_type_be(ofTypeId))));
823
824         tupdesc = lookup_rowtype_tupdesc(ofTypeId, -1);
825         for (i = 0; i < tupdesc->natts; i++)
826         {
827                 Form_pg_attribute attr = tupdesc->attrs[i];
828                 ColumnDef  *n = makeNode(ColumnDef);
829
830                 n->colname = pstrdup(NameStr(attr->attname));
831                 n->typeName = makeTypeNameFromOid(attr->atttypid, attr->atttypmod);
832                 n->constraints = NULL;
833                 n->is_local = true;
834                 n->is_from_type = true;
835                 cxt->columns = lappend(cxt->columns, n);
836         }
837         DecrTupleDescRefCount(tupdesc);
838
839         ReleaseSysCache(tuple);
840 }
841
842 /*
843  * chooseIndexName
844  *
845  * Compute name for an index.  This must match code in indexcmds.c.
846  *
847  * XXX this is inherently broken because the indexes aren't created
848  * immediately, so we fail to resolve conflicts when the same name is
849  * derived for multiple indexes.  However, that's a reasonably uncommon
850  * situation, so we'll live with it for now.
851  */
852 static char *
853 chooseIndexName(const RangeVar *relation, IndexStmt *index_stmt)
854 {
855         Oid                     namespaceId;
856         List       *colnames;
857
858         namespaceId = RangeVarGetCreationNamespace(relation);
859         colnames = ChooseIndexColumnNames(index_stmt->indexParams);
860         return ChooseIndexName(relation->relname, namespaceId,
861                                                    colnames, index_stmt->excludeOpNames,
862                                                    index_stmt->primary, index_stmt->isconstraint);
863 }
864
865 /*
866  * Generate an IndexStmt node using information from an already existing index
867  * "source_idx".  Attribute numbers should be adjusted according to attmap.
868  */
869 static IndexStmt *
870 generateClonedIndexStmt(CreateStmtContext *cxt, Relation source_idx,
871                                                 AttrNumber *attmap)
872 {
873         Oid                     source_relid = RelationGetRelid(source_idx);
874         Form_pg_attribute *attrs = RelationGetDescr(source_idx)->attrs;
875         HeapTuple       ht_idxrel;
876         HeapTuple       ht_idx;
877         Form_pg_class idxrelrec;
878         Form_pg_index idxrec;
879         Form_pg_am      amrec;
880         oidvector  *indclass;
881         IndexStmt  *index;
882         List       *indexprs;
883         ListCell   *indexpr_item;
884         Oid                     indrelid;
885         int                     keyno;
886         Oid                     keycoltype;
887         Datum           datum;
888         bool            isnull;
889
890         /*
891          * Fetch pg_class tuple of source index.  We can't use the copy in the
892          * relcache entry because it doesn't include optional fields.
893          */
894         ht_idxrel = SearchSysCache1(RELOID, ObjectIdGetDatum(source_relid));
895         if (!HeapTupleIsValid(ht_idxrel))
896                 elog(ERROR, "cache lookup failed for relation %u", source_relid);
897         idxrelrec = (Form_pg_class) GETSTRUCT(ht_idxrel);
898
899         /* Fetch pg_index tuple for source index from relcache entry */
900         ht_idx = source_idx->rd_indextuple;
901         idxrec = (Form_pg_index) GETSTRUCT(ht_idx);
902         indrelid = idxrec->indrelid;
903
904         /* Fetch pg_am tuple for source index from relcache entry */
905         amrec = source_idx->rd_am;
906
907         /* Extract indclass from the pg_index tuple */
908         datum = SysCacheGetAttr(INDEXRELID, ht_idx,
909                                                         Anum_pg_index_indclass, &isnull);
910         Assert(!isnull);
911         indclass = (oidvector *) DatumGetPointer(datum);
912
913         /* Begin building the IndexStmt */
914         index = makeNode(IndexStmt);
915         index->relation = cxt->relation;
916         index->accessMethod = pstrdup(NameStr(amrec->amname));
917         if (OidIsValid(idxrelrec->reltablespace))
918                 index->tableSpace = get_tablespace_name(idxrelrec->reltablespace);
919         else
920                 index->tableSpace = NULL;
921         index->unique = idxrec->indisunique;
922         index->primary = idxrec->indisprimary;
923         index->concurrent = false;
924
925         /*
926          * We don't try to preserve the name of the source index; instead, just
927          * let DefineIndex() choose a reasonable name.
928          */
929         index->idxname = NULL;
930
931         /*
932          * If the index is marked PRIMARY or has an exclusion condition, it's
933          * certainly from a constraint; else, if it's not marked UNIQUE, it
934          * certainly isn't.  If it is or might be from a constraint, we have to
935          * fetch the pg_constraint record.
936          */
937         if (index->primary || index->unique || idxrelrec->relhasexclusion)
938         {
939                 Oid                     constraintId = get_index_constraint(source_relid);
940
941                 if (OidIsValid(constraintId))
942                 {
943                         HeapTuple       ht_constr;
944                         Form_pg_constraint conrec;
945
946                         ht_constr = SearchSysCache1(CONSTROID,
947                                                                                 ObjectIdGetDatum(constraintId));
948                         if (!HeapTupleIsValid(ht_constr))
949                                 elog(ERROR, "cache lookup failed for constraint %u",
950                                          constraintId);
951                         conrec = (Form_pg_constraint) GETSTRUCT(ht_constr);
952
953                         index->isconstraint = true;
954                         index->deferrable = conrec->condeferrable;
955                         index->initdeferred = conrec->condeferred;
956
957                         /* If it's an exclusion constraint, we need the operator names */
958                         if (idxrelrec->relhasexclusion)
959                         {
960                                 Datum      *elems;
961                                 int                     nElems;
962                                 int                     i;
963
964                                 Assert(conrec->contype == CONSTRAINT_EXCLUSION);
965                                 /* Extract operator OIDs from the pg_constraint tuple */
966                                 datum = SysCacheGetAttr(CONSTROID, ht_constr,
967                                                                                 Anum_pg_constraint_conexclop,
968                                                                                 &isnull);
969                                 if (isnull)
970                                         elog(ERROR, "null conexclop for constraint %u",
971                                                  constraintId);
972
973                                 deconstruct_array(DatumGetArrayTypeP(datum),
974                                                                   OIDOID, sizeof(Oid), true, 'i',
975                                                                   &elems, NULL, &nElems);
976
977                                 for (i = 0; i < nElems; i++)
978                                 {
979                                         Oid                     operid = DatumGetObjectId(elems[i]);
980                                         HeapTuple       opertup;
981                                         Form_pg_operator operform;
982                                         char       *oprname;
983                                         char       *nspname;
984                                         List       *namelist;
985
986                                         opertup = SearchSysCache1(OPEROID,
987                                                                                           ObjectIdGetDatum(operid));
988                                         if (!HeapTupleIsValid(opertup))
989                                                 elog(ERROR, "cache lookup failed for operator %u",
990                                                          operid);
991                                         operform = (Form_pg_operator) GETSTRUCT(opertup);
992                                         oprname = pstrdup(NameStr(operform->oprname));
993                                         /* For simplicity we always schema-qualify the op name */
994                                         nspname = get_namespace_name(operform->oprnamespace);
995                                         namelist = list_make2(makeString(nspname),
996                                                                                   makeString(oprname));
997                                         index->excludeOpNames = lappend(index->excludeOpNames,
998                                                                                                         namelist);
999                                         ReleaseSysCache(opertup);
1000                                 }
1001                         }
1002
1003                         ReleaseSysCache(ht_constr);
1004                 }
1005                 else
1006                         index->isconstraint = false;
1007         }
1008         else
1009                 index->isconstraint = false;
1010
1011         /* Get the index expressions, if any */
1012         datum = SysCacheGetAttr(INDEXRELID, ht_idx,
1013                                                         Anum_pg_index_indexprs, &isnull);
1014         if (!isnull)
1015         {
1016                 char       *exprsString;
1017
1018                 exprsString = TextDatumGetCString(datum);
1019                 indexprs = (List *) stringToNode(exprsString);
1020         }
1021         else
1022                 indexprs = NIL;
1023
1024         /* Build the list of IndexElem */
1025         index->indexParams = NIL;
1026
1027         indexpr_item = list_head(indexprs);
1028         for (keyno = 0; keyno < idxrec->indnatts; keyno++)
1029         {
1030                 IndexElem  *iparam;
1031                 AttrNumber      attnum = idxrec->indkey.values[keyno];
1032                 int16           opt = source_idx->rd_indoption[keyno];
1033
1034                 iparam = makeNode(IndexElem);
1035
1036                 if (AttributeNumberIsValid(attnum))
1037                 {
1038                         /* Simple index column */
1039                         char       *attname;
1040
1041                         attname = get_relid_attribute_name(indrelid, attnum);
1042                         keycoltype = get_atttype(indrelid, attnum);
1043
1044                         iparam->name = attname;
1045                         iparam->expr = NULL;
1046                 }
1047                 else
1048                 {
1049                         /* Expressional index */
1050                         Node       *indexkey;
1051
1052                         if (indexpr_item == NULL)
1053                                 elog(ERROR, "too few entries in indexprs list");
1054                         indexkey = (Node *) lfirst(indexpr_item);
1055                         indexpr_item = lnext(indexpr_item);
1056
1057                         /* OK to modify indexkey since we are working on a private copy */
1058                         change_varattnos_of_a_node(indexkey, attmap);
1059
1060                         iparam->name = NULL;
1061                         iparam->expr = indexkey;
1062
1063                         keycoltype = exprType(indexkey);
1064                 }
1065
1066                 /* Copy the original index column name */
1067                 iparam->indexcolname = pstrdup(NameStr(attrs[keyno]->attname));
1068
1069                 /* Add the operator class name, if non-default */
1070                 iparam->opclass = get_opclass(indclass->values[keyno], keycoltype);
1071
1072                 iparam->ordering = SORTBY_DEFAULT;
1073                 iparam->nulls_ordering = SORTBY_NULLS_DEFAULT;
1074
1075                 /* Adjust options if necessary */
1076                 if (amrec->amcanorder)
1077                 {
1078                         /*
1079                          * If it supports sort ordering, copy DESC and NULLS opts. Don't
1080                          * set non-default settings unnecessarily, though, so as to
1081                          * improve the chance of recognizing equivalence to constraint
1082                          * indexes.
1083                          */
1084                         if (opt & INDOPTION_DESC)
1085                         {
1086                                 iparam->ordering = SORTBY_DESC;
1087                                 if ((opt & INDOPTION_NULLS_FIRST) == 0)
1088                                         iparam->nulls_ordering = SORTBY_NULLS_LAST;
1089                         }
1090                         else
1091                         {
1092                                 if (opt & INDOPTION_NULLS_FIRST)
1093                                         iparam->nulls_ordering = SORTBY_NULLS_FIRST;
1094                         }
1095                 }
1096
1097                 index->indexParams = lappend(index->indexParams, iparam);
1098         }
1099
1100         /* Copy reloptions if any */
1101         datum = SysCacheGetAttr(RELOID, ht_idxrel,
1102                                                         Anum_pg_class_reloptions, &isnull);
1103         if (!isnull)
1104                 index->options = untransformRelOptions(datum);
1105
1106         /* If it's a partial index, decompile and append the predicate */
1107         datum = SysCacheGetAttr(INDEXRELID, ht_idx,
1108                                                         Anum_pg_index_indpred, &isnull);
1109         if (!isnull)
1110         {
1111                 char       *pred_str;
1112
1113                 /* Convert text string to node tree */
1114                 pred_str = TextDatumGetCString(datum);
1115                 index->whereClause = (Node *) stringToNode(pred_str);
1116                 /* Adjust attribute numbers */
1117                 change_varattnos_of_a_node(index->whereClause, attmap);
1118         }
1119
1120         /* Clean up */
1121         ReleaseSysCache(ht_idxrel);
1122
1123         return index;
1124 }
1125
1126 /*
1127  * get_opclass                  - fetch name of an index operator class
1128  *
1129  * If the opclass is the default for the given actual_datatype, then
1130  * the return value is NIL.
1131  */
1132 static List *
1133 get_opclass(Oid opclass, Oid actual_datatype)
1134 {
1135         HeapTuple       ht_opc;
1136         Form_pg_opclass opc_rec;
1137         List       *result = NIL;
1138
1139         ht_opc = SearchSysCache1(CLAOID, ObjectIdGetDatum(opclass));
1140         if (!HeapTupleIsValid(ht_opc))
1141                 elog(ERROR, "cache lookup failed for opclass %u", opclass);
1142         opc_rec = (Form_pg_opclass) GETSTRUCT(ht_opc);
1143
1144         if (GetDefaultOpClass(actual_datatype, opc_rec->opcmethod) != opclass)
1145         {
1146                 /* For simplicity, we always schema-qualify the name */
1147                 char       *nsp_name = get_namespace_name(opc_rec->opcnamespace);
1148                 char       *opc_name = pstrdup(NameStr(opc_rec->opcname));
1149
1150                 result = list_make2(makeString(nsp_name), makeString(opc_name));
1151         }
1152
1153         ReleaseSysCache(ht_opc);
1154         return result;
1155 }
1156
1157
1158 /*
1159  * transformIndexConstraints
1160  *              Handle UNIQUE, PRIMARY KEY, EXCLUDE constraints, which create indexes.
1161  *              We also merge in any index definitions arising from
1162  *              LIKE ... INCLUDING INDEXES.
1163  */
1164 static void
1165 transformIndexConstraints(ParseState *pstate, CreateStmtContext *cxt)
1166 {
1167         IndexStmt  *index;
1168         List       *indexlist = NIL;
1169         ListCell   *lc;
1170
1171         /*
1172          * Run through the constraints that need to generate an index. For PRIMARY
1173          * KEY, mark each column as NOT NULL and create an index. For UNIQUE or
1174          * EXCLUDE, create an index as for PRIMARY KEY, but do not insist on NOT
1175          * NULL.
1176          */
1177         foreach(lc, cxt->ixconstraints)
1178         {
1179                 Constraint *constraint = (Constraint *) lfirst(lc);
1180
1181                 Assert(IsA(constraint, Constraint));
1182                 Assert(constraint->contype == CONSTR_PRIMARY ||
1183                            constraint->contype == CONSTR_UNIQUE ||
1184                            constraint->contype == CONSTR_EXCLUSION);
1185
1186                 index = transformIndexConstraint(constraint, cxt);
1187
1188                 indexlist = lappend(indexlist, index);
1189         }
1190
1191         /* Add in any indexes defined by LIKE ... INCLUDING INDEXES */
1192         foreach(lc, cxt->inh_indexes)
1193         {
1194                 index = (IndexStmt *) lfirst(lc);
1195
1196                 if (index->primary)
1197                 {
1198                         if (cxt->pkey != NULL)
1199                                 ereport(ERROR,
1200                                                 (errcode(ERRCODE_INVALID_TABLE_DEFINITION),
1201                                                  errmsg("multiple primary keys for table \"%s\" are not allowed",
1202                                                                 cxt->relation->relname)));
1203                         cxt->pkey = index;
1204                 }
1205
1206                 indexlist = lappend(indexlist, index);
1207         }
1208
1209         /*
1210          * Scan the index list and remove any redundant index specifications. This
1211          * can happen if, for instance, the user writes UNIQUE PRIMARY KEY. A
1212          * strict reading of SQL92 would suggest raising an error instead, but
1213          * that strikes me as too anal-retentive. - tgl 2001-02-14
1214          *
1215          * XXX in ALTER TABLE case, it'd be nice to look for duplicate
1216          * pre-existing indexes, too.
1217          */
1218         Assert(cxt->alist == NIL);
1219         if (cxt->pkey != NULL)
1220         {
1221                 /* Make sure we keep the PKEY index in preference to others... */
1222                 cxt->alist = list_make1(cxt->pkey);
1223         }
1224
1225         foreach(lc, indexlist)
1226         {
1227                 bool            keep = true;
1228                 ListCell   *k;
1229
1230                 index = lfirst(lc);
1231
1232                 /* if it's pkey, it's already in cxt->alist */
1233                 if (index == cxt->pkey)
1234                         continue;
1235
1236                 foreach(k, cxt->alist)
1237                 {
1238                         IndexStmt  *priorindex = lfirst(k);
1239
1240                         if (equal(index->indexParams, priorindex->indexParams) &&
1241                                 equal(index->whereClause, priorindex->whereClause) &&
1242                                 equal(index->excludeOpNames, priorindex->excludeOpNames) &&
1243                                 strcmp(index->accessMethod, priorindex->accessMethod) == 0 &&
1244                                 index->deferrable == priorindex->deferrable &&
1245                                 index->initdeferred == priorindex->initdeferred)
1246                         {
1247                                 priorindex->unique |= index->unique;
1248
1249                                 /*
1250                                  * If the prior index is as yet unnamed, and this one is
1251                                  * named, then transfer the name to the prior index. This
1252                                  * ensures that if we have named and unnamed constraints,
1253                                  * we'll use (at least one of) the names for the index.
1254                                  */
1255                                 if (priorindex->idxname == NULL)
1256                                         priorindex->idxname = index->idxname;
1257                                 keep = false;
1258                                 break;
1259                         }
1260                 }
1261
1262                 if (keep)
1263                         cxt->alist = lappend(cxt->alist, index);
1264         }
1265 }
1266
1267 /*
1268  * transformIndexConstraint
1269  *              Transform one UNIQUE, PRIMARY KEY, or EXCLUDE constraint for
1270  *              transformIndexConstraints.
1271  */
1272 static IndexStmt *
1273 transformIndexConstraint(Constraint *constraint, CreateStmtContext *cxt)
1274 {
1275         IndexStmt  *index;
1276         ListCell   *lc;
1277
1278         index = makeNode(IndexStmt);
1279
1280         index->unique = (constraint->contype != CONSTR_EXCLUSION);
1281         index->primary = (constraint->contype == CONSTR_PRIMARY);
1282         if (index->primary)
1283         {
1284                 if (cxt->pkey != NULL)
1285                         ereport(ERROR,
1286                                         (errcode(ERRCODE_INVALID_TABLE_DEFINITION),
1287                          errmsg("multiple primary keys for table \"%s\" are not allowed",
1288                                         cxt->relation->relname)));
1289                 cxt->pkey = index;
1290
1291                 /*
1292                  * In ALTER TABLE case, a primary index might already exist, but
1293                  * DefineIndex will check for it.
1294                  */
1295         }
1296         index->isconstraint = true;
1297         index->deferrable = constraint->deferrable;
1298         index->initdeferred = constraint->initdeferred;
1299
1300         if (constraint->conname != NULL)
1301                 index->idxname = pstrdup(constraint->conname);
1302         else
1303                 index->idxname = NULL;  /* DefineIndex will choose name */
1304
1305         index->relation = cxt->relation;
1306         index->accessMethod = constraint->access_method ? constraint->access_method : DEFAULT_INDEX_TYPE;
1307         index->options = constraint->options;
1308         index->tableSpace = constraint->indexspace;
1309         index->whereClause = constraint->where_clause;
1310         index->indexParams = NIL;
1311         index->excludeOpNames = NIL;
1312         index->concurrent = false;
1313
1314         /*
1315          * If it's an EXCLUDE constraint, the grammar returns a list of pairs of
1316          * IndexElems and operator names.  We have to break that apart into
1317          * separate lists.
1318          */
1319         if (constraint->contype == CONSTR_EXCLUSION)
1320         {
1321                 foreach(lc, constraint->exclusions)
1322                 {
1323                         List       *pair = (List *) lfirst(lc);
1324                         IndexElem  *elem;
1325                         List       *opname;
1326
1327                         Assert(list_length(pair) == 2);
1328                         elem = (IndexElem *) linitial(pair);
1329                         Assert(IsA(elem, IndexElem));
1330                         opname = (List *) lsecond(pair);
1331                         Assert(IsA(opname, List));
1332
1333                         index->indexParams = lappend(index->indexParams, elem);
1334                         index->excludeOpNames = lappend(index->excludeOpNames, opname);
1335                 }
1336
1337                 return index;
1338         }
1339
1340         /*
1341          * For UNIQUE and PRIMARY KEY, we just have a list of column names.
1342          *
1343          * Make sure referenced keys exist.  If we are making a PRIMARY KEY index,
1344          * also make sure they are NOT NULL, if possible. (Although we could leave
1345          * it to DefineIndex to mark the columns NOT NULL, it's more efficient to
1346          * get it right the first time.)
1347          */
1348         foreach(lc, constraint->keys)
1349         {
1350                 char       *key = strVal(lfirst(lc));
1351                 bool            found = false;
1352                 ColumnDef  *column = NULL;
1353                 ListCell   *columns;
1354                 IndexElem  *iparam;
1355
1356                 foreach(columns, cxt->columns)
1357                 {
1358                         column = (ColumnDef *) lfirst(columns);
1359                         Assert(IsA(column, ColumnDef));
1360                         if (strcmp(column->colname, key) == 0)
1361                         {
1362                                 found = true;
1363                                 break;
1364                         }
1365                 }
1366                 if (found)
1367                 {
1368                         /* found column in the new table; force it to be NOT NULL */
1369                         if (constraint->contype == CONSTR_PRIMARY)
1370                                 column->is_not_null = TRUE;
1371                 }
1372                 else if (SystemAttributeByName(key, cxt->hasoids) != NULL)
1373                 {
1374                         /*
1375                          * column will be a system column in the new table, so accept it.
1376                          * System columns can't ever be null, so no need to worry about
1377                          * PRIMARY/NOT NULL constraint.
1378                          */
1379                         found = true;
1380                 }
1381                 else if (cxt->inhRelations)
1382                 {
1383                         /* try inherited tables */
1384                         ListCell   *inher;
1385
1386                         foreach(inher, cxt->inhRelations)
1387                         {
1388                                 RangeVar   *inh = (RangeVar *) lfirst(inher);
1389                                 Relation        rel;
1390                                 int                     count;
1391
1392                                 Assert(IsA(inh, RangeVar));
1393                                 rel = heap_openrv(inh, AccessShareLock);
1394                                 if (rel->rd_rel->relkind != RELKIND_RELATION)
1395                                         ereport(ERROR,
1396                                                         (errcode(ERRCODE_WRONG_OBJECT_TYPE),
1397                                                    errmsg("inherited relation \"%s\" is not a table",
1398                                                                   inh->relname)));
1399                                 for (count = 0; count < rel->rd_att->natts; count++)
1400                                 {
1401                                         Form_pg_attribute inhattr = rel->rd_att->attrs[count];
1402                                         char       *inhname = NameStr(inhattr->attname);
1403
1404                                         if (inhattr->attisdropped)
1405                                                 continue;
1406                                         if (strcmp(key, inhname) == 0)
1407                                         {
1408                                                 found = true;
1409
1410                                                 /*
1411                                                  * We currently have no easy way to force an inherited
1412                                                  * column to be NOT NULL at creation, if its parent
1413                                                  * wasn't so already. We leave it to DefineIndex to
1414                                                  * fix things up in this case.
1415                                                  */
1416                                                 break;
1417                                         }
1418                                 }
1419                                 heap_close(rel, NoLock);
1420                                 if (found)
1421                                         break;
1422                         }
1423                 }
1424
1425                 /*
1426                  * In the ALTER TABLE case, don't complain about index keys not
1427                  * created in the command; they may well exist already. DefineIndex
1428                  * will complain about them if not, and will also take care of marking
1429                  * them NOT NULL.
1430                  */
1431                 if (!found && !cxt->isalter)
1432                         ereport(ERROR,
1433                                         (errcode(ERRCODE_UNDEFINED_COLUMN),
1434                                          errmsg("column \"%s\" named in key does not exist",
1435                                                         key)));
1436
1437                 /* Check for PRIMARY KEY(foo, foo) */
1438                 foreach(columns, index->indexParams)
1439                 {
1440                         iparam = (IndexElem *) lfirst(columns);
1441                         if (iparam->name && strcmp(key, iparam->name) == 0)
1442                         {
1443                                 if (index->primary)
1444                                         ereport(ERROR,
1445                                                         (errcode(ERRCODE_DUPLICATE_COLUMN),
1446                                                          errmsg("column \"%s\" appears twice in primary key constraint",
1447                                                                         key)));
1448                                 else
1449                                         ereport(ERROR,
1450                                                         (errcode(ERRCODE_DUPLICATE_COLUMN),
1451                                         errmsg("column \"%s\" appears twice in unique constraint",
1452                                                    key)));
1453                         }
1454                 }
1455
1456                 /* OK, add it to the index definition */
1457                 iparam = makeNode(IndexElem);
1458                 iparam->name = pstrdup(key);
1459                 iparam->expr = NULL;
1460                 iparam->indexcolname = NULL;
1461                 iparam->opclass = NIL;
1462                 iparam->ordering = SORTBY_DEFAULT;
1463                 iparam->nulls_ordering = SORTBY_NULLS_DEFAULT;
1464                 index->indexParams = lappend(index->indexParams, iparam);
1465         }
1466
1467         return index;
1468 }
1469
1470 /*
1471  * transformFKConstraints
1472  *              handle FOREIGN KEY constraints
1473  */
1474 static void
1475 transformFKConstraints(ParseState *pstate, CreateStmtContext *cxt,
1476                                            bool skipValidation, bool isAddConstraint)
1477 {
1478         ListCell   *fkclist;
1479
1480         if (cxt->fkconstraints == NIL)
1481                 return;
1482
1483         /*
1484          * If CREATE TABLE or adding a column with NULL default, we can safely
1485          * skip validation of the constraint.
1486          */
1487         if (skipValidation)
1488         {
1489                 foreach(fkclist, cxt->fkconstraints)
1490                 {
1491                         Constraint *constraint = (Constraint *) lfirst(fkclist);
1492
1493                         constraint->skip_validation = true;
1494                 }
1495         }
1496
1497         /*
1498          * For CREATE TABLE or ALTER TABLE ADD COLUMN, gin up an ALTER TABLE ADD
1499          * CONSTRAINT command to execute after the basic command is complete. (If
1500          * called from ADD CONSTRAINT, that routine will add the FK constraints to
1501          * its own subcommand list.)
1502          *
1503          * Note: the ADD CONSTRAINT command must also execute after any index
1504          * creation commands.  Thus, this should run after
1505          * transformIndexConstraints, so that the CREATE INDEX commands are
1506          * already in cxt->alist.
1507          */
1508         if (!isAddConstraint)
1509         {
1510                 AlterTableStmt *alterstmt = makeNode(AlterTableStmt);
1511
1512                 alterstmt->relation = cxt->relation;
1513                 alterstmt->cmds = NIL;
1514                 alterstmt->relkind = OBJECT_TABLE;
1515
1516                 foreach(fkclist, cxt->fkconstraints)
1517                 {
1518                         Constraint *constraint = (Constraint *) lfirst(fkclist);
1519                         AlterTableCmd *altercmd = makeNode(AlterTableCmd);
1520
1521                         altercmd->subtype = AT_ProcessedConstraint;
1522                         altercmd->name = NULL;
1523                         altercmd->def = (Node *) constraint;
1524                         alterstmt->cmds = lappend(alterstmt->cmds, altercmd);
1525                 }
1526
1527                 cxt->alist = lappend(cxt->alist, alterstmt);
1528         }
1529 }
1530
1531 /*
1532  * transformIndexStmt - parse analysis for CREATE INDEX and ALTER TABLE
1533  *
1534  * Note: this is a no-op for an index not using either index expressions or
1535  * a predicate expression.      There are several code paths that create indexes
1536  * without bothering to call this, because they know they don't have any
1537  * such expressions to deal with.
1538  */
1539 IndexStmt *
1540 transformIndexStmt(IndexStmt *stmt, const char *queryString)
1541 {
1542         Relation        rel;
1543         ParseState *pstate;
1544         RangeTblEntry *rte;
1545         ListCell   *l;
1546
1547         /*
1548          * We must not scribble on the passed-in IndexStmt, so copy it.  (This is
1549          * overkill, but easy.)
1550          */
1551         stmt = (IndexStmt *) copyObject(stmt);
1552
1553         /*
1554          * Open the parent table with appropriate locking.      We must do this
1555          * because addRangeTableEntry() would acquire only AccessShareLock,
1556          * leaving DefineIndex() needing to do a lock upgrade with consequent risk
1557          * of deadlock.  Make sure this stays in sync with the type of lock
1558          * DefineIndex() wants. If we are being called by ALTER TABLE, we will
1559          * already hold a higher lock.
1560          */
1561         rel = heap_openrv(stmt->relation,
1562                                   (stmt->concurrent ? ShareUpdateExclusiveLock : ShareLock));
1563
1564         /* Set up pstate */
1565         pstate = make_parsestate(NULL);
1566         pstate->p_sourcetext = queryString;
1567
1568         /*
1569          * Put the parent table into the rtable so that the expressions can refer
1570          * to its fields without qualification.
1571          */
1572         rte = addRangeTableEntry(pstate, stmt->relation, NULL, false, true);
1573
1574         /* no to join list, yes to namespaces */
1575         addRTEtoQuery(pstate, rte, false, true, true);
1576
1577         /* take care of the where clause */
1578         if (stmt->whereClause)
1579                 stmt->whereClause = transformWhereClause(pstate,
1580                                                                                                  stmt->whereClause,
1581                                                                                                  "WHERE");
1582
1583         /* take care of any index expressions */
1584         foreach(l, stmt->indexParams)
1585         {
1586                 IndexElem  *ielem = (IndexElem *) lfirst(l);
1587
1588                 if (ielem->expr)
1589                 {
1590                         /* Extract preliminary index col name before transforming expr */
1591                         if (ielem->indexcolname == NULL)
1592                                 ielem->indexcolname = FigureIndexColname(ielem->expr);
1593
1594                         /* Now do parse transformation of the expression */
1595                         ielem->expr = transformExpr(pstate, ielem->expr);
1596
1597                         /*
1598                          * We check only that the result type is legitimate; this is for
1599                          * consistency with what transformWhereClause() checks for the
1600                          * predicate.  DefineIndex() will make more checks.
1601                          */
1602                         if (expression_returns_set(ielem->expr))
1603                                 ereport(ERROR,
1604                                                 (errcode(ERRCODE_DATATYPE_MISMATCH),
1605                                                  errmsg("index expression cannot return a set")));
1606                 }
1607         }
1608
1609         /*
1610          * Check that only the base rel is mentioned.
1611          */
1612         if (list_length(pstate->p_rtable) != 1)
1613                 ereport(ERROR,
1614                                 (errcode(ERRCODE_INVALID_COLUMN_REFERENCE),
1615                                  errmsg("index expressions and predicates can refer only to the table being indexed")));
1616
1617         free_parsestate(pstate);
1618
1619         /* Close relation, but keep the lock */
1620         heap_close(rel, NoLock);
1621
1622         return stmt;
1623 }
1624
1625
1626 /*
1627  * transformRuleStmt -
1628  *        transform a CREATE RULE Statement. The action is a list of parse
1629  *        trees which is transformed into a list of query trees, and we also
1630  *        transform the WHERE clause if any.
1631  *
1632  * actions and whereClause are output parameters that receive the
1633  * transformed results.
1634  *
1635  * Note that we must not scribble on the passed-in RuleStmt, so we do
1636  * copyObject() on the actions and WHERE clause.
1637  */
1638 void
1639 transformRuleStmt(RuleStmt *stmt, const char *queryString,
1640                                   List **actions, Node **whereClause)
1641 {
1642         Relation        rel;
1643         ParseState *pstate;
1644         RangeTblEntry *oldrte;
1645         RangeTblEntry *newrte;
1646
1647         /*
1648          * To avoid deadlock, make sure the first thing we do is grab
1649          * AccessExclusiveLock on the target relation.  This will be needed by
1650          * DefineQueryRewrite(), and we don't want to grab a lesser lock
1651          * beforehand.
1652          */
1653         rel = heap_openrv(stmt->relation, AccessExclusiveLock);
1654
1655         /* Set up pstate */
1656         pstate = make_parsestate(NULL);
1657         pstate->p_sourcetext = queryString;
1658
1659         /*
1660          * NOTE: 'OLD' must always have a varno equal to 1 and 'NEW' equal to 2.
1661          * Set up their RTEs in the main pstate for use in parsing the rule
1662          * qualification.
1663          */
1664         oldrte = addRangeTableEntryForRelation(pstate, rel,
1665                                                                                    makeAlias("old", NIL),
1666                                                                                    false, false);
1667         newrte = addRangeTableEntryForRelation(pstate, rel,
1668                                                                                    makeAlias("new", NIL),
1669                                                                                    false, false);
1670         /* Must override addRangeTableEntry's default access-check flags */
1671         oldrte->requiredPerms = 0;
1672         newrte->requiredPerms = 0;
1673
1674         /*
1675          * They must be in the namespace too for lookup purposes, but only add the
1676          * one(s) that are relevant for the current kind of rule.  In an UPDATE
1677          * rule, quals must refer to OLD.field or NEW.field to be unambiguous, but
1678          * there's no need to be so picky for INSERT & DELETE.  We do not add them
1679          * to the joinlist.
1680          */
1681         switch (stmt->event)
1682         {
1683                 case CMD_SELECT:
1684                         addRTEtoQuery(pstate, oldrte, false, true, true);
1685                         break;
1686                 case CMD_UPDATE:
1687                         addRTEtoQuery(pstate, oldrte, false, true, true);
1688                         addRTEtoQuery(pstate, newrte, false, true, true);
1689                         break;
1690                 case CMD_INSERT:
1691                         addRTEtoQuery(pstate, newrte, false, true, true);
1692                         break;
1693                 case CMD_DELETE:
1694                         addRTEtoQuery(pstate, oldrte, false, true, true);
1695                         break;
1696                 default:
1697                         elog(ERROR, "unrecognized event type: %d",
1698                                  (int) stmt->event);
1699                         break;
1700         }
1701
1702         /* take care of the where clause */
1703         *whereClause = transformWhereClause(pstate,
1704                                                                           (Node *) copyObject(stmt->whereClause),
1705                                                                                 "WHERE");
1706
1707         if (list_length(pstate->p_rtable) != 2)         /* naughty, naughty... */
1708                 ereport(ERROR,
1709                                 (errcode(ERRCODE_INVALID_OBJECT_DEFINITION),
1710                                  errmsg("rule WHERE condition cannot contain references to other relations")));
1711
1712         /* aggregates not allowed (but subselects are okay) */
1713         if (pstate->p_hasAggs)
1714                 ereport(ERROR,
1715                                 (errcode(ERRCODE_GROUPING_ERROR),
1716                    errmsg("cannot use aggregate function in rule WHERE condition")));
1717         if (pstate->p_hasWindowFuncs)
1718                 ereport(ERROR,
1719                                 (errcode(ERRCODE_WINDOWING_ERROR),
1720                           errmsg("cannot use window function in rule WHERE condition")));
1721
1722         /*
1723          * 'instead nothing' rules with a qualification need a query rangetable so
1724          * the rewrite handler can add the negated rule qualification to the
1725          * original query. We create a query with the new command type CMD_NOTHING
1726          * here that is treated specially by the rewrite system.
1727          */
1728         if (stmt->actions == NIL)
1729         {
1730                 Query      *nothing_qry = makeNode(Query);
1731
1732                 nothing_qry->commandType = CMD_NOTHING;
1733                 nothing_qry->rtable = pstate->p_rtable;
1734                 nothing_qry->jointree = makeFromExpr(NIL, NULL);                /* no join wanted */
1735
1736                 *actions = list_make1(nothing_qry);
1737         }
1738         else
1739         {
1740                 ListCell   *l;
1741                 List       *newactions = NIL;
1742
1743                 /*
1744                  * transform each statement, like parse_sub_analyze()
1745                  */
1746                 foreach(l, stmt->actions)
1747                 {
1748                         Node       *action = (Node *) lfirst(l);
1749                         ParseState *sub_pstate = make_parsestate(NULL);
1750                         Query      *sub_qry,
1751                                            *top_subqry;
1752                         bool            has_old,
1753                                                 has_new;
1754
1755                         /*
1756                          * Since outer ParseState isn't parent of inner, have to pass down
1757                          * the query text by hand.
1758                          */
1759                         sub_pstate->p_sourcetext = queryString;
1760
1761                         /*
1762                          * Set up OLD/NEW in the rtable for this statement.  The entries
1763                          * are added only to relnamespace, not varnamespace, because we
1764                          * don't want them to be referred to by unqualified field names
1765                          * nor "*" in the rule actions.  We decide later whether to put
1766                          * them in the joinlist.
1767                          */
1768                         oldrte = addRangeTableEntryForRelation(sub_pstate, rel,
1769                                                                                                    makeAlias("old", NIL),
1770                                                                                                    false, false);
1771                         newrte = addRangeTableEntryForRelation(sub_pstate, rel,
1772                                                                                                    makeAlias("new", NIL),
1773                                                                                                    false, false);
1774                         oldrte->requiredPerms = 0;
1775                         newrte->requiredPerms = 0;
1776                         addRTEtoQuery(sub_pstate, oldrte, false, true, false);
1777                         addRTEtoQuery(sub_pstate, newrte, false, true, false);
1778
1779                         /* Transform the rule action statement */
1780                         top_subqry = transformStmt(sub_pstate,
1781                                                                            (Node *) copyObject(action));
1782
1783                         /*
1784                          * We cannot support utility-statement actions (eg NOTIFY) with
1785                          * nonempty rule WHERE conditions, because there's no way to make
1786                          * the utility action execute conditionally.
1787                          */
1788                         if (top_subqry->commandType == CMD_UTILITY &&
1789                                 *whereClause != NULL)
1790                                 ereport(ERROR,
1791                                                 (errcode(ERRCODE_INVALID_OBJECT_DEFINITION),
1792                                                  errmsg("rules with WHERE conditions can only have SELECT, INSERT, UPDATE, or DELETE actions")));
1793
1794                         /*
1795                          * If the action is INSERT...SELECT, OLD/NEW have been pushed down
1796                          * into the SELECT, and that's what we need to look at. (Ugly
1797                          * kluge ... try to fix this when we redesign querytrees.)
1798                          */
1799                         sub_qry = getInsertSelectQuery(top_subqry, NULL);
1800
1801                         /*
1802                          * If the sub_qry is a setop, we cannot attach any qualifications
1803                          * to it, because the planner won't notice them.  This could
1804                          * perhaps be relaxed someday, but for now, we may as well reject
1805                          * such a rule immediately.
1806                          */
1807                         if (sub_qry->setOperations != NULL && *whereClause != NULL)
1808                                 ereport(ERROR,
1809                                                 (errcode(ERRCODE_FEATURE_NOT_SUPPORTED),
1810                                                  errmsg("conditional UNION/INTERSECT/EXCEPT statements are not implemented")));
1811
1812                         /*
1813                          * Validate action's use of OLD/NEW, qual too
1814                          */
1815                         has_old =
1816                                 rangeTableEntry_used((Node *) sub_qry, PRS2_OLD_VARNO, 0) ||
1817                                 rangeTableEntry_used(*whereClause, PRS2_OLD_VARNO, 0);
1818                         has_new =
1819                                 rangeTableEntry_used((Node *) sub_qry, PRS2_NEW_VARNO, 0) ||
1820                                 rangeTableEntry_used(*whereClause, PRS2_NEW_VARNO, 0);
1821
1822                         switch (stmt->event)
1823                         {
1824                                 case CMD_SELECT:
1825                                         if (has_old)
1826                                                 ereport(ERROR,
1827                                                                 (errcode(ERRCODE_INVALID_OBJECT_DEFINITION),
1828                                                                  errmsg("ON SELECT rule cannot use OLD")));
1829                                         if (has_new)
1830                                                 ereport(ERROR,
1831                                                                 (errcode(ERRCODE_INVALID_OBJECT_DEFINITION),
1832                                                                  errmsg("ON SELECT rule cannot use NEW")));
1833                                         break;
1834                                 case CMD_UPDATE:
1835                                         /* both are OK */
1836                                         break;
1837                                 case CMD_INSERT:
1838                                         if (has_old)
1839                                                 ereport(ERROR,
1840                                                                 (errcode(ERRCODE_INVALID_OBJECT_DEFINITION),
1841                                                                  errmsg("ON INSERT rule cannot use OLD")));
1842                                         break;
1843                                 case CMD_DELETE:
1844                                         if (has_new)
1845                                                 ereport(ERROR,
1846                                                                 (errcode(ERRCODE_INVALID_OBJECT_DEFINITION),
1847                                                                  errmsg("ON DELETE rule cannot use NEW")));
1848                                         break;
1849                                 default:
1850                                         elog(ERROR, "unrecognized event type: %d",
1851                                                  (int) stmt->event);
1852                                         break;
1853                         }
1854
1855                         /*
1856                          * For efficiency's sake, add OLD to the rule action's jointree
1857                          * only if it was actually referenced in the statement or qual.
1858                          *
1859                          * For INSERT, NEW is not really a relation (only a reference to
1860                          * the to-be-inserted tuple) and should never be added to the
1861                          * jointree.
1862                          *
1863                          * For UPDATE, we treat NEW as being another kind of reference to
1864                          * OLD, because it represents references to *transformed* tuples
1865                          * of the existing relation.  It would be wrong to enter NEW
1866                          * separately in the jointree, since that would cause a double
1867                          * join of the updated relation.  It's also wrong to fail to make
1868                          * a jointree entry if only NEW and not OLD is mentioned.
1869                          */
1870                         if (has_old || (has_new && stmt->event == CMD_UPDATE))
1871                         {
1872                                 /*
1873                                  * If sub_qry is a setop, manipulating its jointree will do no
1874                                  * good at all, because the jointree is dummy. (This should be
1875                                  * a can't-happen case because of prior tests.)
1876                                  */
1877                                 if (sub_qry->setOperations != NULL)
1878                                         ereport(ERROR,
1879                                                         (errcode(ERRCODE_FEATURE_NOT_SUPPORTED),
1880                                                          errmsg("conditional UNION/INTERSECT/EXCEPT statements are not implemented")));
1881                                 /* hack so we can use addRTEtoQuery() */
1882                                 sub_pstate->p_rtable = sub_qry->rtable;
1883                                 sub_pstate->p_joinlist = sub_qry->jointree->fromlist;
1884                                 addRTEtoQuery(sub_pstate, oldrte, true, false, false);
1885                                 sub_qry->jointree->fromlist = sub_pstate->p_joinlist;
1886                         }
1887
1888                         newactions = lappend(newactions, top_subqry);
1889
1890                         free_parsestate(sub_pstate);
1891                 }
1892
1893                 *actions = newactions;
1894         }
1895
1896         free_parsestate(pstate);
1897
1898         /* Close relation, but keep the exclusive lock */
1899         heap_close(rel, NoLock);
1900 }
1901
1902
1903 /*
1904  * transformAlterTableStmt -
1905  *              parse analysis for ALTER TABLE
1906  *
1907  * Returns a List of utility commands to be done in sequence.  One of these
1908  * will be the transformed AlterTableStmt, but there may be additional actions
1909  * to be done before and after the actual AlterTable() call.
1910  */
1911 List *
1912 transformAlterTableStmt(AlterTableStmt *stmt, const char *queryString)
1913 {
1914         Relation        rel;
1915         ParseState *pstate;
1916         CreateStmtContext cxt;
1917         List       *result;
1918         List       *save_alist;
1919         ListCell   *lcmd,
1920                            *l;
1921         List       *newcmds = NIL;
1922         bool            skipValidation = true;
1923         AlterTableCmd *newcmd;
1924         LOCKMODE        lockmode;
1925
1926         /*
1927          * We must not scribble on the passed-in AlterTableStmt, so copy it. (This
1928          * is overkill, but easy.)
1929          */
1930         stmt = (AlterTableStmt *) copyObject(stmt);
1931
1932         /*
1933          * Assign the appropriate lock level for this list of subcommands.
1934          */
1935         lockmode = AlterTableGetLockLevel(stmt->cmds);
1936
1937         /*
1938          * Acquire appropriate lock on the target relation, which will be held until
1939          * end of transaction.  This ensures any decisions we make here based on
1940          * the state of the relation will still be good at execution. We must get
1941          * lock now because execution will later require it; taking a lower grade lock
1942          * now and trying to upgrade later risks deadlock.  Any new commands we add
1943          * after this must not upgrade the lock level requested here.
1944          */
1945         rel = relation_openrv(stmt->relation, lockmode);
1946
1947         /* Set up pstate */
1948         pstate = make_parsestate(NULL);
1949         pstate->p_sourcetext = queryString;
1950
1951         cxt.stmtType = "ALTER TABLE";
1952         cxt.relation = stmt->relation;
1953         cxt.rel = rel;
1954         cxt.inhRelations = NIL;
1955         cxt.isalter = true;
1956         cxt.hasoids = false;            /* need not be right */
1957         cxt.columns = NIL;
1958         cxt.ckconstraints = NIL;
1959         cxt.fkconstraints = NIL;
1960         cxt.ixconstraints = NIL;
1961         cxt.inh_indexes = NIL;
1962         cxt.blist = NIL;
1963         cxt.alist = NIL;
1964         cxt.pkey = NULL;
1965
1966         /*
1967          * The only subtypes that currently require parse transformation handling
1968          * are ADD COLUMN and ADD CONSTRAINT.  These largely re-use code from
1969          * CREATE TABLE.
1970          */
1971         foreach(lcmd, stmt->cmds)
1972         {
1973                 AlterTableCmd *cmd = (AlterTableCmd *) lfirst(lcmd);
1974
1975                 switch (cmd->subtype)
1976                 {
1977                         case AT_AddColumn:
1978                         case AT_AddColumnToView:
1979                                 {
1980                                         ColumnDef  *def = (ColumnDef *) cmd->def;
1981
1982                                         Assert(IsA(def, ColumnDef));
1983                                         transformColumnDefinition(pstate, &cxt, def);
1984
1985                                         /*
1986                                          * If the column has a non-null default, we can't skip
1987                                          * validation of foreign keys.
1988                                          */
1989                                         if (def->raw_default != NULL)
1990                                                 skipValidation = false;
1991
1992                                         /*
1993                                          * All constraints are processed in other ways. Remove the
1994                                          * original list
1995                                          */
1996                                         def->constraints = NIL;
1997
1998                                         newcmds = lappend(newcmds, cmd);
1999                                         break;
2000                                 }
2001                         case AT_AddConstraint:
2002
2003                                 /*
2004                                  * The original AddConstraint cmd node doesn't go to newcmds
2005                                  */
2006                                 if (IsA(cmd->def, Constraint))
2007                                 {
2008                                         transformTableConstraint(pstate, &cxt,
2009                                                                                          (Constraint *) cmd->def);
2010                                         if (((Constraint *) cmd->def)->contype == CONSTR_FOREIGN)
2011                                                 skipValidation = false;
2012                                 }
2013                                 else
2014                                         elog(ERROR, "unrecognized node type: %d",
2015                                                  (int) nodeTag(cmd->def));
2016                                 break;
2017
2018                         case AT_ProcessedConstraint:
2019
2020                                 /*
2021                                  * Already-transformed ADD CONSTRAINT, so just make it look
2022                                  * like the standard case.
2023                                  */
2024                                 cmd->subtype = AT_AddConstraint;
2025                                 newcmds = lappend(newcmds, cmd);
2026                                 break;
2027
2028                         default:
2029                                 newcmds = lappend(newcmds, cmd);
2030                                 break;
2031                 }
2032         }
2033
2034         /*
2035          * transformIndexConstraints wants cxt.alist to contain only index
2036          * statements, so transfer anything we already have into save_alist
2037          * immediately.
2038          */
2039         save_alist = cxt.alist;
2040         cxt.alist = NIL;
2041
2042         /* Postprocess index and FK constraints */
2043         transformIndexConstraints(pstate, &cxt);
2044
2045         transformFKConstraints(pstate, &cxt, skipValidation, true);
2046
2047         /*
2048          * Push any index-creation commands into the ALTER, so that they can be
2049          * scheduled nicely by tablecmds.c.  Note that tablecmds.c assumes that
2050          * the IndexStmt attached to an AT_AddIndex subcommand has already been
2051          * through transformIndexStmt.
2052          */
2053         foreach(l, cxt.alist)
2054         {
2055                 Node       *idxstmt = (Node *) lfirst(l);
2056
2057                 Assert(IsA(idxstmt, IndexStmt));
2058                 newcmd = makeNode(AlterTableCmd);
2059                 newcmd->subtype = AT_AddIndex;
2060                 newcmd->def = (Node *) transformIndexStmt((IndexStmt *) idxstmt,
2061                                                                                                   queryString);
2062                 newcmds = lappend(newcmds, newcmd);
2063         }
2064         cxt.alist = NIL;
2065
2066         /* Append any CHECK or FK constraints to the commands list */
2067         foreach(l, cxt.ckconstraints)
2068         {
2069                 newcmd = makeNode(AlterTableCmd);
2070                 newcmd->subtype = AT_AddConstraint;
2071                 newcmd->def = (Node *) lfirst(l);
2072                 newcmds = lappend(newcmds, newcmd);
2073         }
2074         foreach(l, cxt.fkconstraints)
2075         {
2076                 newcmd = makeNode(AlterTableCmd);
2077                 newcmd->subtype = AT_AddConstraint;
2078                 newcmd->def = (Node *) lfirst(l);
2079                 newcmds = lappend(newcmds, newcmd);
2080         }
2081
2082         /* Close rel but keep lock */
2083         relation_close(rel, NoLock);
2084
2085         /*
2086          * Output results.
2087          */
2088         stmt->cmds = newcmds;
2089
2090         result = lappend(cxt.blist, stmt);
2091         result = list_concat(result, cxt.alist);
2092         result = list_concat(result, save_alist);
2093
2094         return result;
2095 }
2096
2097
2098 /*
2099  * Preprocess a list of column constraint clauses
2100  * to attach constraint attributes to their primary constraint nodes
2101  * and detect inconsistent/misplaced constraint attributes.
2102  *
2103  * NOTE: currently, attributes are only supported for FOREIGN KEY, UNIQUE,
2104  * and PRIMARY KEY constraints, but someday they ought to be supported
2105  * for other constraint types.
2106  */
2107 static void
2108 transformConstraintAttrs(ParseState *pstate, List *constraintList)
2109 {
2110         Constraint *lastprimarycon = NULL;
2111         bool            saw_deferrability = false;
2112         bool            saw_initially = false;
2113         ListCell   *clist;
2114
2115 #define SUPPORTS_ATTRS(node)                            \
2116         ((node) != NULL &&                                              \
2117          ((node)->contype == CONSTR_PRIMARY ||  \
2118           (node)->contype == CONSTR_UNIQUE ||   \
2119           (node)->contype == CONSTR_EXCLUSION || \
2120           (node)->contype == CONSTR_FOREIGN))
2121
2122         foreach(clist, constraintList)
2123         {
2124                 Constraint *con = (Constraint *) lfirst(clist);
2125
2126                 if (!IsA(con, Constraint))
2127                         elog(ERROR, "unrecognized node type: %d",
2128                                  (int) nodeTag(con));
2129                 switch (con->contype)
2130                 {
2131                         case CONSTR_ATTR_DEFERRABLE:
2132                                 if (!SUPPORTS_ATTRS(lastprimarycon))
2133                                         ereport(ERROR,
2134                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2135                                                          errmsg("misplaced DEFERRABLE clause"),
2136                                                          parser_errposition(pstate, con->location)));
2137                                 if (saw_deferrability)
2138                                         ereport(ERROR,
2139                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2140                                                          errmsg("multiple DEFERRABLE/NOT DEFERRABLE clauses not allowed"),
2141                                                          parser_errposition(pstate, con->location)));
2142                                 saw_deferrability = true;
2143                                 lastprimarycon->deferrable = true;
2144                                 break;
2145
2146                         case CONSTR_ATTR_NOT_DEFERRABLE:
2147                                 if (!SUPPORTS_ATTRS(lastprimarycon))
2148                                         ereport(ERROR,
2149                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2150                                                          errmsg("misplaced NOT DEFERRABLE clause"),
2151                                                          parser_errposition(pstate, con->location)));
2152                                 if (saw_deferrability)
2153                                         ereport(ERROR,
2154                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2155                                                          errmsg("multiple DEFERRABLE/NOT DEFERRABLE clauses not allowed"),
2156                                                          parser_errposition(pstate, con->location)));
2157                                 saw_deferrability = true;
2158                                 lastprimarycon->deferrable = false;
2159                                 if (saw_initially &&
2160                                         lastprimarycon->initdeferred)
2161                                         ereport(ERROR,
2162                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2163                                                          errmsg("constraint declared INITIALLY DEFERRED must be DEFERRABLE"),
2164                                                          parser_errposition(pstate, con->location)));
2165                                 break;
2166
2167                         case CONSTR_ATTR_DEFERRED:
2168                                 if (!SUPPORTS_ATTRS(lastprimarycon))
2169                                         ereport(ERROR,
2170                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2171                                                          errmsg("misplaced INITIALLY DEFERRED clause"),
2172                                                          parser_errposition(pstate, con->location)));
2173                                 if (saw_initially)
2174                                         ereport(ERROR,
2175                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2176                                                          errmsg("multiple INITIALLY IMMEDIATE/DEFERRED clauses not allowed"),
2177                                                          parser_errposition(pstate, con->location)));
2178                                 saw_initially = true;
2179                                 lastprimarycon->initdeferred = true;
2180
2181                                 /*
2182                                  * If only INITIALLY DEFERRED appears, assume DEFERRABLE
2183                                  */
2184                                 if (!saw_deferrability)
2185                                         lastprimarycon->deferrable = true;
2186                                 else if (!lastprimarycon->deferrable)
2187                                         ereport(ERROR,
2188                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2189                                                          errmsg("constraint declared INITIALLY DEFERRED must be DEFERRABLE"),
2190                                                          parser_errposition(pstate, con->location)));
2191                                 break;
2192
2193                         case CONSTR_ATTR_IMMEDIATE:
2194                                 if (!SUPPORTS_ATTRS(lastprimarycon))
2195                                         ereport(ERROR,
2196                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2197                                                          errmsg("misplaced INITIALLY IMMEDIATE clause"),
2198                                                          parser_errposition(pstate, con->location)));
2199                                 if (saw_initially)
2200                                         ereport(ERROR,
2201                                                         (errcode(ERRCODE_SYNTAX_ERROR),
2202                                                          errmsg("multiple INITIALLY IMMEDIATE/DEFERRED clauses not allowed"),
2203                                                          parser_errposition(pstate, con->location)));
2204                                 saw_initially = true;
2205                                 lastprimarycon->initdeferred = false;
2206                                 break;
2207
2208                         default:
2209                                 /* Otherwise it's not an attribute */
2210                                 lastprimarycon = con;
2211                                 /* reset flags for new primary node */
2212                                 saw_deferrability = false;
2213                                 saw_initially = false;
2214                                 break;
2215                 }
2216         }
2217 }
2218
2219 /*
2220  * Special handling of type definition for a column
2221  */
2222 static void
2223 transformColumnType(ParseState *pstate, ColumnDef *column)
2224 {
2225         /*
2226          * All we really need to do here is verify that the type is valid.
2227          */
2228         Type            ctype = typenameType(pstate, column->typeName, NULL);
2229
2230         ReleaseSysCache(ctype);
2231 }
2232
2233
2234 /*
2235  * transformCreateSchemaStmt -
2236  *        analyzes the CREATE SCHEMA statement
2237  *
2238  * Split the schema element list into individual commands and place
2239  * them in the result list in an order such that there are no forward
2240  * references (e.g. GRANT to a table created later in the list). Note
2241  * that the logic we use for determining forward references is
2242  * presently quite incomplete.
2243  *
2244  * SQL92 also allows constraints to make forward references, so thumb through
2245  * the table columns and move forward references to a posterior alter-table
2246  * command.
2247  *
2248  * The result is a list of parse nodes that still need to be analyzed ---
2249  * but we can't analyze the later commands until we've executed the earlier
2250  * ones, because of possible inter-object references.
2251  *
2252  * Note: this breaks the rules a little bit by modifying schema-name fields
2253  * within passed-in structs.  However, the transformation would be the same
2254  * if done over, so it should be all right to scribble on the input to this
2255  * extent.
2256  */
2257 List *
2258 transformCreateSchemaStmt(CreateSchemaStmt *stmt)
2259 {
2260         CreateSchemaStmtContext cxt;
2261         List       *result;
2262         ListCell   *elements;
2263
2264         cxt.stmtType = "CREATE SCHEMA";
2265         cxt.schemaname = stmt->schemaname;
2266         cxt.authid = stmt->authid;
2267         cxt.sequences = NIL;
2268         cxt.tables = NIL;
2269         cxt.views = NIL;
2270         cxt.indexes = NIL;
2271         cxt.triggers = NIL;
2272         cxt.grants = NIL;
2273
2274         /*
2275          * Run through each schema element in the schema element list. Separate
2276          * statements by type, and do preliminary analysis.
2277          */
2278         foreach(elements, stmt->schemaElts)
2279         {
2280                 Node       *element = lfirst(elements);
2281
2282                 switch (nodeTag(element))
2283                 {
2284                         case T_CreateSeqStmt:
2285                                 {
2286                                         CreateSeqStmt *elp = (CreateSeqStmt *) element;
2287
2288                                         setSchemaName(cxt.schemaname, &elp->sequence->schemaname);
2289                                         cxt.sequences = lappend(cxt.sequences, element);
2290                                 }
2291                                 break;
2292
2293                         case T_CreateStmt:
2294                                 {
2295                                         CreateStmt *elp = (CreateStmt *) element;
2296
2297                                         setSchemaName(cxt.schemaname, &elp->relation->schemaname);
2298
2299                                         /*
2300                                          * XXX todo: deal with constraints
2301                                          */
2302                                         cxt.tables = lappend(cxt.tables, element);
2303                                 }
2304                                 break;
2305
2306                         case T_ViewStmt:
2307                                 {
2308                                         ViewStmt   *elp = (ViewStmt *) element;
2309
2310                                         setSchemaName(cxt.schemaname, &elp->view->schemaname);
2311
2312                                         /*
2313                                          * XXX todo: deal with references between views
2314                                          */
2315                                         cxt.views = lappend(cxt.views, element);
2316                                 }
2317                                 break;
2318
2319                         case T_IndexStmt:
2320                                 {
2321                                         IndexStmt  *elp = (IndexStmt *) element;
2322
2323                                         setSchemaName(cxt.schemaname, &elp->relation->schemaname);
2324                                         cxt.indexes = lappend(cxt.indexes, element);
2325                                 }
2326                                 break;
2327
2328                         case T_CreateTrigStmt:
2329                                 {
2330                                         CreateTrigStmt *elp = (CreateTrigStmt *) element;
2331
2332                                         setSchemaName(cxt.schemaname, &elp->relation->schemaname);
2333                                         cxt.triggers = lappend(cxt.triggers, element);
2334                                 }
2335                                 break;
2336
2337                         case T_GrantStmt:
2338                                 cxt.grants = lappend(cxt.grants, element);
2339                                 break;
2340
2341                         default:
2342                                 elog(ERROR, "unrecognized node type: %d",
2343                                          (int) nodeTag(element));
2344                 }
2345         }
2346
2347         result = NIL;
2348         result = list_concat(result, cxt.sequences);
2349         result = list_concat(result, cxt.tables);
2350         result = list_concat(result, cxt.views);
2351         result = list_concat(result, cxt.indexes);
2352         result = list_concat(result, cxt.triggers);
2353         result = list_concat(result, cxt.grants);
2354
2355         return result;
2356 }
2357
2358 /*
2359  * setSchemaName
2360  *              Set or check schema name in an element of a CREATE SCHEMA command
2361  */
2362 static void
2363 setSchemaName(char *context_schema, char **stmt_schema_name)
2364 {
2365         if (*stmt_schema_name == NULL)
2366                 *stmt_schema_name = context_schema;
2367         else if (strcmp(context_schema, *stmt_schema_name) != 0)
2368                 ereport(ERROR,
2369                                 (errcode(ERRCODE_INVALID_SCHEMA_DEFINITION),
2370                                  errmsg("CREATE specifies a schema (%s) "
2371                                                 "different from the one being created (%s)",
2372                                                 *stmt_schema_name, context_schema)));
2373 }