Annotation of pgsql/src/backend/rewrite/rewriteHandler.c, revision 1.107
1.1 scrappy 1: /*-------------------------------------------------------------------------
2: *
1.35 momjian 3: * rewriteHandler.c
1.95 tgl 4: * Primary module of query rewriter.
1.1 scrappy 5: *
1.103 momjian 6: * Portions Copyright (c) 1996-2002, PostgreSQL Global Development Group
1.66 momjian 7: * Portions Copyright (c) 1994, Regents of the University of California
1.1 scrappy 8: *
9: * IDENTIFICATION
1.107 ! tgl 10: * $Header: /cvsroot/pgsql-server/src/backend/rewrite/rewriteHandler.c,v 1.106 2002/08/26 17:53:58 tgl Exp $
1.1 scrappy 11: *
12: *-------------------------------------------------------------------------
13: */
14: #include "postgres.h"
1.53 momjian 15:
16: #include "access/heapam.h"
1.55 tgl 17: #include "catalog/pg_operator.h"
1.53 momjian 18: #include "catalog/pg_type.h"
19: #include "miscadmin.h"
1.55 tgl 20: #include "nodes/makefuncs.h"
1.47 tgl 21: #include "optimizer/clauses.h"
1.28 momjian 22: #include "optimizer/prep.h"
1.70 tgl 23: #include "optimizer/var.h"
1.53 momjian 24: #include "parser/analyze.h"
1.101 tgl 25: #include "parser/parse_coerce.h"
1.55 tgl 26: #include "parser/parse_expr.h"
27: #include "parser/parse_oper.h"
1.53 momjian 28: #include "parser/parse_target.h"
1.101 tgl 29: #include "parser/parse_type.h"
1.53 momjian 30: #include "parser/parsetree.h"
1.95 tgl 31: #include "rewrite/rewriteHandler.h"
1.1 scrappy 32: #include "rewrite/rewriteManip.h"
1.101 tgl 33: #include "utils/builtins.h"
1.22 momjian 34: #include "utils/lsyscache.h"
35:
36:
1.95 tgl 37: static Query *rewriteRuleAction(Query *parsetree,
1.98 momjian 38: Query *rule_action,
39: Node *rule_qual,
40: int rt_index,
41: CmdType event);
1.89 tgl 42: static List *adjustJoinTreeList(Query *parsetree, bool removert, int rt_index);
1.101 tgl 43: static void rewriteTargetList(Query *parsetree, Relation target_relation);
44: static TargetEntry *process_matched_tle(TargetEntry *src_tle,
45: TargetEntry *prior_tle);
1.86 tgl 46: static void markQueryForUpdate(Query *qry, bool skipOldNew);
1.81 tgl 47: static List *matchLocks(CmdType event, RuleLock *rulelocks,
1.90 momjian 48: int varno, Query *parsetree);
1.22 momjian 49: static Query *fireRIRrules(Query *parsetree);
1.82 tgl 50:
1.1 scrappy 51:
52: /*
1.95 tgl 53: * rewriteRuleAction -
54: * Rewrite the rule action with appropriate qualifiers (taken from
55: * the triggering query).
1.1 scrappy 56: */
1.95 tgl 57: static Query *
58: rewriteRuleAction(Query *parsetree,
1.6 momjian 59: Query *rule_action,
60: Node *rule_qual,
1.4 momjian 61: int rt_index,
1.95 tgl 62: CmdType event)
1.4 momjian 63: {
1.95 tgl 64: int current_varno,
65: new_varno;
66: int rt_length;
1.84 tgl 67: Query *sub_action;
68: Query **sub_action_ptr;
1.4 momjian 69:
1.95 tgl 70: /*
71: * Make modifiable copies of rule action and qual (what we're passed
72: * are the stored versions in the relcache; don't touch 'em!).
73: */
74: rule_action = (Query *) copyObject(rule_action);
75: rule_qual = (Node *) copyObject(rule_qual);
76:
77: current_varno = rt_index;
1.84 tgl 78: rt_length = length(parsetree->rtable);
1.95 tgl 79: new_varno = PRS2_NEW_VARNO + rt_length;
1.84 tgl 80:
81: /*
82: * Adjust rule action and qual to offset its varnos, so that we can
1.94 tgl 83: * merge its rtable with the main parsetree's rtable.
1.84 tgl 84: *
1.90 momjian 85: * If the rule action is an INSERT...SELECT, the OLD/NEW rtable entries
86: * will be in the SELECT part, and we have to modify that rather than
87: * the top-level INSERT (kluge!).
1.84 tgl 88: */
1.95 tgl 89: sub_action = getInsertSelectQuery(rule_action, &sub_action_ptr);
1.84 tgl 90:
91: OffsetVarNodes((Node *) sub_action, rt_length, 0);
1.95 tgl 92: OffsetVarNodes(rule_qual, rt_length, 0);
1.84 tgl 93: /* but references to *OLD* should point at original rt_index */
94: ChangeVarNodes((Node *) sub_action,
95: PRS2_OLD_VARNO + rt_length, rt_index, 0);
1.95 tgl 96: ChangeVarNodes(rule_qual,
1.84 tgl 97: PRS2_OLD_VARNO + rt_length, rt_index, 0);
98:
99: /*
1.98 momjian 100: * Generate expanded rtable consisting of main parsetree's rtable plus
101: * rule action's rtable; this becomes the complete rtable for the rule
102: * action. Some of the entries may be unused after we finish
103: * rewriting, but if we tried to clean those out we'd have a much
104: * harder job to adjust RT indexes in the query's Vars. It's OK to
105: * have unused RT entries, since planner will ignore them.
1.84 tgl 106: *
1.94 tgl 107: * NOTE: because planner will destructively alter rtable, we must ensure
1.98 momjian 108: * that rule action's rtable is separate and shares no substructure
109: * with the main rtable. Hence do a deep copy here.
1.94 tgl 110: */
111: sub_action->rtable = nconc((List *) copyObject(parsetree->rtable),
112: sub_action->rtable);
1.84 tgl 113:
114: /*
115: * Each rule action's jointree should be the main parsetree's jointree
1.90 momjian 116: * plus that rule's jointree, but usually *without* the original
117: * rtindex that we're replacing (if present, which it won't be for
118: * INSERT). Note that if the rule action refers to OLD, its jointree
119: * will add a reference to rt_index. If the rule action doesn't refer
120: * to OLD, but either the rule_qual or the user query quals do, then
121: * we need to keep the original rtindex in the jointree to provide
122: * data for the quals. We don't want the original rtindex to be
123: * joined twice, however, so avoid keeping it if the rule action
124: * mentions it.
1.94 tgl 125: *
1.98 momjian 126: * As above, the action's jointree must not share substructure with the
127: * main parsetree's.
1.84 tgl 128: */
1.87 tgl 129: if (sub_action->jointree != NULL)
1.84 tgl 130: {
1.90 momjian 131: bool keeporig;
132: List *newjointree;
1.84 tgl 133:
1.90 momjian 134: keeporig = (!rangeTableEntry_used((Node *) sub_action->jointree,
135: rt_index, 0)) &&
1.95 tgl 136: (rangeTableEntry_used(rule_qual, rt_index, 0) ||
1.98 momjian 137: rangeTableEntry_used(parsetree->jointree->quals, rt_index, 0));
1.89 tgl 138: newjointree = adjustJoinTreeList(parsetree, !keeporig, rt_index);
1.84 tgl 139: sub_action->jointree->fromlist =
140: nconc(newjointree, sub_action->jointree->fromlist);
141: }
142:
143: /*
144: * We copy the qualifications of the parsetree to the action and vice
145: * versa. So force hasSubLinks if one of them has it. If this is not
146: * right, the flag will get cleared later, but we mustn't risk having
1.98 momjian 147: * it not set when it needs to be. (XXX this should probably be
148: * handled by AddQual and friends, not here...)
1.84 tgl 149: */
150: if (parsetree->hasSubLinks)
151: sub_action->hasSubLinks = TRUE;
152: else if (sub_action->hasSubLinks)
153: parsetree->hasSubLinks = TRUE;
154:
155: /*
1.90 momjian 156: * Event Qualification forces copying of parsetree and splitting into
157: * two queries one w/rule_qual, one w/NOT rule_qual. Also add user
158: * query qual onto rule action
1.84 tgl 159: */
1.95 tgl 160: AddQual(sub_action, rule_qual);
1.84 tgl 161:
162: AddQual(sub_action, parsetree->jointree->quals);
1.4 momjian 163:
1.84 tgl 164: /*
1.90 momjian 165: * Rewrite new.attribute w/ right hand side of target-list entry for
166: * appropriate field name in insert/update.
1.84 tgl 167: *
168: * KLUGE ALERT: since ResolveNew returns a mutated copy, we can't just
169: * apply it to sub_action; we have to remember to update the sublink
1.95 tgl 170: * inside rule_action, too.
1.84 tgl 171: */
1.95 tgl 172: if (event == CMD_INSERT || event == CMD_UPDATE)
1.84 tgl 173: {
174: sub_action = (Query *) ResolveNew((Node *) sub_action,
1.95 tgl 175: new_varno,
1.84 tgl 176: 0,
177: parsetree->targetList,
1.95 tgl 178: event,
179: current_varno);
1.84 tgl 180: if (sub_action_ptr)
181: *sub_action_ptr = sub_action;
182: else
1.95 tgl 183: rule_action = sub_action;
1.4 momjian 184: }
1.84 tgl 185:
1.95 tgl 186: return rule_action;
1.4 momjian 187: }
188:
1.22 momjian 189: /*
1.89 tgl 190: * Copy the query's jointree list, and optionally attempt to remove any
191: * occurrence of the given rt_index as a top-level join item (we do not look
192: * for it within join items; this is OK because we are only expecting to find
193: * it as an UPDATE or DELETE target relation, which will be at the top level
1.94 tgl 194: * of the join). Returns modified jointree list --- this is a separate copy
195: * sharing no nodes with the original.
1.22 momjian 196: */
1.80 tgl 197: static List *
1.89 tgl 198: adjustJoinTreeList(Query *parsetree, bool removert, int rt_index)
1.71 momjian 199: {
1.94 tgl 200: List *newjointree = copyObject(parsetree->jointree->fromlist);
1.80 tgl 201: List *jjt;
1.58 tgl 202:
1.89 tgl 203: if (removert)
1.58 tgl 204: {
1.89 tgl 205: foreach(jjt, newjointree)
206: {
207: RangeTblRef *rtr = lfirst(jjt);
1.22 momjian 208:
1.90 momjian 209: if (IsA(rtr, RangeTblRef) &&rtr->rtindex == rt_index)
1.89 tgl 210: {
211: newjointree = lremove(rtr, newjointree);
212: break;
213: }
1.80 tgl 214: }
1.58 tgl 215: }
1.80 tgl 216: return newjointree;
1.22 momjian 217: }
1.20 momjian 218:
1.4 momjian 219:
1.22 momjian 220: /*
1.101 tgl 221: * rewriteTargetList - rewrite INSERT/UPDATE targetlist into standard form
222: *
223: * This has the following responsibilities:
224: *
225: * 1. For an INSERT, add tlist entries to compute default values for any
226: * attributes that have defaults and are not assigned to in the given tlist.
227: * (We do not insert anything for default-less attributes, however. The
228: * planner will later insert NULLs for them, but there's no reason to slow
229: * down rewriter processing with extra tlist nodes.)
230: *
231: * 2. Merge multiple entries for the same target attribute, or declare error
232: * if we can't. Presently, multiple entries are only allowed for UPDATE of
233: * an array field, for example "UPDATE table SET foo[2] = 42, foo[4] = 43".
234: * We can merge such operations into a single assignment op. Essentially,
235: * the expression we want to produce in this case is like
236: * foo = array_set(array_set(foo, 2, 42), 4, 43)
237: *
238: * 3. Sort the tlist into standard order: non-junk fields in order by resno,
239: * then junk fields (these in no particular order).
240: *
241: * We must do items 1 and 2 before firing rewrite rules, else rewritten
242: * references to NEW.foo will produce wrong or incomplete results. Item 3
243: * is not needed for rewriting, but will be needed by the planner, and we
244: * can do it essentially for free while handling items 1 and 2.
245: */
246: static void
247: rewriteTargetList(Query *parsetree, Relation target_relation)
248: {
249: CmdType commandType = parsetree->commandType;
250: List *tlist = parsetree->targetList;
251: List *new_tlist = NIL;
252: int attrno,
253: numattrs;
254: List *temp;
255:
256: /*
257: * Scan the tuple description in the relation's relcache entry to make
258: * sure we have all the user attributes in the right order.
259: */
260: numattrs = RelationGetNumberOfAttributes(target_relation);
261:
262: for (attrno = 1; attrno <= numattrs; attrno++)
263: {
264: Form_pg_attribute att_tup = target_relation->rd_att->attrs[attrno-1];
265: TargetEntry *new_tle = NULL;
1.105 tgl 266:
267: /* We can ignore deleted attributes */
268: if (att_tup->attisdropped)
269: continue;
1.101 tgl 270:
271: /*
272: * Look for targetlist entries matching this attr. We match by
273: * resno, but the resname should match too.
274: *
275: * Junk attributes are not candidates to be matched.
276: */
277: foreach(temp, tlist)
278: {
279: TargetEntry *old_tle = (TargetEntry *) lfirst(temp);
280: Resdom *resdom = old_tle->resdom;
281:
282: if (!resdom->resjunk && resdom->resno == attrno)
283: {
284: Assert(strcmp(resdom->resname,
285: NameStr(att_tup->attname)) == 0);
286: new_tle = process_matched_tle(old_tle, new_tle);
287: /* keep scanning to detect multiple assignments to attr */
288: }
289: }
290:
291: if (new_tle == NULL && commandType == CMD_INSERT)
292: {
293: /*
294: * Didn't find a matching tlist entry; if it's an INSERT,
295: * look for a default value, and add a tlist entry computing
296: * the default if we find one.
297: */
298: Node *new_expr;
299:
300: new_expr = build_column_default(target_relation, attrno);
301:
302: if (new_expr)
303: new_tle = makeTargetEntry(makeResdom(attrno,
304: att_tup->atttypid,
305: att_tup->atttypmod,
306: pstrdup(NameStr(att_tup->attname)),
307: false),
308: new_expr);
309: }
310:
311: if (new_tle)
312: new_tlist = lappend(new_tlist, new_tle);
313: }
314:
315: /*
316: * Copy all resjunk tlist entries to the end of the new tlist, and
317: * assign them resnos above the last real resno.
318: *
319: * Typical junk entries include ORDER BY or GROUP BY expressions (are
320: * these actually possible in an INSERT or UPDATE?), system attribute
321: * references, etc.
322: */
323: foreach(temp, tlist)
324: {
325: TargetEntry *old_tle = (TargetEntry *) lfirst(temp);
326: Resdom *resdom = old_tle->resdom;
327:
328: if (resdom->resjunk)
329: {
330: /* Get the resno right, but don't copy unnecessarily */
331: if (resdom->resno != attrno)
332: {
333: resdom = (Resdom *) copyObject((Node *) resdom);
334: resdom->resno = attrno;
335: old_tle = makeTargetEntry(resdom, old_tle->expr);
336: }
337: new_tlist = lappend(new_tlist, old_tle);
338: attrno++;
339: }
340: else
341: {
342: /* Let's just make sure we processed all the non-junk items */
343: if (resdom->resno < 1 || resdom->resno > numattrs)
344: elog(ERROR, "rewriteTargetList: bogus resno %d in targetlist",
345: resdom->resno);
346: }
347: }
348:
349: parsetree->targetList = new_tlist;
350: }
351:
352:
353: /*
354: * Convert a matched TLE from the original tlist into a correct new TLE.
355: *
356: * This routine detects and handles multiple assignments to the same target
357: * attribute.
358: */
359: static TargetEntry *
360: process_matched_tle(TargetEntry *src_tle,
361: TargetEntry *prior_tle)
362: {
363: Resdom *resdom = src_tle->resdom;
364: Node *priorbottom;
365: ArrayRef *newexpr;
366:
367: if (prior_tle == NULL)
368: {
369: /*
370: * Normal case where this is the first assignment to the
371: * attribute.
372: */
373: return src_tle;
374: }
375:
376: /*
377: * Multiple assignments to same attribute. Allow only if all are
378: * array-assign operators with same bottom array object.
379: */
380: if (src_tle->expr == NULL || !IsA(src_tle->expr, ArrayRef) ||
381: ((ArrayRef *) src_tle->expr)->refassgnexpr == NULL ||
382: prior_tle->expr == NULL || !IsA(prior_tle->expr, ArrayRef) ||
383: ((ArrayRef *) prior_tle->expr)->refassgnexpr == NULL ||
1.106 tgl 384: ((ArrayRef *) src_tle->expr)->refrestype !=
385: ((ArrayRef *) prior_tle->expr)->refrestype)
1.101 tgl 386: elog(ERROR, "Multiple assignments to same attribute \"%s\"",
387: resdom->resname);
388:
389: /*
390: * Prior TLE could be a nest of ArrayRefs if we do this more than
391: * once.
392: */
393: priorbottom = ((ArrayRef *) prior_tle->expr)->refexpr;
394: while (priorbottom != NULL && IsA(priorbottom, ArrayRef) &&
395: ((ArrayRef *) priorbottom)->refassgnexpr != NULL)
396: priorbottom = ((ArrayRef *) priorbottom)->refexpr;
397: if (!equal(priorbottom, ((ArrayRef *) src_tle->expr)->refexpr))
398: elog(ERROR, "Multiple assignments to same attribute \"%s\"",
399: resdom->resname);
400:
401: /*
402: * Looks OK to nest 'em.
403: */
404: newexpr = makeNode(ArrayRef);
405: memcpy(newexpr, src_tle->expr, sizeof(ArrayRef));
406: newexpr->refexpr = prior_tle->expr;
407:
408: return makeTargetEntry(resdom, (Node *) newexpr);
409: }
410:
411:
412: /*
413: * Make an expression tree for the default value for a column.
414: *
415: * If there is no default, return a NULL instead.
416: */
1.104 momjian 417: Node *
1.101 tgl 418: build_column_default(Relation rel, int attrno)
419: {
420: TupleDesc rd_att = rel->rd_att;
421: Form_pg_attribute att_tup = rd_att->attrs[attrno - 1];
422: Oid atttype = att_tup->atttypid;
423: int32 atttypmod = att_tup->atttypmod;
424: Node *expr = NULL;
425: Oid exprtype;
426:
427: /*
428: * Scan to see if relation has a default for this column.
429: */
430: if (rd_att->constr && rd_att->constr->num_defval > 0)
431: {
432: AttrDefault *defval = rd_att->constr->defval;
433: int ndef = rd_att->constr->num_defval;
434:
435: while (--ndef >= 0)
436: {
437: if (attrno == defval[ndef].adnum)
438: {
439: /*
440: * Found it, convert string representation to node tree.
441: */
442: expr = stringToNode(defval[ndef].adbin);
443: break;
444: }
445: }
446: }
447:
448: if (expr == NULL)
449: {
450: /*
451: * No per-column default, so look for a default for the type itself.
452: */
453: if (att_tup->attisset)
454: {
455: /*
456: * Set attributes are represented as OIDs no matter what the set
457: * element type is, and the element type's default is irrelevant
458: * too.
459: */
460: }
461: else
462: {
463: expr = get_typdefault(atttype);
464: }
465: }
466:
467: if (expr == NULL)
468: return NULL; /* No default anywhere */
469:
470: /*
471: * Make sure the value is coerced to the target column
472: * type (might not be right type yet if it's not a
473: * constant!) This should match the parser's processing of
474: * non-defaulted expressions --- see
475: * updateTargetListEntry().
476: */
477: exprtype = exprType(expr);
478:
479: if (exprtype != atttype)
480: {
481: expr = CoerceTargetExpr(NULL, expr, exprtype,
1.102 tgl 482: atttype, atttypmod, false);
1.101 tgl 483:
484: /*
485: * This really shouldn't fail; should have checked the
486: * default's type when it was created ...
487: */
488: if (expr == NULL)
489: elog(ERROR, "Column \"%s\" is of type %s"
490: " but default expression is of type %s"
491: "\n\tYou will need to rewrite or cast the expression",
492: NameStr(att_tup->attname),
493: format_type_be(atttype),
494: format_type_be(exprtype));
495: }
496:
497: /*
498: * If the column is a fixed-length type, it may need a
499: * length coercion as well as a type coercion.
500: */
501: expr = coerce_type_typmod(NULL, expr, atttype, atttypmod);
502:
503: return expr;
504: }
505:
506:
507: /*
1.81 tgl 508: * matchLocks -
509: * match the list of locks and returns the matching rules
1.22 momjian 510: */
1.81 tgl 511: static List *
512: matchLocks(CmdType event,
513: RuleLock *rulelocks,
514: int varno,
515: Query *parsetree)
1.71 momjian 516: {
1.81 tgl 517: List *real_locks = NIL;
518: int nlocks;
519: int i;
1.58 tgl 520:
1.81 tgl 521: Assert(rulelocks != NULL); /* we get called iff there is some lock */
522: Assert(parsetree != NULL);
1.22 momjian 523:
1.81 tgl 524: if (parsetree->commandType != CMD_SELECT)
1.58 tgl 525: {
1.81 tgl 526: if (parsetree->resultRelation != varno)
527: return NIL;
1.58 tgl 528: }
1.22 momjian 529:
1.81 tgl 530: nlocks = rulelocks->numLocks;
1.22 momjian 531:
1.81 tgl 532: for (i = 0; i < nlocks; i++)
1.45 momjian 533: {
1.81 tgl 534: RewriteRule *oneLock = rulelocks->rules[i];
1.22 momjian 535:
1.81 tgl 536: if (oneLock->event == event)
1.63 tgl 537: {
1.81 tgl 538: if (parsetree->commandType != CMD_SELECT ||
539: (oneLock->attrno == -1 ?
540: rangeTableEntry_used((Node *) parsetree, varno, 0) :
541: attribute_used((Node *) parsetree,
542: varno, oneLock->attrno, 0)))
543: real_locks = lappend(real_locks, oneLock);
1.63 tgl 544: }
1.22 momjian 545: }
1.45 momjian 546:
1.81 tgl 547: return real_locks;
1.58 tgl 548: }
1.22 momjian 549:
550:
1.81 tgl 551: static Query *
552: ApplyRetrieveRule(Query *parsetree,
553: RewriteRule *rule,
554: int rt_index,
555: bool relation_level,
556: Relation relation,
557: bool relIsUsed)
1.58 tgl 558: {
1.81 tgl 559: Query *rule_action;
560: RangeTblEntry *rte,
561: *subrte;
1.22 momjian 562:
1.81 tgl 563: if (length(rule->actions) != 1)
564: elog(ERROR, "ApplyRetrieveRule: expected just one rule action");
565: if (rule->qual != NULL)
566: elog(ERROR, "ApplyRetrieveRule: can't handle qualified ON SELECT rule");
1.90 momjian 567: if (!relation_level)
1.81 tgl 568: elog(ERROR, "ApplyRetrieveRule: can't handle per-attribute ON SELECT rule");
1.71 momjian 569:
1.63 tgl 570: /*
1.81 tgl 571: * Make a modifiable copy of the view query, and recursively expand
572: * any view references inside it.
1.58 tgl 573: */
1.81 tgl 574: rule_action = copyObject(lfirst(rule->actions));
1.22 momjian 575:
1.81 tgl 576: rule_action = fireRIRrules(rule_action);
1.22 momjian 577:
1.81 tgl 578: /*
1.90 momjian 579: * VIEWs are really easy --- just plug the view query in as a
580: * subselect, replacing the relation's original RTE.
1.81 tgl 581: */
582: rte = rt_fetch(rt_index, parsetree->rtable);
1.58 tgl 583:
1.99 tgl 584: rte->rtekind = RTE_SUBQUERY;
1.81 tgl 585: rte->relid = InvalidOid;
586: rte->subquery = rule_action;
587: rte->inh = false; /* must not be set for a subquery */
1.71 momjian 588:
1.58 tgl 589: /*
1.81 tgl 590: * We move the view's permission check data down to its rangetable.
591: * The checks will actually be done against the *OLD* entry therein.
1.58 tgl 592: */
1.81 tgl 593: subrte = rt_fetch(PRS2_OLD_VARNO, rule_action->rtable);
594: Assert(subrte->relid == relation->rd_id);
595: subrte->checkForRead = rte->checkForRead;
596: subrte->checkForWrite = rte->checkForWrite;
1.93 tgl 597: subrte->checkAsUser = rte->checkAsUser;
1.27 thomas 598:
1.81 tgl 599: rte->checkForRead = false; /* no permission check on subquery itself */
600: rte->checkForWrite = false;
1.93 tgl 601: rte->checkAsUser = InvalidOid;
1.60 tgl 602:
1.71 momjian 603: /*
1.81 tgl 604: * FOR UPDATE of view?
1.60 tgl 605: */
1.81 tgl 606: if (intMember(rt_index, parsetree->rowMarks))
1.22 momjian 607: {
1.45 momjian 608: /*
1.81 tgl 609: * Remove the view from the list of rels that will actually be
610: * marked FOR UPDATE by the executor. It will still be access-
611: * checked for write access, though.
1.29 vadim 612: */
1.81 tgl 613: parsetree->rowMarks = lremovei(rt_index, parsetree->rowMarks);
1.58 tgl 614:
1.81 tgl 615: /*
616: * Set up the view's referenced tables as if FOR UPDATE.
617: */
1.86 tgl 618: markQueryForUpdate(rule_action, true);
619: }
620:
621: return parsetree;
622: }
623:
624: /*
625: * Recursively mark all relations used by a view as FOR UPDATE.
626: *
627: * This may generate an invalid query, eg if some sub-query uses an
628: * aggregate. We leave it to the planner to detect that.
629: *
630: * NB: this must agree with the parser's transformForUpdate() routine.
631: */
632: static void
633: markQueryForUpdate(Query *qry, bool skipOldNew)
634: {
635: Index rti = 0;
636: List *l;
637:
638: foreach(l, qry->rtable)
639: {
640: RangeTblEntry *rte = (RangeTblEntry *) lfirst(l);
641:
642: rti++;
643:
644: /* Ignore OLD and NEW entries if we are at top level of view */
645: if (skipOldNew &&
646: (rti == PRS2_OLD_VARNO || rti == PRS2_NEW_VARNO))
647: continue;
648:
1.99 tgl 649: if (rte->rtekind == RTE_RELATION)
1.86 tgl 650: {
651: if (!intMember(rti, qry->rowMarks))
652: qry->rowMarks = lappendi(qry->rowMarks, rti);
653: rte->checkForWrite = true;
1.29 vadim 654: }
1.99 tgl 655: else if (rte->rtekind == RTE_SUBQUERY)
656: {
657: /* FOR UPDATE of subquery is propagated to subquery's rels */
658: markQueryForUpdate(rte->subquery, false);
659: }
1.29 vadim 660: }
1.22 momjian 661: }
662:
663:
1.58 tgl 664: /*
1.81 tgl 665: * fireRIRonSubLink -
666: * Apply fireRIRrules() to each SubLink (subselect in expression) found
667: * in the given tree.
1.58 tgl 668: *
669: * NOTE: although this has the form of a walker, we cheat and modify the
1.71 momjian 670: * SubLink nodes in-place. It is caller's responsibility to ensure that
1.58 tgl 671: * no unwanted side-effects occur!
1.80 tgl 672: *
673: * This is unlike most of the other routines that recurse into subselects,
674: * because we must take control at the SubLink node in order to replace
675: * the SubLink's subselect link with the possibly-rewritten subquery.
1.58 tgl 676: */
677: static bool
1.81 tgl 678: fireRIRonSubLink(Node *node, void *context)
1.22 momjian 679: {
680: if (node == NULL)
1.58 tgl 681: return false;
682: if (IsA(node, SubLink))
683: {
684: SubLink *sub = (SubLink *) node;
1.22 momjian 685:
1.58 tgl 686: /* Do what we came for */
1.80 tgl 687: sub->subselect = (Node *) fireRIRrules((Query *) (sub->subselect));
688: /* Fall through to process lefthand args of SubLink */
1.22 momjian 689: }
1.90 momjian 690:
1.80 tgl 691: /*
692: * Do NOT recurse into Query nodes, because fireRIRrules already
1.81 tgl 693: * processed subselects of subselects for us.
1.80 tgl 694: */
1.81 tgl 695: return expression_tree_walker(node, fireRIRonSubLink,
1.58 tgl 696: (void *) context);
1.22 momjian 697: }
698:
699:
700: /*
701: * fireRIRrules -
702: * Apply all RIR rules on each rangetable entry in a query
703: */
704: static Query *
705: fireRIRrules(Query *parsetree)
706: {
1.45 momjian 707: int rt_index;
1.22 momjian 708:
1.71 momjian 709: /*
710: * don't try to convert this into a foreach loop, because rtable list
711: * can get changed each time through...
1.60 tgl 712: */
1.22 momjian 713: rt_index = 0;
1.45 momjian 714: while (rt_index < length(parsetree->rtable))
715: {
1.83 tgl 716: RangeTblEntry *rte;
717: Relation rel;
718: List *locks;
719: RuleLock *rules;
720: RewriteRule *rule;
721: LOCKMODE lockmode;
722: bool relIsUsed;
723: int i;
724: List *l;
725:
1.22 momjian 726: ++rt_index;
727:
1.62 tgl 728: rte = rt_fetch(rt_index, parsetree->rtable);
1.44 wieck 729:
1.60 tgl 730: /*
1.81 tgl 731: * A subquery RTE can't have associated rules, so there's nothing
732: * to do to this level of the query, but we must recurse into the
733: * subquery to expand any rule references in it.
734: */
1.99 tgl 735: if (rte->rtekind == RTE_SUBQUERY)
1.81 tgl 736: {
737: rte->subquery = fireRIRrules(rte->subquery);
738: continue;
739: }
740:
741: /*
1.99 tgl 742: * Joins and other non-relation RTEs can be ignored completely.
743: */
744: if (rte->rtekind != RTE_RELATION)
745: continue;
746:
747: /*
1.72 tgl 748: * If the table is not referenced in the query, then we ignore it.
749: * This prevents infinite expansion loop due to new rtable entries
750: * inserted by expansion of a rule. A table is referenced if it is
1.80 tgl 751: * part of the join set (a source table), or is referenced by any
752: * Var nodes, or is the result table.
1.60 tgl 753: */
1.80 tgl 754: relIsUsed = rangeTableEntry_used((Node *) parsetree, rt_index, 0);
755:
756: if (!relIsUsed && rt_index != parsetree->resultRelation)
1.22 momjian 757: continue;
1.45 momjian 758:
1.83 tgl 759: /*
1.90 momjian 760: * This may well be the first access to the relation during the
761: * current statement (it will be, if this Query was extracted from
762: * a rule or somehow got here other than via the parser).
763: * Therefore, grab the appropriate lock type for the relation, and
764: * do not release it until end of transaction. This protects the
765: * rewriter and planner against schema changes mid-query.
1.83 tgl 766: *
1.90 momjian 767: * If the relation is the query's result relation, then
768: * RewriteQuery() already got the right lock on it, so we need no
769: * additional lock. Otherwise, check to see if the relation is
770: * accessed FOR UPDATE or not.
1.83 tgl 771: */
772: if (rt_index == parsetree->resultRelation)
773: lockmode = NoLock;
774: else if (intMember(rt_index, parsetree->rowMarks))
775: lockmode = RowShareLock;
776: else
777: lockmode = AccessShareLock;
778:
1.100 tgl 779: rel = heap_open(rte->relid, lockmode);
1.92 tgl 780:
781: /*
782: * Collect the RIR rules that we must apply
783: */
1.60 tgl 784: rules = rel->rd_rules;
785: if (rules == NULL)
1.45 momjian 786: {
1.83 tgl 787: heap_close(rel, NoLock);
1.22 momjian 788: continue;
789: }
1.60 tgl 790: locks = NIL;
1.45 momjian 791: for (i = 0; i < rules->numLocks; i++)
792: {
1.22 momjian 793: rule = rules->rules[i];
794: if (rule->event != CMD_SELECT)
795: continue;
1.45 momjian 796:
1.60 tgl 797: if (rule->attrno > 0)
798: {
799: /* per-attr rule; do we need it? */
1.80 tgl 800: if (!attribute_used((Node *) parsetree, rt_index,
1.71 momjian 801: rule->attrno, 0))
1.60 tgl 802: continue;
803: }
1.22 momjian 804:
805: locks = lappend(locks, rule);
806: }
807:
808: /*
809: * Now apply them
810: */
1.45 momjian 811: foreach(l, locks)
812: {
1.22 momjian 813: rule = lfirst(l);
814:
1.58 tgl 815: parsetree = ApplyRetrieveRule(parsetree,
1.81 tgl 816: rule,
1.58 tgl 817: rt_index,
1.81 tgl 818: rule->attrno == -1,
1.58 tgl 819: rel,
1.80 tgl 820: relIsUsed);
1.4 momjian 821: }
1.22 momjian 822:
1.83 tgl 823: heap_close(rel, NoLock);
1.22 momjian 824: }
825:
1.81 tgl 826: /*
827: * Recurse into sublink subqueries, too.
828: */
829: if (parsetree->hasSubLinks)
1.82 tgl 830: query_tree_walker(parsetree, fireRIRonSubLink, NULL,
1.90 momjian 831: false /* already handled the ones in rtable */ );
1.81 tgl 832:
833: /*
1.90 momjian 834: * If the query was marked having aggregates, check if this is still
835: * true after rewriting. Ditto for sublinks. Note there should be no
836: * aggs in the qual at this point. (Does this code still do anything
837: * useful? The view-becomes-subselect-in-FROM approach doesn't look
838: * like it could remove aggs or sublinks...)
1.81 tgl 839: */
1.68 tgl 840: if (parsetree->hasAggs)
1.81 tgl 841: {
842: parsetree->hasAggs = checkExprHasAggs((Node *) parsetree);
843: if (parsetree->hasAggs)
844: if (checkExprHasAggs((Node *) parsetree->jointree))
845: elog(ERROR, "fireRIRrules: failed to remove aggs from qual");
846: }
1.62 tgl 847: if (parsetree->hasSubLinks)
1.81 tgl 848: parsetree->hasSubLinks = checkExprHasSubLink((Node *) parsetree);
1.22 momjian 849:
850: return parsetree;
851: }
852:
853:
854: /*
855: * idea is to fire regular rules first, then qualified instead
856: * rules and unqualified instead rules last. Any lemming is counted for.
857: */
858: static List *
859: orderRules(List *locks)
860: {
861: List *regular = NIL;
862: List *instead_rules = NIL;
863: List *instead_qualified = NIL;
864: List *i;
865:
866: foreach(i, locks)
867: {
868: RewriteRule *rule_lock = (RewriteRule *) lfirst(i);
869:
870: if (rule_lock->isInstead)
1.4 momjian 871: {
1.22 momjian 872: if (rule_lock->qual == NULL)
873: instead_rules = lappend(instead_rules, rule_lock);
874: else
875: instead_qualified = lappend(instead_qualified, rule_lock);
1.4 momjian 876: }
1.22 momjian 877: else
878: regular = lappend(regular, rule_lock);
1.4 momjian 879: }
1.81 tgl 880: return nconc(nconc(regular, instead_qualified), instead_rules);
1.4 momjian 881: }
1.1 scrappy 882:
1.22 momjian 883:
1.84 tgl 884: /*
885: * Modify the given query by adding 'AND NOT rule_qual' to its qualification.
886: * This is used to generate suitable "else clauses" for conditional INSTEAD
887: * rules.
888: *
1.90 momjian 889: * The rule_qual may contain references to OLD or NEW. OLD references are
1.84 tgl 890: * replaced by references to the specified rt_index (the relation that the
891: * rule applies to). NEW references are only possible for INSERT and UPDATE
892: * queries on the relation itself, and so they should be replaced by copies
893: * of the related entries in the query's own targetlist.
894: */
1.5 momjian 895: static Query *
1.6 momjian 896: CopyAndAddQual(Query *parsetree,
897: Node *rule_qual,
1.4 momjian 898: int rt_index,
899: CmdType event)
900: {
1.5 momjian 901: Query *new_tree = (Query *) copyObject(parsetree);
1.84 tgl 902: Node *new_qual = (Node *) copyObject(rule_qual);
1.4 momjian 903:
1.84 tgl 904: /* Fix references to OLD */
905: ChangeVarNodes(new_qual, PRS2_OLD_VARNO, rt_index, 0);
906: /* Fix references to NEW */
907: if (event == CMD_INSERT || event == CMD_UPDATE)
908: new_qual = ResolveNew(new_qual,
909: PRS2_NEW_VARNO,
910: 0,
911: parsetree->targetList,
912: event,
913: rt_index);
914: /* And attach the fixed qual */
1.4 momjian 915: AddNotQual(new_tree, new_qual);
916:
917: return new_tree;
1.1 scrappy 918: }
919:
920:
1.22 momjian 921:
1.1 scrappy 922: /*
1.4 momjian 923: * fireRules -
1.18 scrappy 924: * Iterate through rule locks applying rules.
925: * All rules create their own parsetrees. Instead rules
926: * with rule qualification save the original parsetree
927: * and add their negated qualification to it. Real instead
928: * rules finally throw away the original parsetree.
1.21 momjian 929: *
1.18 scrappy 930: * remember: reality is for dead birds -- glass
1.1 scrappy 931: *
932: */
1.5 momjian 933: static List *
1.6 momjian 934: fireRules(Query *parsetree,
1.4 momjian 935: int rt_index,
936: CmdType event,
1.6 momjian 937: bool *instead_flag,
938: List *locks,
939: List **qual_products)
1.4 momjian 940: {
1.5 momjian 941: List *results = NIL;
942: List *i;
1.4 momjian 943:
944: /* choose rule to fire from list of rules */
945: if (locks == NIL)
1.22 momjian 946: return NIL;
1.4 momjian 947:
1.18 scrappy 948: locks = orderRules(locks); /* real instead rules last */
1.81 tgl 949:
1.4 momjian 950: foreach(i, locks)
951: {
1.5 momjian 952: RewriteRule *rule_lock = (RewriteRule *) lfirst(i);
1.80 tgl 953: Node *event_qual;
1.5 momjian 954: List *actions;
955: List *r;
1.4 momjian 956:
957: /* multiple rule action time */
958: *instead_flag = rule_lock->isInstead;
959: event_qual = rule_lock->qual;
960: actions = rule_lock->actions;
1.81 tgl 961:
1.21 momjian 962: if (event_qual != NULL && *instead_flag)
963: {
964: Query *qual_product;
1.18 scrappy 965:
1.91 momjian 966: /*
967: * If there are instead rules with qualifications, the
968: * original query is still performed. But all the negated rule
969: * qualifications of the instead rules are added so it does
970: * its actions only in cases where the rule quals of all
971: * instead rules are false. Think of it as the default action
972: * in a case. We save this in *qual_products so
973: * deepRewriteQuery() can add it to the query list after we
974: * mangled it up enough.
1.18 scrappy 975: */
1.21 momjian 976: if (*qual_products == NIL)
1.18 scrappy 977: qual_product = parsetree;
1.21 momjian 978: else
1.81 tgl 979: qual_product = (Query *) lfirst(*qual_products);
1.21 momjian 980:
981: qual_product = CopyAndAddQual(qual_product,
982: event_qual,
983: rt_index,
984: event);
1.18 scrappy 985:
1.81 tgl 986: *qual_products = makeList1(qual_product);
1.18 scrappy 987: }
988:
1.4 momjian 989: foreach(r, actions)
990: {
1.5 momjian 991: Query *rule_action = lfirst(r);
1.4 momjian 992:
1.18 scrappy 993: if (rule_action->commandType == CMD_NOTHING)
994: continue;
1.25 momjian 995:
1.95 tgl 996: rule_action = rewriteRuleAction(parsetree, rule_action,
997: event_qual, rt_index, event);
1.4 momjian 998:
1.95 tgl 999: results = lappend(results, rule_action);
1.4 momjian 1000: }
1.18 scrappy 1001:
1.91 momjian 1002: /*
1003: * If this was an unqualified instead rule, throw away an
1004: * eventually saved 'default' parsetree
1.18 scrappy 1005: */
1.21 momjian 1006: if (event_qual == NULL && *instead_flag)
1.18 scrappy 1007: *qual_products = NIL;
1.4 momjian 1008: }
1009: return results;
1010: }
1011:
1.18 scrappy 1012:
1013:
1.5 momjian 1014: static List *
1.6 momjian 1015: RewriteQuery(Query *parsetree, bool *instead_flag, List **qual_products)
1.4 momjian 1016: {
1.5 momjian 1017: CmdType event;
1.45 momjian 1018: List *product_queries = NIL;
1.81 tgl 1019: int result_relation;
1.45 momjian 1020: RangeTblEntry *rt_entry;
1.81 tgl 1021: Relation rt_entry_relation;
1022: RuleLock *rt_entry_locks;
1.1 scrappy 1023:
1.4 momjian 1024: Assert(parsetree != NULL);
1.1 scrappy 1025:
1.4 momjian 1026: event = parsetree->commandType;
1.1 scrappy 1027:
1.22 momjian 1028: /*
1.45 momjian 1029: * SELECT rules are handled later when we have all the queries that
1030: * should get executed
1.22 momjian 1031: */
1032: if (event == CMD_SELECT)
1033: return NIL;
1034:
1035: /*
1036: * Utilities aren't rewritten at all - why is this here?
1037: */
1.4 momjian 1038: if (event == CMD_UTILITY)
1039: return NIL;
1.1 scrappy 1040:
1041: /*
1.57 tgl 1042: * the statement is an update, insert or delete - fire rules on it.
1.1 scrappy 1043: */
1.4 momjian 1044: result_relation = parsetree->resultRelation;
1.83 tgl 1045: Assert(result_relation != 0);
1.22 momjian 1046: rt_entry = rt_fetch(result_relation, parsetree->rtable);
1.99 tgl 1047: Assert(rt_entry->rtekind == RTE_RELATION);
1.83 tgl 1048:
1049: /*
1.90 momjian 1050: * This may well be the first access to the result relation during the
1051: * current statement (it will be, if this Query was extracted from a
1052: * rule or somehow got here other than via the parser). Therefore,
1053: * grab the appropriate lock type for a result relation, and do not
1054: * release it until end of transaction. This protects the rewriter
1055: * and planner against schema changes mid-query.
1.83 tgl 1056: */
1.100 tgl 1057: rt_entry_relation = heap_open(rt_entry->relid, RowExclusiveLock);
1.101 tgl 1058:
1059: /*
1060: * If it's an INSERT or UPDATE, rewrite the targetlist into standard
1061: * form. This will be needed by the planner anyway, and doing it now
1062: * ensures that any references to NEW.field will behave sanely.
1063: */
1064: if (event == CMD_INSERT || event == CMD_UPDATE)
1065: rewriteTargetList(parsetree, rt_entry_relation);
1.92 tgl 1066:
1067: /*
1068: * Collect and apply the appropriate rules.
1069: */
1.22 momjian 1070: rt_entry_locks = rt_entry_relation->rd_rules;
1071:
1072: if (rt_entry_locks != NULL)
1073: {
1.77 tgl 1074: List *locks = matchLocks(event, rt_entry_locks,
1075: result_relation, parsetree);
1.22 momjian 1076:
1.34 momjian 1077: product_queries = fireRules(parsetree,
1.45 momjian 1078: result_relation,
1079: event,
1080: instead_flag,
1081: locks,
1082: qual_products);
1.1 scrappy 1083: }
1084:
1.90 momjian 1085: heap_close(rt_entry_relation, NoLock); /* keep lock! */
1.77 tgl 1086:
1.22 momjian 1087: return product_queries;
1088: }
1.10 momjian 1089:
1.1 scrappy 1090:
1091: /*
1092: * to avoid infinite recursion, we restrict the number of times a query
1.77 tgl 1093: * can be rewritten. Detecting cycles is left for the reader as an exercise.
1.1 scrappy 1094: */
1095: #ifndef REWRITE_INVOKE_MAX
1.4 momjian 1096: #define REWRITE_INVOKE_MAX 10
1.1 scrappy 1097: #endif
1098:
1.5 momjian 1099: static int numQueryRewriteInvoked = 0;
1.1 scrappy 1100:
1101: /*
1102: * deepRewriteQuery -
1.4 momjian 1103: * rewrites the query and apply the rules again on the queries rewritten
1.1 scrappy 1104: */
1.5 momjian 1105: static List *
1.6 momjian 1106: deepRewriteQuery(Query *parsetree)
1.1 scrappy 1107: {
1.5 momjian 1108: List *n;
1109: List *rewritten = NIL;
1.81 tgl 1110: List *result;
1.5 momjian 1111: bool instead;
1112: List *qual_products = NIL;
1.4 momjian 1113:
1114: if (++numQueryRewriteInvoked > REWRITE_INVOKE_MAX)
1115: {
1.9 momjian 1116: elog(ERROR, "query rewritten %d times, may contain cycles",
1.4 momjian 1117: numQueryRewriteInvoked - 1);
1118: }
1.1 scrappy 1119:
1.97 tgl 1120: instead = false;
1.4 momjian 1121: result = RewriteQuery(parsetree, &instead, &qual_products);
1122:
1123: foreach(n, result)
1124: {
1.5 momjian 1125: Query *pt = lfirst(n);
1.81 tgl 1126: List *newstuff;
1.4 momjian 1127:
1128: newstuff = deepRewriteQuery(pt);
1129: if (newstuff != NIL)
1130: rewritten = nconc(rewritten, newstuff);
1131: }
1.18 scrappy 1132:
1.91 momjian 1133: /*
1.98 momjian 1134: * For INSERTs, the original query is done first; for UPDATE/DELETE,
1135: * it is done last. This is needed because update and delete rule
1136: * actions might not do anything if they are invoked after the update
1137: * or delete is performed. The command counter increment between the
1138: * query execution makes the deleted (and maybe the updated) tuples
1139: * disappear so the scans for them in the rule actions cannot find
1140: * them.
1.18 scrappy 1141: */
1.97 tgl 1142: if (parsetree->commandType == CMD_INSERT)
1143: {
1144: /*
1145: * qual_products are the original query with the negated rule
1146: * qualification of an INSTEAD rule
1147: */
1148: if (qual_products != NIL)
1149: rewritten = nconc(qual_products, rewritten);
1.98 momjian 1150:
1.97 tgl 1151: /*
1152: * Add the unmodified original query, if no INSTEAD rule was seen.
1153: */
1154: if (!instead)
1.96 wieck 1155: rewritten = lcons(parsetree, rewritten);
1.97 tgl 1156: }
1157: else
1158: {
1159: /*
1160: * qual_products are the original query with the negated rule
1161: * qualification of an INSTEAD rule
1162: */
1163: if (qual_products != NIL)
1164: rewritten = nconc(rewritten, qual_products);
1.98 momjian 1165:
1.97 tgl 1166: /*
1167: * Add the unmodified original query, if no INSTEAD rule was seen.
1168: */
1169: if (!instead)
1.96 wieck 1170: rewritten = lappend(rewritten, parsetree);
1.97 tgl 1171: }
1.4 momjian 1172:
1173: return rewritten;
1.12 scrappy 1174: }
1.22 momjian 1175:
1176:
1177: /*
1.82 tgl 1178: * QueryRewriteOne -
1.22 momjian 1179: * rewrite one query
1180: */
1181: static List *
1182: QueryRewriteOne(Query *parsetree)
1183: {
1184: numQueryRewriteInvoked = 0;
1185:
1186: /*
1187: * take a deep breath and apply all the rewrite rules - ay
1188: */
1189: return deepRewriteQuery(parsetree);
1190: }
1191:
1192:
1193: /*
1.82 tgl 1194: * QueryRewrite -
1195: * Primary entry point to the query rewriter.
1196: * Rewrite one query via query rewrite system, possibly returning 0
1197: * or many queries.
1198: *
1199: * NOTE: The code in QueryRewrite was formerly in pg_parse_and_plan(), and was
1200: * moved here so that it would be invoked during EXPLAIN.
1.22 momjian 1201: */
1.82 tgl 1202: List *
1203: QueryRewrite(Query *parsetree)
1.22 momjian 1204: {
1.45 momjian 1205: List *querylist;
1206: List *results = NIL;
1207: List *l;
1.22 momjian 1208:
1209: /*
1210: * Step 1
1211: *
1212: * Apply all non-SELECT rules possibly getting 0 or many queries
1213: */
1214: querylist = QueryRewriteOne(parsetree);
1215:
1216: /*
1.62 tgl 1217: * Step 2
1.22 momjian 1218: *
1219: * Apply all the RIR rules on each query
1220: */
1.45 momjian 1221: foreach(l, querylist)
1222: {
1.90 momjian 1223: Query *query = (Query *) lfirst(l);
1.45 momjian 1224:
1.82 tgl 1225: query = fireRIRrules(query);
1.71 momjian 1226:
1.45 momjian 1227: /*
1.82 tgl 1228: * If the query target was rewritten as a view, complain.
1.45 momjian 1229: */
1.82 tgl 1230: if (query->resultRelation)
1.45 momjian 1231: {
1.82 tgl 1232: RangeTblEntry *rte = rt_fetch(query->resultRelation,
1233: query->rtable);
1234:
1.99 tgl 1235: if (rte->rtekind == RTE_SUBQUERY)
1.82 tgl 1236: {
1237: switch (query->commandType)
1238: {
1239: case CMD_INSERT:
1.107 ! tgl 1240: elog(ERROR, "Cannot insert into a view"
! 1241: "\n\tYou need an unconditional ON INSERT DO INSTEAD rule");
1.82 tgl 1242: break;
1243: case CMD_UPDATE:
1.107 ! tgl 1244: elog(ERROR, "Cannot update a view"
! 1245: "\n\tYou need an unconditional ON UPDATE DO INSTEAD rule");
1.82 tgl 1246: break;
1247: case CMD_DELETE:
1.107 ! tgl 1248: elog(ERROR, "Cannot delete from a view"
! 1249: "\n\tYou need an unconditional ON DELETE DO INSTEAD rule");
1.82 tgl 1250: break;
1251: default:
1252: elog(ERROR, "QueryRewrite: unexpected commandType %d",
1253: (int) query->commandType);
1254: break;
1255: }
1.45 momjian 1256: }
1257: }
1258:
1.82 tgl 1259: results = lappend(results, query);
1.45 momjian 1260: }
1261:
1.82 tgl 1262: return results;
1.22 momjian 1263: }
PostgreSQL CVSweb <webmaster@postgresql.org>