noupdate -
trigger to prevent updates on single columns
+plpgsql -
+ Postgres procedural language
+ by Jan Wieck <jwieck@debis.com>
+
pginterface -
A crude C/4GL
by Bruce Momjian <root@candle.pha.pa.us>
--- /dev/null
+ PL/pgSQL
+ A procedural language for the PostgreSQL RDBMS
+
+ Jan Wieck <jwieck@debis.com>
+
+
+
+ Preface
+
+ PL/pgSQL is a procedural language based on SQL designed for
+ the PostgreSQL database system.
+
+ The extensibility features of PostgreSQL are mostly based on
+ the ability to define functions for various operations.
+ Functions could have been written in PostgreSQL's SQL dialect
+ or in the C programming language. Functions written in C are
+ compiled into a shared object and loaded by the database
+ backend process on demand. Also the trigger features of
+ PostgreSQL are based on functions but required the use of the
+ C language.
+
+ Since version 6.3 PostgreSQL supports the definition of
+ procedural languages. In the case of a function or trigger
+ procedure defined in a procedural language, the database has
+ no builtin knowlege how to interpret the functions source
+ text. Instead, the function and trigger calls are passed into
+ a handler that knows the details of the language. The
+ handler itself is a function compiled into a shared object
+ and loaded on demand.
+
+
+ Overview
+
+ The PL/pgSQL language is case insensitive. All keywords and
+ identifiers can be used in upper-/lowercase mixed.
+
+ PL/pgSQL is a block oriented language. A block is defined as
+
+ [<<label>>]
+ [DECLARE
+ -- declarations]
+ BEGIN
+ -- statements
+ END;
+
+ There can be any number of subblocks in the statements
+ section of a block. Subblocks can be used to hide variables
+ from outside a block of statements (see Scope and visability
+ below). The variables declared in the declarations section
+ preceding a block are initialized to their default values
+ every time the block is entered, not only once per function
+ call.
+
+ It is important not to misunderstand the meaning of BEGIN/END
+ for grouping statements in PL/pgSQL and the database commands
+ for transaction control. Functions or trigger procedures
+ cannot start or commit transactions and PostgreSQL
+ transactions cannot have subtransactions.
+
+
+ Comments
+
+ There are two types of comments in PL/pgSQL. A double dash
+ '--' starts a comment that extends to the end of the line. A
+ '/*' starts a block comment that extends to the next '*/'.
+ Block comments cannot be nested, but double dash comments can
+ be enclosed into a block comment and double dashes can hide
+ '/*' and '*/'.
+
+
+ Declarations
+
+ All variables, rows and records used in a block or it's
+ subblocks must be declared in the declarations section of the
+ block except for the loop variable of a FOR loop iterating
+ over a range of integer values. The parameters given to the
+ function are automatically declared with the usual
+ identifiers $n. The declarations have the following syntax:
+
+ <name> [CONSTANT] <type> [NOT NULL]
+ [DEFAULT | := <value>];
+
+ Declares a variable of the specified type. If the
+ variable is declared as CONSTANT, the value cannot be
+ changed. If NOT NULL is specified, an assignment of a
+ NULL value results in a runtime error. Since the
+ default value of a variable is the SQL NULL value,
+ all variables declared as NOT NULL must also have a
+ default value.
+
+ The default value is evaluated at the actual function
+ call. So assigning 'now' to an abstime variable
+ causes the variable to have the time of the actual
+ function call, not when the function was compiled
+ (during it's first call since the lifetime of the
+ database connection).
+
+ <name> <class>%ROWTYPE;
+
+ Declares a row with the structure of the given class.
+ Class must be an existing table- or viewname of the
+ database. The fields of the row are accessed in the
+ dot notation. Parameters to a procedure could be
+ tuple types. In that case the corresponding
+ identifier $n will be a rowtype. Only the user
+ attributes of a tuple are accessible in the row.
+ There must be no whitespaces between the classname,
+ the percent and the ROWTYPE keyword.
+
+ The fields of the rowtype inherit the tables
+ fieldsizes for char() etc. data types (atttypmod
+ from pg_attribute).
+
+ <name> RECORD;
+
+ Records are similar to rowtypes, but they have no
+ predefined structure They are used in selections and
+ FOR loops to hold one actual database tuple from a
+ select operation. One and the same record can be used
+ in different selections. Accessing a record or an
+ attempt to assign a value to a record field when
+ there's no actual tuple in it results in a runtime
+ error.
+
+ The new and old tuples in triggers are given to the
+ trigger procedure as records. This is necessary,
+ because under PostgreSQL one and the same trigger
+ procedure can handle trigger events for different
+ tables.
+
+ <name> ALIAS FOR $n;
+
+ For better readability of the code it's possible to
+ define an alias for a positional parameter to the
+ function.
+
+ RENAME <oldname> TO <newname>;
+
+ Change the name of a variable, record or rowtype.
+ This is useful if new or old should be referenced by
+ another name inside a trigger procedure.
+
+ Datatypes
+
+ The type of a variable can be any of the existing data types
+ of the database. <type> above is defined as:
+
+ postgesql-basetype
+ or variable%TYPE
+ or rowtype.field%TYPE
+ or class.field%TYPE
+
+ As for the rowtype declaration, there must be no whitespaces
+ between the classname, the percent and the TYPE keyword.
+
+ Expressions
+
+ All expressions used in PL/pgSQL statements are processed
+ using the backends executor. Since even a constant looking
+ expression can have a totally different meaning for a
+ particular data type (as 'now' for abstime), it is impossible
+ for the PL/pgSQL parser to identify real constant values
+ other than the NULL keyword. The expressions are evaluated by
+ internally executing a query
+
+ SELECT <expr>
+
+ over the SPI manager. In the expression, occurences of
+ variable identifiers are substituted by parameters and the
+ actual values from the variables are passed to the executor
+ as query parameters. All the expressions used in a PL/pgSQL
+ function are only prepared and saved once.
+
+ If record fields are used in expressions or database
+ statements, the data types of the fields should not change
+ between calls of one and the same expression. Keep this in
+ mind when writing trigger procedures that handle events for
+ more than one table.
+
+ Statements
+
+ Anything not understood by the parser as specified below will
+ be put into a query and sent down to the database engine to
+ execute. The resulting query should not return any data
+ (insert, update, delete queries and all utility statements).
+
+ Assignment
+
+ An assignment of a value to a variable or rowtype field
+ is written as:
+
+ <identifier> := <expr>;
+
+ If the expressions result data type doesn't match the
+ variables data type, or the variables atttypmod value is
+ known (as for char(20)), the result value will be
+ implicitly casted by the PL/pgSQL executor using the
+ result types output- and the variables type input-
+ functions. Note that this could potentially result in
+ runtime errors generated by the types input functions.
+
+ An assignment of a complete selection into a record or
+ rowtype can be done as:
+
+ SELECT expressions INTO <target> FROM fromlist;
+
+ Target can be a record or rowtype variable, or a comma
+ separated list of variables and record/row fields.
+
+ If a rowtype or a variable list is used as target, the
+ selected values must exactly match the structure of the
+ target(s) or a runtime error occurs. The fromlist can be
+ followed by any valid qualification, grouping, sorting
+ etc.
+
+ There is a special condition [NOT] FOUND that can be used
+ immediately after a SELECT INTO to check if the data has
+ been found.
+
+ SELECT * INTO myrec FROM EMP WHERE empname = myname;
+ IF NOT FOUND THEN
+ RAISE EXCEPTION 'employee % not found', myname;
+ END IF;
+
+ If the selection returns multiple rows, only the first is
+ moved into the target fields. All others are discarded.
+
+
+ Calling another function
+
+ If a function should be called, this is normally done by
+ a SELECT query. But there are cases where someone isn't
+ interested in the functions result.
+
+ PERFORM querystring;
+
+ executes a 'SELECT querystring' over the SPI manager and
+ discards the result.
+
+
+ Returning from the function
+
+ RETURN <expr>;
+
+ The function terminates and the value of <expr> will be
+ returned to the upper executor. The return value of a
+ function cannot be undefined. If control reaches the end
+ of the toplevel block of the function without hitting a
+ RETURN statement, a runtime error will occur.
+
+
+ Aborting and messages
+
+ As indicated above there is an RAISE statement that can
+ throw messages into the PostgreSQL elog mechanism.
+
+ RAISE level 'format' [, identifier [...]];
+
+ Inside the format, % can be used as a placeholder for the
+ following, comma separated identifiers. The identifiers
+ must specify an existing variable or row/record field.
+
+
+ Conditionals
+
+ IF <expr> THEN
+ -- statements
+ [ELSE
+ -- statements]
+ END IF;
+
+ The expression <expr> must return a value that at least
+ can be casted into a boolean.
+
+
+ Loops
+
+ There are multiple types of loops.
+
+ [<<label>>]
+ LOOP
+ -- statements
+ END LOOP;
+
+ An unconditional loop that must be terminated explicitly
+ by an EXIT statement. The optional label can be used by
+ EXIT statements of nested loops to specify which level of
+ nesting should be terminated.
+
+ [<<label>>]
+ WHILE <expr> LOOP
+ -- statements
+ END LOOP;
+
+ A conditional loop that is executed as long as the
+ evaluation of <expr> returns true.
+
+ [<<label>>]
+ FOR <name> IN [REVERSE] <expr>..<expr> LOOP
+ -- statements
+ END LOOP.
+
+ A loop that iterates over a range of integer values. The
+ variable <name> is automatically created as type integer
+ and exists only inside the loop. The two expressions
+ giving the lower and upper bound of the range are
+ evaluated only when entering the loop. The iteration step
+ is 1.
+
+ FOR <recname|rowname> IN <select_clause> LOOP
+ -- statements
+ END LOOP;
+
+ The record or row is assigned all the rows resulting from
+ the select clause and the statements executed for each.
+ If the loop is terminated with an EXIT statement, the
+ last accessed row is still accessible in the record or
+ rowtype.
+
+ EXIT [label] [WHEN <expr>];
+
+ If no label given, the innermost loop is terminated and
+ the statement following END LOOP is executed next. If
+ label is given, it must be the label of the current or an
+ upper level of nested loops or blocks. Then the named
+ loop or block is terminated and control continues with
+ the statement after the loops/blocks corresponding END.
+
+ Trigger procedures
+
+ PL/pgSQL can also be used to define trigger procedures. They
+ are created using CREATE FUNCTION as a function with no
+ arguments and a return type of opaque.
+
+ There are some PostgreSQL specific details in functions used
+ as trigger procedures.
+
+ First they have some special variables created above the
+ toplevel statement block. These are:
+
+ new (record)
+ The new database tuple on INSERT/UPDATE operations at
+ ROW level.
+
+ old (record)
+ The old database tuple on UPDATE/DELETE operations at
+ ROW level.
+
+ tg_name (type name)
+ The triggers name from pg_trigger.
+
+ tg_when (type text)
+ A string of either 'BEFORE' or 'AFTER' depending on
+ the triggers definition.
+
+ tg_level (type text)
+ A string of either 'ROW' or 'STATEMENT' depending on
+ the triggers definition.
+
+ tg_op (type text)
+ A string of 'INSERT', 'UPDATE' or 'DELETE' telling
+ for which operation the trigger is actually fired.
+
+ tg_relid (type oid)
+ The Oid of the relation for which the trigger is
+ actually fired.
+
+ tg_relname (type name)
+ The relations name for which the trigger is actually
+ fired.
+
+ tg_nargs (type integer)
+ The number of arguments given to the trigger
+ procedure in the CREATE TRIGGER statement.
+
+ tg_argv[] (types text)
+ The arguments from the CREATE TRIGGER statement. The
+ index counts from 0 and can be given as expression.
+ Invalid indices (< 0 or >= tg_nargs) result in a NULL
+ value.
+
+ Second, they must return either NULL, or a record/rowtype
+ containing exactly the structure of the table the trigger was
+ fired for. Triggers fired AFTER might allways return NULL
+ with no effect. Triggers fired BEFORE signal the trigger
+ manager to skip the operation for this actual row when
+ returning NULL. Otherwise, the returned record/rowtype
+ replaces the inserted/updated tuple in the operation. It is
+ possible to replace single values directly in new and return
+ that, or to build a complete new record/rowtype to return.
+
+ Exceptions
+
+ PostgreSQL doesn't have a very smart exception handling
+ model. Whenever the parser, planner/optimizer or executor
+ decide that a statement cannot be processed any longer, the
+ whole transaction gets aborted and the the system jumps back
+ into the mainloop using longjmp() to get the next query from
+ the client application.
+
+ It is possible to hook into the longjmp() mechanism to notice
+ that this happens. But currently it's impossible to tell what
+ really caused the abort (input/output conversion error,
+ floating point error, parse error) And it's possible that the
+ backend is in an inconsistent state at this point so
+ returning to the upper executor or issuing more commands
+ might corrupt the whole database.
+
+ Thus, the only thing PL/pgSQL currently does when it
+ encounters an abort during execution of a function or trigger
+ procedure is to write some additional DEBUG log messages
+ telling in which function and where (line number and type of
+ statement) this happened.
+
+ This might change in the future.
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
--- /dev/null
+Installation of PL/pgSQL
+
+
+1) Type 'make' to build the shared plpgsql object.
+
+2) Type 'make install' to install the shared object in
+ the PostgreSQL library directory.
+
+3) Declare the PL/pgSQL procedural language in your
+ database by
+
+ psql dbname <mklang.sql
+
+ If the PostgreSQL library directory is different from
+ /usr/local/pgsql/lib you must edit mklang.sql prior.
+
+ If you declare the language in the template1 database,
+ any subsequently created database will have PL/pgSQL
+ support installed automatically.
+
+
+
--- /dev/null
+%{
+/**********************************************************************
+ * gram.y - Parser for the PL/pgSQL
+ * procedural language
+ *
+ * IDENTIFICATION
+ * $Header: /cvsroot/pgsql/contrib/plpgsql/src/Attic/gram.y,v 1.1 1998/08/22 12:38:30 momjian Exp $
+ *
+ * This software is copyrighted by Jan Wieck - Hamburg.
+ *
+ * The author hereby grants permission to use, copy, modify,
+ * distribute, and license this software and its documentation
+ * for any purpose, provided that existing copyright notices are
+ * retained in all copies and that this notice is included
+ * verbatim in any distributions. No written agreement, license,
+ * or royalty fee is required for any of the authorized uses.
+ * Modifications to this software may be copyrighted by their
+ * author and need not follow the licensing terms described
+ * here, provided that the new terms are clearly indicated on
+ * the first page of each file where they apply.
+ *
+ * IN NO EVENT SHALL THE AUTHOR OR DISTRIBUTORS BE LIABLE TO ANY
+ * PARTY FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL, OR
+ * CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OF THIS
+ * SOFTWARE, ITS DOCUMENTATION, OR ANY DERIVATIVES THEREOF, EVEN
+ * IF THE AUTHOR HAVE BEEN ADVISED OF THE POSSIBILITY OF SUCH
+ * DAMAGE.
+ *
+ * THE AUTHOR AND DISTRIBUTORS SPECIFICALLY DISCLAIM ANY
+ * WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
+ * WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
+ * PURPOSE, AND NON-INFRINGEMENT. THIS SOFTWARE IS PROVIDED ON
+ * AN "AS IS" BASIS, AND THE AUTHOR AND DISTRIBUTORS HAVE NO
+ * OBLIGATION TO PROVIDE MAINTENANCE, SUPPORT, UPDATES,
+ * ENHANCEMENTS, OR MODIFICATIONS.
+ *
+ **********************************************************************/
+
+#include "stdio.h"
+#include "string.h"
+#include "plpgsql.h"
+
+extern int yylineno;
+extern char yytext[];
+
+static PLpgSQL_expr *read_sqlstmt(int until, char *s, char *sqlstart);
+static PLpgSQL_stmt *make_select_stmt(void);
+static PLpgSQL_expr *make_tupret_expr(PLpgSQL_row *row);
+
+%}
+
+%union {
+ int32 ival;
+ char *str;
+ struct {
+ char *name;
+ int lineno;
+ } varname;
+ struct {
+ int nalloc;
+ int nused;
+ int *dtnums;
+ } dtlist;
+ struct {
+ int reverse;
+ PLpgSQL_expr *expr;
+ } forilow;
+ struct {
+ char *label;
+ int n_initvars;
+ int *initvarnos;
+ } declhdr;
+ PLpgSQL_type *dtype;
+ PLpgSQL_var *var;
+ PLpgSQL_row *row;
+ PLpgSQL_rec *rec;
+ PLpgSQL_recfield *recfield;
+ PLpgSQL_trigarg *trigarg;
+ PLpgSQL_expr *expr;
+ PLpgSQL_stmt *stmt;
+ PLpgSQL_stmts *stmts;
+ PLpgSQL_stmt_block *program;
+ PLpgSQL_nsitem *nsitem;
+}
+
+%type <declhdr> decl_sect
+%type <varname> decl_varname
+%type <str> decl_renname
+%type <ival> decl_const, decl_notnull, decl_atttypmod, decl_atttypmodval
+%type <expr> decl_defval
+%type <dtype> decl_datatype, decl_dtypename
+%type <row> decl_rowtype
+%type <nsitem> decl_aliasitem
+%type <str> decl_stmts, decl_stmt
+
+%type <expr> expr_until_semi, expr_until_then, expr_until_loop
+%type <expr> opt_exitcond
+
+%type <ival> assign_var
+%type <var> fori_var
+%type <varname> fori_varname
+%type <forilow> fori_lower
+%type <rec> fors_target
+
+%type <str> opt_lblname, opt_label
+%type <str> opt_exitlabel
+%type <str> execsql_start
+
+%type <stmts> proc_sect, proc_stmts, stmt_else, loop_body
+%type <stmt> proc_stmt, pl_block
+%type <stmt> stmt_assign, stmt_if, stmt_loop, stmt_while, stmt_exit
+%type <stmt> stmt_return, stmt_raise, stmt_execsql, stmt_fori
+%type <stmt> stmt_fors, stmt_select, stmt_perform
+
+%type <dtlist> raise_params
+%type <ival> raise_level, raise_param
+%type <str> raise_msg
+
+%type <ival> lno
+
+ /*
+ * Keyword tokens
+ */
+%token K_ALIAS
+%token K_ASSIGN
+%token K_BEGIN
+%token K_CONSTANT
+%token K_DEBUG
+%token K_DECLARE
+%token K_DEFAULT
+%token K_DOTDOT
+%token K_ELSE
+%token K_END
+%token K_EXCEPTION
+%token K_EXIT
+%token K_FOR
+%token K_FROM
+%token K_IF
+%token K_IN
+%token K_INTO
+%token K_LOOP
+%token K_NOT
+%token K_NOTICE
+%token K_NULL
+%token K_PERFORM
+%token K_RAISE
+%token K_RECORD
+%token K_RENAME
+%token K_RETURN
+%token K_REVERSE
+%token K_SELECT
+%token K_THEN
+%token K_TO
+%token K_TYPE
+%token K_WHEN
+%token K_WHILE
+
+ /*
+ * Other tokens
+ */
+%token T_FUNCTION
+%token T_TRIGGER
+%token T_CHAR
+%token T_BPCHAR
+%token T_VARCHAR
+%token T_LABEL
+%token T_STRING
+%token T_VARIABLE
+%token T_ROW
+%token T_ROWTYPE
+%token T_RECORD
+%token T_RECFIELD
+%token T_TGARGV
+%token T_DTYPE
+%token T_WORD
+%token T_NUMBER
+%token T_ERROR
+
+%token O_OPTION
+%token O_DUMP
+
+%%
+
+pl_function : T_FUNCTION comp_optsect pl_block
+ {
+ yylval.program = (PLpgSQL_stmt_block *)$3;
+ }
+ | T_TRIGGER comp_optsect pl_block
+ {
+ yylval.program = (PLpgSQL_stmt_block *)$3;
+ }
+ ;
+
+comp_optsect :
+ | comp_options
+ ;
+
+comp_options : comp_options comp_option
+ | comp_option
+ ;
+
+comp_option : O_OPTION O_DUMP
+ {
+ plpgsql_DumpExecTree = 1;
+ }
+ ;
+
+pl_block : decl_sect K_BEGIN lno proc_sect K_END ';'
+ {
+ PLpgSQL_stmt_block *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_block));
+ memset(new, 0, sizeof(PLpgSQL_stmt_block));
+
+ new->cmd_type = PLPGSQL_STMT_BLOCK;
+ new->lineno = $3;
+ new->label = $1.label;
+ new->n_initvars = $1.n_initvars;
+ new->initvarnos = $1.initvarnos;
+ new->body = $4;
+
+ plpgsql_ns_pop();
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+
+decl_sect : opt_label
+ {
+ plpgsql_ns_setlocal(false);
+ $$.label = $1;
+ $$.n_initvars = 0;
+ $$.initvarnos = NULL;
+ plpgsql_add_initdatums(NULL);
+ }
+ | opt_label decl_start
+ {
+ plpgsql_ns_setlocal(false);
+ $$.label = $1;
+ $$.n_initvars = 0;
+ $$.initvarnos = NULL;
+ plpgsql_add_initdatums(NULL);
+ }
+ | opt_label decl_start decl_stmts
+ {
+ plpgsql_ns_setlocal(false);
+ if ($3 != NULL) {
+ $$.label = $3;
+ } else {
+ $$.label = $1;
+ }
+ $$.n_initvars = plpgsql_add_initdatums(&($$.initvarnos));
+ }
+ ;
+
+decl_start : K_DECLARE
+ {
+ plpgsql_ns_setlocal(true);
+ }
+ ;
+
+decl_stmts : decl_stmts decl_stmt
+ {
+ $$ = $2;
+ }
+ | decl_stmt
+ {
+ $$ = $1;
+ }
+ ;
+
+decl_stmt : '<' '<' opt_lblname '>' '>'
+ {
+ $$ = $3;
+ }
+ | K_DECLARE
+ {
+ $$ = NULL;
+ }
+ | decl_statement
+ {
+ $$ = NULL;
+ }
+ ;
+
+decl_statement : decl_varname decl_const decl_datatype decl_notnull decl_defval
+ {
+ PLpgSQL_var *new;
+
+ new = malloc(sizeof(PLpgSQL_var));
+
+ new->dtype = PLPGSQL_DTYPE_VAR;
+ new->refname = $1.name;
+ new->lineno = $1.lineno;
+
+ new->datatype = $3;
+ new->isconst = $2;
+ new->notnull = $4;
+ new->default_val = $5;
+
+ plpgsql_adddatum((PLpgSQL_datum *)new);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, new->varno,
+ $1.name);
+ }
+ | decl_varname K_RECORD ';'
+ {
+ PLpgSQL_rec *new;
+
+ new = malloc(sizeof(PLpgSQL_var));
+
+ new->dtype = PLPGSQL_DTYPE_REC;
+ new->refname = $1.name;
+ new->lineno = $1.lineno;
+
+ plpgsql_adddatum((PLpgSQL_datum *)new);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_REC, new->recno,
+ $1.name);
+ }
+ | decl_varname decl_rowtype ';'
+ {
+ $2->dtype = PLPGSQL_DTYPE_ROW;
+ $2->refname = $1.name;
+ $2->lineno = $1.lineno;
+
+ plpgsql_adddatum((PLpgSQL_datum *)$2);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_ROW, $2->rowno,
+ $1.name);
+ }
+ | decl_varname K_ALIAS K_FOR decl_aliasitem ';'
+ {
+ plpgsql_ns_additem($4->itemtype,
+ $4->itemno, $1.name);
+ }
+ | K_RENAME decl_renname K_TO decl_renname ';'
+ {
+ plpgsql_ns_rename($2, $4);
+ }
+ ;
+
+decl_aliasitem : T_WORD
+ {
+ PLpgSQL_nsitem *nsi;
+ char *name;
+
+ plpgsql_ns_setlocal(false);
+ name = plpgsql_tolower(pstrdup(yytext));
+ if (name[0] != '$') {
+ elog(ERROR, "can only alias positional parameters");
+ }
+ nsi = plpgsql_ns_lookup(name, NULL);
+ if (nsi == NULL) {
+ elog(ERROR, "function has no parameter %s", name);
+ }
+
+ plpgsql_ns_setlocal(true);
+
+ $$ = nsi;
+ }
+ ;
+
+decl_rowtype : T_ROW
+ {
+ $$ = yylval.row;
+ }
+ ;
+
+decl_varname : T_WORD
+ {
+ $$.name = strdup(yytext);
+ $$.lineno = yylineno;
+ }
+ ;
+
+decl_renname : T_WORD
+ {
+ $$ = plpgsql_tolower(pstrdup(yytext));
+ }
+ ;
+
+decl_const :
+ { $$ = 0; }
+ | K_CONSTANT
+ { $$ = 1; }
+ ;
+
+decl_datatype : decl_dtypename
+ {
+ $$ = $1;
+ }
+ ;
+
+decl_dtypename : T_DTYPE
+ {
+ $$ = yylval.dtype;
+ }
+ | T_CHAR decl_atttypmod
+ {
+ if ($2 < 0) {
+ plpgsql_parse_word("char");
+ $$ = yylval.dtype;
+ } else {
+ plpgsql_parse_word("bpchar");
+ $$ = yylval.dtype;
+ $$->atttypmod = $2;
+ }
+ }
+ | T_VARCHAR decl_atttypmod
+ {
+ plpgsql_parse_word("varchar");
+ $$ = yylval.dtype;
+ $$->atttypmod = $2;
+ }
+ | T_BPCHAR '(' decl_atttypmodval ')'
+ {
+ plpgsql_parse_word("bpchar");
+ $$ = yylval.dtype;
+ $$->atttypmod = $3;
+ }
+ ;
+
+decl_atttypmod :
+ {
+ $$ = -1;
+ }
+ | '(' decl_atttypmodval ')'
+ {
+ $$ = $2;
+ }
+ ;
+
+decl_atttypmodval : T_NUMBER
+ {
+ $$ = int2in(yytext) + VARHDRSZ;
+ }
+ ;
+
+decl_notnull :
+ { $$ = 0; }
+ | K_NOT K_NULL
+ { $$ = 1; }
+ ;
+
+decl_defval : ';'
+ { $$ = NULL; }
+ | decl_defkey
+ {
+ int tok;
+ int lno;
+ PLpgSQL_dstring ds;
+ PLpgSQL_expr *expr;
+
+ lno = yylineno;
+ expr = malloc(sizeof(PLpgSQL_expr));
+ plpgsql_dstring_init(&ds);
+ plpgsql_dstring_append(&ds, "SELECT ");
+
+ expr->dtype = PLPGSQL_DTYPE_EXPR;
+ expr->plan = NULL;
+ expr->nparams = 0;
+
+ tok = yylex();
+ switch (tok) {
+ case 0:
+ plpgsql_error_lineno = lno;
+ plpgsql_comperrinfo();
+ elog(ERROR, "unexpected end of file");
+ case K_NULL:
+ if (yylex() != ';') {
+ plpgsql_error_lineno = lno;
+ plpgsql_comperrinfo();
+ elog(ERROR, "expectec ; after NULL");
+ }
+ free(expr);
+ plpgsql_dstring_free(&ds);
+
+ $$ = NULL;
+ break;
+
+ default:
+ plpgsql_dstring_append(&ds, yytext);
+ while ((tok = yylex()) != ';') {
+ if (tok == 0) {
+ plpgsql_error_lineno = lno;
+ plpgsql_comperrinfo();
+ elog(ERROR, "unterminated default value");
+ }
+ if (plpgsql_SpaceScanned) {
+ plpgsql_dstring_append(&ds, " ");
+ }
+ plpgsql_dstring_append(&ds, yytext);
+ }
+ expr->query = strdup(plpgsql_dstring_get(&ds));
+ plpgsql_dstring_free(&ds);
+
+ $$ = expr;
+ break;
+ }
+ }
+ ;
+
+decl_defkey : K_ASSIGN
+ | K_DEFAULT
+
+proc_sect :
+ {
+ PLpgSQL_stmts *new;
+
+ new = malloc(sizeof(PLpgSQL_stmts));
+ memset(new, 0, sizeof(PLpgSQL_stmts));
+ $$ = new;
+ }
+ | proc_stmts
+ {
+ $$ = $1;
+ }
+ ;
+
+proc_stmts : proc_stmts proc_stmt
+ {
+ if ($1->stmts_used == $1->stmts_alloc) {
+ $1->stmts_alloc *= 2;
+ $1->stmts = realloc($1->stmts, sizeof(PLpgSQL_stmt *) * $1->stmts_alloc);
+ }
+ $1->stmts[$1->stmts_used++] = (struct PLpgSQL_stmt *)$2;
+
+ $$ = $1;
+ }
+ | proc_stmt
+ {
+ PLpgSQL_stmts *new;
+
+ new = malloc(sizeof(PLpgSQL_stmts));
+ memset(new, 0, sizeof(PLpgSQL_stmts));
+
+ new->stmts_alloc = 64;
+ new->stmts_used = 1;
+ new->stmts = malloc(sizeof(PLpgSQL_stmt *) * new->stmts_alloc);
+ new->stmts[0] = (struct PLpgSQL_stmt *)$1;
+
+ $$ = new;
+ }
+ ;
+
+proc_stmt : pl_block
+ { $$ = $1; }
+ | stmt_assign
+ { $$ = $1; }
+ | stmt_if
+ { $$ = $1; }
+ | stmt_loop
+ { $$ = $1; }
+ | stmt_while
+ { $$ = $1; }
+ | stmt_fori
+ { $$ = $1; }
+ | stmt_fors
+ { $$ = $1; }
+ | stmt_select
+ { $$ = $1; }
+ | stmt_exit
+ { $$ = $1; }
+ | stmt_return
+ { $$ = $1; }
+ | stmt_raise
+ { $$ = $1; }
+ | stmt_execsql
+ { $$ = $1; }
+ | stmt_perform
+ { $$ = $1; }
+ ;
+
+stmt_perform : K_PERFORM lno expr_until_semi
+ {
+ PLpgSQL_stmt_assign *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_assign));
+ memset(new, 0, sizeof(PLpgSQL_stmt_assign));
+
+ new->cmd_type = PLPGSQL_STMT_ASSIGN;
+ new->lineno = $2;
+ new->varno = -1;
+ new->expr = $3;
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+stmt_assign : assign_var lno K_ASSIGN expr_until_semi
+ {
+ PLpgSQL_stmt_assign *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_assign));
+ memset(new, 0, sizeof(PLpgSQL_stmt_assign));
+
+ new->cmd_type = PLPGSQL_STMT_ASSIGN;
+ new->lineno = $2;
+ new->varno = $1;
+ new->expr = $4;
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+assign_var : T_VARIABLE
+ {
+ if (yylval.var->isconst) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "%s is declared CONSTANT", yylval.var->refname);
+ }
+ $$ = yylval.var->varno;
+ }
+ | T_RECFIELD
+ {
+ $$ = yylval.recfield->rfno;
+ }
+ ;
+
+stmt_if : K_IF lno expr_until_then proc_sect stmt_else K_END K_IF ';'
+ {
+ PLpgSQL_stmt_if *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_if));
+ memset(new, 0, sizeof(PLpgSQL_stmt_if));
+
+ new->cmd_type = PLPGSQL_STMT_IF;
+ new->lineno = $2;
+ new->cond = $3;
+ new->true_body = $4;
+ new->false_body = $5;
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+stmt_else :
+ {
+ PLpgSQL_stmts *new;
+
+ new = malloc(sizeof(PLpgSQL_stmts));
+ memset(new, 0, sizeof(PLpgSQL_stmts));
+ $$ = new;
+ }
+ | K_ELSE proc_sect
+ { $$ = $2; }
+ ;
+
+stmt_loop : opt_label K_LOOP lno loop_body
+ {
+ PLpgSQL_stmt_loop *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_loop));
+ memset(new, 0, sizeof(PLpgSQL_stmt_loop));
+
+ new->cmd_type = PLPGSQL_STMT_LOOP;
+ new->lineno = $3;
+ new->label = $1;
+ new->body = $4;
+
+ plpgsql_ns_pop();
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+stmt_while : opt_label K_WHILE lno expr_until_loop loop_body
+ {
+ PLpgSQL_stmt_while *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_while));
+ memset(new, 0, sizeof(PLpgSQL_stmt_while));
+
+ new->cmd_type = PLPGSQL_STMT_WHILE;
+ new->lineno = $3;
+ new->label = $1;
+ new->cond = $4;
+ new->body = $5;
+
+ plpgsql_ns_pop();
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+stmt_fori : opt_label K_FOR lno fori_var K_IN fori_lower expr_until_loop loop_body
+ {
+ PLpgSQL_stmt_fori *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_fori));
+ memset(new, 0, sizeof(PLpgSQL_stmt_fori));
+
+ new->cmd_type = PLPGSQL_STMT_FORI;
+ new->lineno = $3;
+ new->label = $1;
+ new->var = $4;
+ new->reverse = $6.reverse;
+ new->lower = $6.expr;
+ new->upper = $7;
+ new->body = $8;
+
+ plpgsql_ns_pop();
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+fori_var : fori_varname
+ {
+ PLpgSQL_var *new;
+
+ new = malloc(sizeof(PLpgSQL_var));
+
+ new->dtype = PLPGSQL_DTYPE_VAR;
+ new->refname = $1.name;
+ new->lineno = $1.lineno;
+
+ plpgsql_parse_word("integer");
+
+ new->datatype = yylval.dtype;
+ new->isconst = false;
+ new->notnull = false;
+ new->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)new);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, new->varno,
+ $1.name);
+
+ plpgsql_add_initdatums(NULL);
+
+ $$ = new;
+ }
+ ;
+
+fori_varname : T_VARIABLE
+ {
+ $$.name = strdup(yytext);
+ $$.lineno = yylineno;
+ }
+ | T_WORD
+ {
+ $$.name = strdup(yytext);
+ $$.lineno = yylineno;
+ }
+ ;
+
+fori_lower :
+ {
+ int tok;
+ int lno;
+ PLpgSQL_dstring ds;
+ int nparams = 0;
+ int params[1024];
+ char buf[32];
+ PLpgSQL_expr *expr;
+ int firsttok = 1;
+
+ lno = yylineno;
+ plpgsql_dstring_init(&ds);
+ plpgsql_dstring_append(&ds, "SELECT ");
+
+ $$.reverse = 0;
+ while((tok = yylex()) != K_DOTDOT) {
+ if (firsttok) {
+ firsttok = 0;
+ if (tok == K_REVERSE) {
+ $$.reverse = 1;
+ continue;
+ }
+ }
+ if (tok == ';') break;
+ if (plpgsql_SpaceScanned) {
+ plpgsql_dstring_append(&ds, " ");
+ }
+ switch (tok) {
+ case T_VARIABLE:
+ params[nparams] = yylval.var->varno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_RECFIELD:
+ params[nparams] = yylval.recfield->rfno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_TGARGV:
+ params[nparams] = yylval.trigarg->dno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ default:
+ if (tok == 0) {
+ plpgsql_error_lineno = lno;
+ plpgsql_comperrinfo();
+ elog(ERROR, "missing .. to terminate lower bound of for loop");
+ }
+ plpgsql_dstring_append(&ds, yytext);
+ break;
+ }
+ }
+
+ expr = malloc(sizeof(PLpgSQL_expr) + sizeof(int) * nparams - 1);
+ expr->dtype = PLPGSQL_DTYPE_EXPR;
+ expr->query = strdup(plpgsql_dstring_get(&ds));
+ expr->plan = NULL;
+ expr->nparams = nparams;
+ while(nparams-- > 0) {
+ expr->params[nparams] = params[nparams];
+ }
+ plpgsql_dstring_free(&ds);
+ $$.expr = expr;
+ }
+
+stmt_fors : opt_label K_FOR lno fors_target K_IN K_SELECT expr_until_loop loop_body
+ {
+ PLpgSQL_stmt_fors *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_fors));
+ memset(new, 0, sizeof(PLpgSQL_stmt_fors));
+
+ new->cmd_type = PLPGSQL_STMT_FORS;
+ new->lineno = $3;
+ new->label = $1;
+ switch ($4->dtype) {
+ case PLPGSQL_DTYPE_REC:
+ new->rec = $4;
+ break;
+ case PLPGSQL_DTYPE_ROW:
+ new->row = (PLpgSQL_row *)$4;
+ break;
+ default:
+ plpgsql_comperrinfo();
+ elog(ERROR, "unknown dtype %d in stmt_fors", $4->dtype);
+ }
+ new->query = $7;
+ new->body = $8;
+
+ plpgsql_ns_pop();
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+
+fors_target : T_RECORD
+ {
+ $$ = yylval.rec;
+ }
+ | T_ROW
+ {
+ $$ = (PLpgSQL_rec *)(yylval.row);
+ }
+ ;
+
+stmt_select : K_SELECT lno
+ {
+ $$ = make_select_stmt();
+ $$->lineno = $2;
+ }
+ ;
+
+stmt_exit : K_EXIT lno opt_exitlabel opt_exitcond
+ {
+ PLpgSQL_stmt_exit *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_exit));
+ memset(new, 0, sizeof(PLpgSQL_stmt_exit));
+
+ new->cmd_type = PLPGSQL_STMT_EXIT;
+ new->lineno = $2;
+ new->label = $3;
+ new->cond = $4;
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+stmt_return : K_RETURN lno
+ {
+ PLpgSQL_stmt_return *new;
+ PLpgSQL_expr *expr = NULL;
+ int tok;
+
+ new = malloc(sizeof(PLpgSQL_stmt_return));
+ memset(new, 0, sizeof(PLpgSQL_stmt_return));
+
+ if (plpgsql_curr_compile->fn_retistuple) {
+ new->retistuple = true;
+ new->retrecno = -1;
+ switch (tok = yylex()) {
+ case K_NULL:
+ expr = NULL;
+ break;
+
+ case T_ROW:
+ expr = make_tupret_expr(yylval.row);
+ break;
+
+ case T_RECORD:
+ new->retrecno = yylval.rec->recno;
+ expr = NULL;
+ break;
+
+ default:
+ yyerror("return type mismatch in function returning table row");
+ break;
+ }
+ if (yylex() != ';') {
+ yyerror("expected ';'");
+ }
+ } else {
+ new->retistuple = false;
+ expr = plpgsql_read_expression(';', ";");
+ }
+
+ new->cmd_type = PLPGSQL_STMT_RETURN;
+ new->lineno = $2;
+ new->expr = expr;
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+stmt_raise : K_RAISE lno raise_level raise_msg raise_params ';'
+ {
+ PLpgSQL_stmt_raise *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_raise));
+
+ new->cmd_type = PLPGSQL_STMT_RAISE;
+ new->lineno = $2;
+ new->elog_level = $3;
+ new->message = $4;
+ new->nparams = $5.nused;
+ new->params = malloc(sizeof(int) * $5.nused);
+ memcpy(new->params, $5.dtnums, sizeof(int) * $5.nused);
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ | K_RAISE lno raise_level raise_msg ';'
+ {
+ PLpgSQL_stmt_raise *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_raise));
+
+ new->cmd_type = PLPGSQL_STMT_RAISE;
+ new->lineno = $2;
+ new->elog_level = $3;
+ new->message = $4;
+ new->nparams = 0;
+ new->params = NULL;
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+raise_msg : T_STRING
+ {
+ $$ = strdup(yytext);
+ }
+ ;
+
+raise_level : K_EXCEPTION
+ {
+ $$ = ERROR;
+ }
+ | K_NOTICE
+ {
+ $$ = NOTICE;
+ }
+ | K_DEBUG
+ {
+ $$ = DEBUG;
+ }
+ ;
+
+raise_params : raise_params raise_param
+ {
+ if ($1.nused == $1.nalloc) {
+ $1.nalloc *= 2;
+ $1.dtnums = repalloc($1.dtnums, sizeof(int) * $1.nalloc);
+ }
+ $1.dtnums[$1.nused++] = $2;
+
+ $$.nalloc = $1.nalloc;
+ $$.nused = $1.nused;
+ $$.dtnums = $1.dtnums;
+ }
+ | raise_param
+ {
+ $$.nalloc = 1;
+ $$.nused = 1;
+ $$.dtnums = palloc(sizeof(int) * $$.nalloc);
+ $$.dtnums[0] = $1;
+ }
+ ;
+
+raise_param : ',' T_VARIABLE
+ {
+ $$ = yylval.var->varno;
+ }
+ | ',' T_RECFIELD
+ {
+ $$ = yylval.recfield->rfno;
+ }
+ | ',' T_TGARGV
+ {
+ $$ = yylval.trigarg->dno;
+ }
+ ;
+
+loop_body : proc_sect K_END K_LOOP ';'
+ { $$ = $1; }
+ ;
+
+stmt_execsql : execsql_start lno
+ {
+ PLpgSQL_stmt_execsql *new;
+
+ new = malloc(sizeof(PLpgSQL_stmt_execsql));
+ new->cmd_type = PLPGSQL_STMT_EXECSQL;
+ new->lineno = $2;
+ new->sqlstmt = read_sqlstmt(';', ";", $1);
+
+ $$ = (PLpgSQL_stmt *)new;
+ }
+ ;
+
+execsql_start : T_WORD
+ { $$ = strdup(yytext); }
+ | T_ERROR
+ { $$ = strdup(yytext); }
+ ;
+
+expr_until_semi :
+ { $$ = plpgsql_read_expression(';', ";"); }
+ ;
+
+expr_until_then :
+ { $$ = plpgsql_read_expression(K_THEN, "THEN"); }
+ ;
+
+expr_until_loop :
+ { $$ = plpgsql_read_expression(K_LOOP, "LOOP"); }
+ ;
+
+opt_label :
+ {
+ plpgsql_ns_push(NULL);
+ $$ = NULL;
+ }
+ | '<' '<' opt_lblname '>' '>'
+ {
+ plpgsql_ns_push($3);
+ $$ = $3;
+ }
+ ;
+
+opt_exitlabel :
+ { $$ = NULL; }
+ | T_LABEL
+ { $$ = strdup(yytext); }
+ ;
+
+opt_exitcond : ';'
+ { $$ = NULL; }
+ | K_WHEN expr_until_semi
+ { $$ = $2; }
+ ;
+
+opt_lblname : T_WORD
+ { $$ = strdup(yytext); }
+ ;
+
+lno :
+ {
+ plpgsql_error_lineno = yylineno;
+ $$ = yylineno;
+ }
+ ;
+
+%%
+
+PLpgSQL_expr *
+plpgsql_read_expression (int until, char *s)
+{
+ return read_sqlstmt(until, s, "SELECT ");
+}
+
+
+static PLpgSQL_expr *
+read_sqlstmt (int until, char *s, char *sqlstart)
+{
+ int tok;
+ int lno;
+ PLpgSQL_dstring ds;
+ int nparams = 0;
+ int params[1024];
+ char buf[32];
+ PLpgSQL_expr *expr;
+
+ lno = yylineno;
+ plpgsql_dstring_init(&ds);
+ plpgsql_dstring_append(&ds, sqlstart);
+
+ while((tok = yylex()) != until) {
+ if (tok == ';') break;
+ if (plpgsql_SpaceScanned) {
+ plpgsql_dstring_append(&ds, " ");
+ }
+ switch (tok) {
+ case T_VARIABLE:
+ params[nparams] = yylval.var->varno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_RECFIELD:
+ params[nparams] = yylval.recfield->rfno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_TGARGV:
+ params[nparams] = yylval.trigarg->dno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ default:
+ if (tok == 0) {
+ plpgsql_error_lineno = lno;
+ plpgsql_comperrinfo();
+ elog(ERROR, "missing %s at end of SQL statement", s);
+ }
+ plpgsql_dstring_append(&ds, yytext);
+ break;
+ }
+ }
+
+ expr = malloc(sizeof(PLpgSQL_expr) + sizeof(int) * nparams - 1);
+ expr->dtype = PLPGSQL_DTYPE_EXPR;
+ expr->query = strdup(plpgsql_dstring_get(&ds));
+ expr->plan = NULL;
+ expr->nparams = nparams;
+ while(nparams-- > 0) {
+ expr->params[nparams] = params[nparams];
+ }
+ plpgsql_dstring_free(&ds);
+
+ return expr;
+}
+
+
+static PLpgSQL_stmt *
+make_select_stmt()
+{
+ int tok;
+ int lno;
+ PLpgSQL_dstring ds;
+ int nparams = 0;
+ int params[1024];
+ char buf[32];
+ PLpgSQL_expr *expr;
+ PLpgSQL_row *row = NULL;
+ PLpgSQL_rec *rec = NULL;
+ PLpgSQL_stmt_select *select;
+ int have_nexttok = 0;
+
+ lno = yylineno;
+ plpgsql_dstring_init(&ds);
+ plpgsql_dstring_append(&ds, "SELECT ");
+
+ while((tok = yylex()) != K_INTO) {
+ if (tok == ';') {
+ PLpgSQL_stmt_execsql *execsql;
+
+ expr = malloc(sizeof(PLpgSQL_expr) + sizeof(int) * nparams - 1);
+ expr->dtype = PLPGSQL_DTYPE_EXPR;
+ expr->query = strdup(plpgsql_dstring_get(&ds));
+ expr->plan = NULL;
+ expr->nparams = nparams;
+ while(nparams-- > 0) {
+ expr->params[nparams] = params[nparams];
+ }
+ plpgsql_dstring_free(&ds);
+
+ execsql = malloc(sizeof(PLpgSQL_stmt_execsql));
+ execsql->cmd_type = PLPGSQL_STMT_EXECSQL;
+ execsql->sqlstmt = expr;
+
+ return (PLpgSQL_stmt *)execsql;
+ }
+
+ if (plpgsql_SpaceScanned) {
+ plpgsql_dstring_append(&ds, " ");
+ }
+ switch (tok) {
+ case T_VARIABLE:
+ params[nparams] = yylval.var->varno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_RECFIELD:
+ params[nparams] = yylval.recfield->rfno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_TGARGV:
+ params[nparams] = yylval.trigarg->dno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ default:
+ if (tok == 0) {
+ plpgsql_error_lineno = yylineno;
+ plpgsql_comperrinfo();
+ elog(ERROR, "unexpected end of file");
+ }
+ plpgsql_dstring_append(&ds, yytext);
+ break;
+ }
+ }
+
+ tok = yylex();
+ switch (tok) {
+ case T_ROW:
+ row = yylval.row;
+ break;
+
+ case T_RECORD:
+ rec = yylval.rec;
+ break;
+
+ case T_VARIABLE:
+ case T_RECFIELD:
+ {
+ PLpgSQL_var *var;
+ PLpgSQL_recfield *recfield;
+ int nfields = 1;
+ char *fieldnames[1024];
+ int varnos[1024];
+
+ switch (tok) {
+ case T_VARIABLE:
+ var = yylval.var;
+ fieldnames[0] = strdup(yytext);
+ varnos[0] = var->varno;
+ break;
+
+ case T_RECFIELD:
+ recfield = yylval.recfield;
+ fieldnames[0] = strdup(yytext);
+ varnos[0] = recfield->rfno;
+ break;
+ }
+
+ while ((tok = yylex()) == ',') {
+ tok = yylex();
+ switch(tok) {
+ case T_VARIABLE:
+ var = yylval.var;
+ fieldnames[nfields] = strdup(yytext);
+ varnos[nfields++] = var->varno;
+ break;
+
+ case T_RECFIELD:
+ recfield = yylval.recfield;
+ fieldnames[0] = strdup(yytext);
+ varnos[0] = recfield->rfno;
+ break;
+
+ default:
+ elog(ERROR, "plpgsql: %s is not a variable or record field", yytext);
+ }
+ }
+ row = malloc(sizeof(PLpgSQL_row));
+ row->dtype = PLPGSQL_DTYPE_ROW;
+ row->refname = strdup("*internal*");
+ row->lineno = yylineno;
+ row->rowtypeclass = InvalidOid;
+ row->nfields = nfields;
+ row->fieldnames = malloc(sizeof(char *) * nfields);
+ row->varnos = malloc(sizeof(int) * nfields);
+ while (--nfields >= 0) {
+ row->fieldnames[nfields] = fieldnames[nfields];
+ row->varnos[nfields] = varnos[nfields];
+ }
+
+ plpgsql_adddatum((PLpgSQL_datum *)row);
+
+ have_nexttok = 1;
+ }
+ break;
+
+ default:
+ {
+ if (plpgsql_SpaceScanned) {
+ plpgsql_dstring_append(&ds, " ");
+ }
+ plpgsql_dstring_append(&ds, yytext);
+
+ while(1) {
+ tok = yylex();
+ if (tok == ';') {
+ PLpgSQL_stmt_execsql *execsql;
+
+ expr = malloc(sizeof(PLpgSQL_expr) + sizeof(int) * nparams - 1);
+ expr->dtype = PLPGSQL_DTYPE_EXPR;
+ expr->query = strdup(plpgsql_dstring_get(&ds));
+ expr->plan = NULL;
+ expr->nparams = nparams;
+ while(nparams-- > 0) {
+ expr->params[nparams] = params[nparams];
+ }
+ plpgsql_dstring_free(&ds);
+
+ execsql = malloc(sizeof(PLpgSQL_stmt_execsql));
+ execsql->cmd_type = PLPGSQL_STMT_EXECSQL;
+ execsql->sqlstmt = expr;
+
+ return (PLpgSQL_stmt *)execsql;
+ }
+
+ if (plpgsql_SpaceScanned) {
+ plpgsql_dstring_append(&ds, " ");
+ }
+ switch (tok) {
+ case T_VARIABLE:
+ params[nparams] = yylval.var->varno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_RECFIELD:
+ params[nparams] = yylval.recfield->rfno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_TGARGV:
+ params[nparams] = yylval.trigarg->dno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ default:
+ if (tok == 0) {
+ plpgsql_error_lineno = yylineno;
+ plpgsql_comperrinfo();
+ elog(ERROR, "unexpected end of file");
+ }
+ plpgsql_dstring_append(&ds, yytext);
+ break;
+ }
+ }
+ }
+ }
+
+ /************************************************************
+ * Eat up the rest of the statement after the target fields
+ ************************************************************/
+ while(1) {
+ if (!have_nexttok) {
+ tok = yylex();
+ }
+ have_nexttok = 0;
+ if (tok == ';') {
+ break;
+ }
+
+ if (plpgsql_SpaceScanned) {
+ plpgsql_dstring_append(&ds, " ");
+ }
+ switch (tok) {
+ case T_VARIABLE:
+ params[nparams] = yylval.var->varno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_RECFIELD:
+ params[nparams] = yylval.recfield->rfno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ case T_TGARGV:
+ params[nparams] = yylval.trigarg->dno;
+ sprintf(buf, "$%d", ++nparams);
+ plpgsql_dstring_append(&ds, buf);
+ break;
+
+ default:
+ if (tok == 0) {
+ plpgsql_error_lineno = yylineno;
+ plpgsql_comperrinfo();
+ elog(ERROR, "unexpected end of file");
+ }
+ plpgsql_dstring_append(&ds, yytext);
+ break;
+ }
+ }
+
+ expr = malloc(sizeof(PLpgSQL_expr) + sizeof(int) * (nparams - 1));
+ expr->dtype = PLPGSQL_DTYPE_EXPR;
+ expr->query = strdup(plpgsql_dstring_get(&ds));
+ expr->plan = NULL;
+ expr->nparams = nparams;
+ while(nparams-- > 0) {
+ expr->params[nparams] = params[nparams];
+ }
+ plpgsql_dstring_free(&ds);
+
+ select = malloc(sizeof(PLpgSQL_stmt_select));
+ memset(select, 0, sizeof(PLpgSQL_stmt_select));
+ select->cmd_type = PLPGSQL_STMT_SELECT;
+ select->rec = rec;
+ select->row = row;
+ select->query = expr;
+
+ return (PLpgSQL_stmt *)select;
+}
+
+
+static PLpgSQL_expr *
+make_tupret_expr(PLpgSQL_row *row)
+{
+ PLpgSQL_dstring ds;
+ PLpgSQL_expr *expr;
+ int i;
+ char buf[16];
+
+ expr = malloc(sizeof(PLpgSQL_expr) + sizeof(int) * (row->nfields - 1));
+ expr->dtype = PLPGSQL_DTYPE_EXPR;
+
+ plpgsql_dstring_init(&ds);
+ plpgsql_dstring_append(&ds, "SELECT ");
+
+ for (i = 0; i < row->nfields; i++) {
+ sprintf(buf, "%s$%d", (i > 0) ? "," : "", i + 1);
+ plpgsql_dstring_append(&ds, buf);
+ expr->params[i] = row->varnos[i];
+ }
+
+ expr->query = strdup(plpgsql_dstring_get(&ds));
+ expr->plan = NULL;
+ expr->plan_argtypes = NULL;
+ expr->nparams = row->nfields;
+
+ plpgsql_dstring_free(&ds);
+ return expr;
+}
+
+
+
+#include "pl_scan.c"
--- /dev/null
+--
+-- PL/pgSQL language declaration
+--
+-- $Header: /cvsroot/pgsql/contrib/plpgsql/src/Attic/mklang.sql,v 1.1 1998/08/22 12:38:31 momjian Exp $
+--
+
+create function plpgsql_call_handler() returns opaque
+ as '/usr/local/pgsql/lib/plpgsql.so'
+ language 'C';
+
+create trusted procedural language 'plpgsql'
+ handler plpgsql_call_handler
+ lancompiler 'PL/pgSQL';
+
--- /dev/null
+/**********************************************************************
+ * pl_comp.c - Compiler part of the PL/pgSQL
+ * procedural language
+ *
+ * IDENTIFICATION
+ * $Header: /cvsroot/pgsql/contrib/plpgsql/src/Attic/pl_comp.c,v 1.1 1998/08/22 12:38:32 momjian Exp $
+ *
+ * This software is copyrighted by Jan Wieck - Hamburg.
+ *
+ * The author hereby grants permission to use, copy, modify,
+ * distribute, and license this software and its documentation
+ * for any purpose, provided that existing copyright notices are
+ * retained in all copies and that this notice is included
+ * verbatim in any distributions. No written agreement, license,
+ * or royalty fee is required for any of the authorized uses.
+ * Modifications to this software may be copyrighted by their
+ * author and need not follow the licensing terms described
+ * here, provided that the new terms are clearly indicated on
+ * the first page of each file where they apply.
+ *
+ * IN NO EVENT SHALL THE AUTHOR OR DISTRIBUTORS BE LIABLE TO ANY
+ * PARTY FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL, OR
+ * CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OF THIS
+ * SOFTWARE, ITS DOCUMENTATION, OR ANY DERIVATIVES THEREOF, EVEN
+ * IF THE AUTHOR HAVE BEEN ADVISED OF THE POSSIBILITY OF SUCH
+ * DAMAGE.
+ *
+ * THE AUTHOR AND DISTRIBUTORS SPECIFICALLY DISCLAIM ANY
+ * WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
+ * WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
+ * PURPOSE, AND NON-INFRINGEMENT. THIS SOFTWARE IS PROVIDED ON
+ * AN "AS IS" BASIS, AND THE AUTHOR AND DISTRIBUTORS HAVE NO
+ * OBLIGATION TO PROVIDE MAINTENANCE, SUPPORT, UPDATES,
+ * ENHANCEMENTS, OR MODIFICATIONS.
+ *
+ **********************************************************************/
+
+#include <stdio.h>
+#include <stdlib.h>
+#include <stdarg.h>
+#include <unistd.h>
+#include <fcntl.h>
+#include <string.h>
+#include <ctype.h>
+
+#include "plpgsql.h"
+#include "pl.tab.h"
+
+#include "executor/spi.h"
+#include "commands/trigger.h"
+#include "utils/elog.h"
+#include "utils/builtins.h"
+#include "fmgr.h"
+#include "access/heapam.h"
+
+#include "utils/syscache.h"
+#include "utils/catcache.h"
+#include "catalog/catname.h"
+#include "catalog/pg_proc.h"
+#include "catalog/pg_type.h"
+#include "catalog/pg_class.h"
+#include "catalog/pg_attribute.h"
+#include "catalog/pg_attrdef.h"
+
+
+/* ----------
+ * Variables in the parser that shouldn't go into plpgsql.h
+ * ----------
+ */
+extern PLPGSQL_YYSTYPE plpgsql_yylval;
+extern int plpgsql_yylineno;
+extern char plpgsql_yytext[];
+
+void plpgsql_yyerror(const char *s);
+
+/* ----------
+ * Our own local and global variables
+ * ----------
+ */
+static int datums_alloc;
+int plpgsql_nDatums;
+PLpgSQL_datum **plpgsql_Datums;
+static int datums_last = 0;
+
+int plpgsql_error_lineno;
+char *plpgsql_error_funcname;
+int plpgsql_DumpExecTree = 0;
+
+PLpgSQL_function *plpgsql_curr_compile;
+
+
+/* ----------
+ * Local function declarations
+ * ----------
+ */
+static char *xlateSqlType(char *name);
+
+
+/* ----------
+ * plpgsql_compile Given a pg_proc's oid, make
+ * an execution tree for it.
+ * ----------
+ */
+PLpgSQL_function *plpgsql_compile(Oid fn_oid, int functype)
+{
+ int parse_rc;
+ HeapTuple procTup;
+ Form_pg_proc procStruct;
+ HeapTuple typeTup;
+ TypeTupleForm typeStruct;
+ char *proc_source;
+ PLpgSQL_function *function;
+ PLpgSQL_var *var;
+ PLpgSQL_row *row;
+ PLpgSQL_rec *rec;
+ int i;
+ int arg_varnos[MAXFMGRARGS];
+
+ /* ----------
+ * Initialize the compiler
+ * ----------
+ */
+ plpgsql_ns_init();
+ plpgsql_ns_push(NULL);
+ plpgsql_DumpExecTree = 0;
+
+ datums_alloc = 128;
+ plpgsql_nDatums = 0;
+ plpgsql_Datums = palloc(sizeof(PLpgSQL_datum *) * datums_alloc);
+ datums_last = 0;
+
+ /* ----------
+ * Lookup the pg_proc tuple by Oid
+ * ----------
+ */
+ procTup = SearchSysCacheTuple(PROOID,
+ ObjectIdGetDatum(fn_oid),
+ 0, 0, 0);
+ if (!HeapTupleIsValid(procTup)) {
+ elog(ERROR, "plpgsql: cache lookup from pg_proc failed");
+ }
+
+ /* ----------
+ * Setup the scanner input and error info
+ * ----------
+ */
+ procStruct = (Form_pg_proc) GETSTRUCT(procTup);
+ proc_source = textout(&(procStruct->prosrc));
+ plpgsql_setinput(proc_source, functype);
+ plpgsql_error_funcname = nameout(&(procStruct->proname));
+ plpgsql_error_lineno = 0;
+
+ /* ----------
+ * Create the new function node
+ * ----------
+ */
+ function = malloc(sizeof(PLpgSQL_function));
+ memset(function, 0, sizeof(PLpgSQL_function));
+ plpgsql_curr_compile = function;
+
+ function->fn_functype = functype;
+ function->fn_oid = fn_oid;
+ function->fn_name = strdup(nameout(&(procStruct->proname)));
+
+ switch (functype) {
+ case T_FUNCTION:
+ /* ----------
+ * Normal function has a defined returntype
+ * ----------
+ */
+ function->fn_rettype = procStruct->prorettype;
+ function->fn_retset = procStruct->proretset;
+
+ /* ----------
+ * Lookup the functions return type
+ * ----------
+ */
+ typeTup = SearchSysCacheTuple(TYPOID,
+ ObjectIdGetDatum(procStruct->prorettype), 0, 0, 0);
+
+ if (!HeapTupleIsValid(typeTup)) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "cache lookup for return type %d failed",
+ procStruct->prorettype);
+ }
+ typeStruct = (TypeTupleForm) GETSTRUCT(typeTup);
+ if (typeStruct->typrelid != InvalidOid) {
+ function->fn_retistuple = true;
+ } else {
+ function->fn_retbyval = typeStruct->typbyval;
+ function->fn_rettyplen = typeStruct->typlen;
+ fmgr_info(typeStruct->typinput, &(function->fn_retinput));
+ }
+
+ /* ----------
+ * Create the variables for the procedures parameters
+ * ----------
+ */
+ for (i = 0; i < procStruct->pronargs; i++) {
+ char buf[256];
+
+ /* ----------
+ * Get the parameters type
+ * ----------
+ */
+ typeTup = SearchSysCacheTuple(TYPOID,
+ ObjectIdGetDatum(procStruct->proargtypes[i]), 0, 0, 0);
+
+ if (!HeapTupleIsValid(typeTup)) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "cache lookup for argument type %d failed",
+ procStruct->proargtypes[i]);
+ }
+ typeStruct = (TypeTupleForm) GETSTRUCT(typeTup);
+
+ if (typeStruct->typrelid != InvalidOid) {
+ /* ----------
+ * For tuple type parameters, we set up a record
+ * of that type
+ * ----------
+ */
+ sprintf(buf, "%s%%rowtype", nameout(&(typeStruct->typname)));
+ if (plpgsql_parse_wordrowtype(buf) != T_ROW) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "cannot get tuple struct of argument %d", i + 1);
+ }
+
+ row = plpgsql_yylval.row;
+ sprintf(buf, "$%d", i + 1);
+
+ row->refname = strdup(buf);
+
+ plpgsql_adddatum((PLpgSQL_datum *)row);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_ROW, row->rowno, buf);
+
+ arg_varnos[i] = row->rowno;
+ } else {
+ /* ----------
+ * Normal parameters get a var node
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ memset(var, 0, sizeof(PLpgSQL_var));
+ var->datatype = malloc(sizeof(PLpgSQL_type));
+ memset(var->datatype, 0, sizeof(PLpgSQL_type));
+
+ sprintf(buf, "$%d", i + 1);
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = strdup(buf);
+ var->lineno = 0;
+ var->datatype->typname = strdup(nameout(&(typeStruct->typname)));
+ var->datatype->typoid = procStruct->proargtypes[i];
+ fmgr_info(typeStruct->typinput, &(var->datatype->typinput));
+ var->datatype->typbyval = typeStruct->typbyval;
+ var->datatype->atttypmod = -1;
+ var->isconst = true;
+ var->notnull = false;
+ var->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, var->varno, buf);
+
+ arg_varnos[i] = var->varno;
+ }
+ }
+ break;
+
+ case T_TRIGGER:
+ /* ----------
+ * Trigger procedures return type is unknown yet
+ * ----------
+ */
+ function->fn_rettype = InvalidOid;
+ function->fn_retbyval = false;
+ function->fn_retistuple = true;
+ function->fn_retset = false;
+
+ /* ----------
+ * Add the record for referencing NEW
+ * ----------
+ */
+ rec = malloc(sizeof(PLpgSQL_rec));
+ memset(rec, 0, sizeof(PLpgSQL_rec));
+ rec->dtype = PLPGSQL_DTYPE_REC;
+ rec->refname = strdup("new");
+ plpgsql_adddatum((PLpgSQL_datum *)rec);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_REC, rec->recno, rec->refname);
+ function->new_varno = rec->recno;
+
+ /* ----------
+ * Add the record for referencing OLD
+ * ----------
+ */
+ rec = malloc(sizeof(PLpgSQL_rec));
+ memset(rec, 0, sizeof(PLpgSQL_rec));
+ rec->dtype = PLPGSQL_DTYPE_REC;
+ rec->refname = strdup("old");
+ plpgsql_adddatum((PLpgSQL_datum *)rec);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_REC, rec->recno, rec->refname);
+ function->old_varno = rec->recno;
+
+ /* ----------
+ * Add the variable tg_name
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ memset(var, 0, sizeof(PLpgSQL_var));
+
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = strdup("tg_name");
+ var->lineno = 0;
+ plpgsql_parse_word("name");
+ var->datatype = plpgsql_yylval.dtype;
+ var->isconst = false;
+ var->notnull = false;
+ var->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, var->varno, var->refname);
+ function->tg_name_varno = var->varno;
+
+ /* ----------
+ * Add the variable tg_when
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ memset(var, 0, sizeof(PLpgSQL_var));
+
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = strdup("tg_when");
+ var->lineno = 0;
+ plpgsql_parse_word("text");
+ var->datatype = plpgsql_yylval.dtype;
+ var->isconst = false;
+ var->notnull = false;
+ var->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, var->varno, var->refname);
+ function->tg_when_varno = var->varno;
+
+ /* ----------
+ * Add the variable tg_level
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ memset(var, 0, sizeof(PLpgSQL_var));
+
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = strdup("tg_level");
+ var->lineno = 0;
+ plpgsql_parse_word("text");
+ var->datatype = plpgsql_yylval.dtype;
+ var->isconst = false;
+ var->notnull = false;
+ var->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, var->varno, var->refname);
+ function->tg_level_varno = var->varno;
+
+ /* ----------
+ * Add the variable tg_op
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ memset(var, 0, sizeof(PLpgSQL_var));
+
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = strdup("tg_op");
+ var->lineno = 0;
+ plpgsql_parse_word("text");
+ var->datatype = plpgsql_yylval.dtype;
+ var->isconst = false;
+ var->notnull = false;
+ var->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, var->varno, var->refname);
+ function->tg_op_varno = var->varno;
+
+ /* ----------
+ * Add the variable tg_relid
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ memset(var, 0, sizeof(PLpgSQL_var));
+
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = strdup("tg_relid");
+ var->lineno = 0;
+ plpgsql_parse_word("oid");
+ var->datatype = plpgsql_yylval.dtype;
+ var->isconst = false;
+ var->notnull = false;
+ var->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, var->varno, var->refname);
+ function->tg_relid_varno = var->varno;
+
+ /* ----------
+ * Add the variable tg_relname
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ memset(var, 0, sizeof(PLpgSQL_var));
+
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = strdup("tg_relname");
+ var->lineno = 0;
+ plpgsql_parse_word("name");
+ var->datatype = plpgsql_yylval.dtype;
+ var->isconst = false;
+ var->notnull = false;
+ var->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, var->varno, var->refname);
+ function->tg_relname_varno = var->varno;
+
+ /* ----------
+ * Add the variable tg_nargs
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ memset(var, 0, sizeof(PLpgSQL_var));
+
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = strdup("tg_nargs");
+ var->lineno = 0;
+ plpgsql_parse_word("int4");
+ var->datatype = plpgsql_yylval.dtype;
+ var->isconst = false;
+ var->notnull = false;
+ var->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, var->varno, var->refname);
+ function->tg_nargs_varno = var->varno;
+
+ break;
+
+ default:
+ elog(ERROR, "unknown function type %d in plpgsql_compile()",
+ functype);
+ break;
+ }
+
+ /* ----------
+ * Create the magic found variable indicating if the
+ * last FOR or SELECT statement returned data
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ memset(var, 0, sizeof(PLpgSQL_var));
+
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = strdup("found");
+ var->lineno = 0;
+ plpgsql_parse_word("bool");
+ var->datatype = plpgsql_yylval.dtype;
+ var->isconst = false;
+ var->notnull = false;
+ var->default_val = NULL;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_VAR, var->varno, strdup("found"));
+ function->found_varno = var->varno;
+
+ /* ----------
+ * Forget about the above created variables
+ * ----------
+ */
+ plpgsql_add_initdatums(NULL);
+
+ /* ----------
+ * Now parse the functions text
+ * ----------
+ */
+ parse_rc = plpgsql_yyparse();
+ if (parse_rc != 0) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "plpgsql: parser returned %d ???", parse_rc);
+ }
+
+ /* ----------
+ * If that was successful, complete the functions info.
+ * ----------
+ */
+ function->fn_nargs = procStruct->pronargs;
+ for (i = 0; i < function->fn_nargs; i++) {
+ function->fn_argvarnos[i] = arg_varnos[i];
+ }
+ function->ndatums = plpgsql_nDatums;
+ function->datums = malloc(sizeof(PLpgSQL_datum *) * plpgsql_nDatums);
+ for (i = 0; i < plpgsql_nDatums; i++) {
+ function->datums[i] = plpgsql_Datums[i];
+ }
+ function->action = plpgsql_yylval.program;
+
+
+ /* ----------
+ * Finally return the compiled function
+ * ----------
+ */
+ if (plpgsql_DumpExecTree) {
+ plpgsql_dumptree(function);
+ }
+ return function;
+}
+
+
+/* ----------
+ * plpgsql_parse_word The scanner calls this to postparse
+ * any single word not found by a
+ * keyword rule.
+ * ----------
+ */
+int plpgsql_parse_word(char *word)
+{
+ PLpgSQL_nsitem *nse;
+ char *cp;
+ HeapTuple typeTup;
+ TypeTupleForm typeStruct;
+ char *typeXlated;
+
+ /* ----------
+ * We do our lookups case insensitive
+ * ----------
+ */
+ cp = plpgsql_tolower(pstrdup(word));
+
+ /* ----------
+ * Special handling when compiling triggers
+ * ----------
+ */
+ if (plpgsql_curr_compile->fn_functype == T_TRIGGER) {
+ if (!strcmp(cp, "tg_argv")) {
+ int save_spacescanned = plpgsql_SpaceScanned;
+ PLpgSQL_trigarg *trigarg;
+
+ trigarg = malloc(sizeof(PLpgSQL_trigarg));
+ memset(trigarg, 0, sizeof(PLpgSQL_trigarg));
+ trigarg->dtype = PLPGSQL_DTYPE_TRIGARG;
+
+ if (plpgsql_yylex() != '[') {
+ plpgsql_yyerror("expected [");
+ }
+
+ trigarg->argnum = plpgsql_read_expression(']', "]");
+
+ plpgsql_adddatum((PLpgSQL_datum *)trigarg);
+ plpgsql_yylval.trigarg = trigarg;
+
+ plpgsql_SpaceScanned = save_spacescanned;
+ return T_TGARGV;
+ }
+ }
+
+ /* ----------
+ * Do a lookup on the compilers namestack
+ * ----------
+ */
+ nse = plpgsql_ns_lookup(cp, NULL);
+ if (nse != NULL) {
+ pfree(cp);
+ switch (nse->itemtype) {
+ case PLPGSQL_NSTYPE_LABEL:
+ return T_LABEL;
+
+ case PLPGSQL_NSTYPE_VAR:
+ plpgsql_yylval.var = (PLpgSQL_var *)(plpgsql_Datums[nse->itemno]);
+ return T_VARIABLE;
+
+ case PLPGSQL_NSTYPE_REC:
+ plpgsql_yylval.rec = (PLpgSQL_rec *)(plpgsql_Datums[nse->itemno]);
+ return T_RECORD;
+
+ case PLPGSQL_NSTYPE_ROW:
+ plpgsql_yylval.row = (PLpgSQL_row *)(plpgsql_Datums[nse->itemno]);
+ return T_ROW;
+
+ default:
+ return T_ERROR;
+ }
+ }
+
+ /* ----------
+ * Try to find a data type with that name, but ignore
+ * pg_type entries that are in fact class types.
+ * ----------
+ */
+ typeXlated = xlateSqlType(cp);
+ typeTup = SearchSysCacheTuple(TYPNAME,
+ PointerGetDatum(typeXlated), 0, 0, 0);
+ if (HeapTupleIsValid(typeTup)) {
+ PLpgSQL_type *typ;
+
+ typeStruct = (TypeTupleForm) GETSTRUCT(typeTup);
+
+ if (typeStruct->typrelid != InvalidOid) {
+ pfree(cp);
+ return T_WORD;
+ }
+
+ typ = (PLpgSQL_type *)malloc(sizeof(PLpgSQL_type));
+
+ typ->typname = strdup(nameout(&(typeStruct->typname)));
+ typ->typoid = typeTup->t_oid;
+ fmgr_info(typeStruct->typinput, &(typ->typinput));
+ typ->typbyval = typeStruct->typbyval;
+ typ->atttypmod = -1;
+
+ plpgsql_yylval.dtype = typ;
+
+ pfree(cp);
+ return T_DTYPE;
+ }
+
+ /* ----------
+ * Nothing found - up to now it's a word without any
+ * special meaning for us.
+ * ----------
+ */
+ pfree(cp);
+ return T_WORD;
+}
+
+
+/* ----------
+ * plpgsql_parse_dblword Same lookup for two words
+ * separated by a dot.
+ * ----------
+ */
+int plpgsql_parse_dblword(char *string)
+{
+ char *word1;
+ char *word2;
+ PLpgSQL_nsitem *ns;
+
+ /* ----------
+ * Convert to lower case and separate the words
+ * ----------
+ */
+ word1 = plpgsql_tolower(pstrdup(string));
+ word2 = strchr(word1, '.');
+ *word2++ = '\0';
+
+ /* ----------
+ * Lookup the first word
+ * ----------
+ */
+ ns = plpgsql_ns_lookup(word1, NULL);
+ if (ns == NULL) {
+ pfree(word1);
+ return T_ERROR;
+ }
+
+ switch (ns->itemtype) {
+ case PLPGSQL_NSTYPE_LABEL:
+ /* ----------
+ * First word is a label, so second word could be
+ * a variable, record or row in that bodies namestack.
+ * Anything else could only be something in a query
+ * given to the SPI manager and T_ERROR will get eaten
+ * up by the collector routines.
+ * ----------
+ */
+ ns = plpgsql_ns_lookup(word2, word1);
+ if (ns == NULL) {
+ pfree(word1);
+ return T_ERROR;
+ }
+ switch (ns->itemtype) {
+ case PLPGSQL_NSTYPE_VAR:
+ plpgsql_yylval.var = (PLpgSQL_var *)(plpgsql_Datums[ns->itemno]);
+ pfree(word1);
+ return T_VARIABLE;
+
+ case PLPGSQL_NSTYPE_REC:
+ plpgsql_yylval.rec = (PLpgSQL_rec *)(plpgsql_Datums[ns->itemno]);
+ pfree(word1);
+ return T_RECORD;
+
+ case PLPGSQL_NSTYPE_ROW:
+ plpgsql_yylval.row = (PLpgSQL_row *)(plpgsql_Datums[ns->itemno]);
+ pfree(word1);
+ return T_ROW;
+
+ default:
+ pfree(word1);
+ return T_ERROR;
+ }
+
+ case PLPGSQL_NSTYPE_REC:
+ {
+ /* ----------
+ * First word is a record name, so second word
+ * must be a field in this record.
+ * ----------
+ */
+ PLpgSQL_recfield *new;
+
+ new = malloc(sizeof(PLpgSQL_recfield));
+ new->dtype = PLPGSQL_DTYPE_RECFIELD;
+ new->fieldname = strdup(word2);
+ new->recno = ns->itemno;
+
+ plpgsql_adddatum((PLpgSQL_datum *)new);
+
+ pfree(word1);
+ plpgsql_yylval.recfield = new;
+ return T_RECFIELD;
+ }
+
+ case PLPGSQL_NSTYPE_ROW:
+ {
+ /* ----------
+ * First word is a row name, so second word must
+ * be a field in this row.
+ * ----------
+ */
+ PLpgSQL_row *row;
+ int i;
+
+ row = (PLpgSQL_row *)(plpgsql_Datums[ns->itemno]);
+ for (i = 0; i < row->nfields; i++) {
+ if (!strcmp(row->fieldnames[i], word2)) {
+ plpgsql_yylval.var = (PLpgSQL_var *)(plpgsql_Datums[row->varnos[i]]);
+ pfree(word1);
+ return T_VARIABLE;
+ }
+ }
+ plpgsql_comperrinfo();
+ elog(ERROR, "row %s doesn't have a field %s",
+ word1, word2);
+ }
+
+ default:
+ break;
+ }
+
+ pfree(word1);
+ return T_ERROR;
+}
+
+
+/* ----------
+ * plpgsql_parse_tripword Same lookup for three words
+ * separated by dots.
+ * ----------
+ */
+int plpgsql_parse_tripword(char *string)
+{
+ char *word1;
+ char *word2;
+ char *word3;
+ PLpgSQL_nsitem *ns;
+
+ /* ----------
+ * Convert to lower case and separate the words
+ * ----------
+ */
+ word1 = plpgsql_tolower(pstrdup(string));
+ word2 = strchr(word1, '.');
+ *word2++ = '\0';
+ word3 = strchr(word2, '.');
+ *word3++ = '\0';
+
+ /* ----------
+ * Lookup the first word - it must be a label
+ * ----------
+ */
+ ns = plpgsql_ns_lookup(word1, NULL);
+ if (ns == NULL) {
+ pfree(word1);
+ return T_ERROR;
+ }
+ if (ns->itemtype != PLPGSQL_NSTYPE_LABEL) {
+ pfree(word1);
+ return T_ERROR;
+ }
+
+ /* ----------
+ * First word is a label, so second word could be
+ * a record or row
+ * ----------
+ */
+ ns = plpgsql_ns_lookup(word2, word1);
+ if (ns == NULL) {
+ pfree(word1);
+ return T_ERROR;
+ }
+
+ switch (ns->itemtype) {
+ case PLPGSQL_NSTYPE_REC:
+ {
+ /* ----------
+ * This word is a record name, so third word
+ * must be a field in this record.
+ * ----------
+ */
+ PLpgSQL_recfield *new;
+
+ new = malloc(sizeof(PLpgSQL_recfield));
+ new->dtype = PLPGSQL_DTYPE_RECFIELD;
+ new->fieldname = strdup(word3);
+ new->recno = ns->itemno;
+
+ plpgsql_adddatum((PLpgSQL_datum *)new);
+
+ pfree(word1);
+ plpgsql_yylval.recfield = new;
+ return T_RECFIELD;
+ }
+
+ case PLPGSQL_NSTYPE_ROW:
+ {
+ /* ----------
+ * This word is a row name, so third word must
+ * be a field in this row.
+ * ----------
+ */
+ PLpgSQL_row *row;
+ int i;
+
+ row = (PLpgSQL_row *)(plpgsql_Datums[ns->itemno]);
+ for (i = 0; i < row->nfields; i++) {
+ if (!strcmp(row->fieldnames[i], word3)) {
+ plpgsql_yylval.var = (PLpgSQL_var *)(plpgsql_Datums[row->varnos[i]]);
+ pfree(word1);
+ return T_VARIABLE;
+ }
+ }
+ plpgsql_comperrinfo();
+ elog(ERROR, "row %s.%s doesn't have a field %s",
+ word1, word2, word3);
+ }
+
+ default:
+ break;
+ }
+
+ pfree(word1);
+ return T_ERROR;
+}
+
+
+/* ----------
+ * plpgsql_parse_wordtype The scanner found word%TYPE. word can be
+ * a variable name or a basetype.
+ * ----------
+ */
+int plpgsql_parse_wordtype(char *word)
+{
+ PLpgSQL_nsitem *nse;
+ char *cp;
+ HeapTuple typeTup;
+ TypeTupleForm typeStruct;
+ char *typeXlated;
+ bool old_nsstate;
+
+ /* ----------
+ * We do our lookups case insensitive
+ * ----------
+ */
+ cp = plpgsql_tolower(pstrdup(word));
+ *(strchr(cp, '%')) = '\0';
+
+ /* ----------
+ * Do a lookup on the compilers namestack.
+ * But ensure it moves up to the toplevel.
+ * ----------
+ */
+ old_nsstate = plpgsql_ns_setlocal(false);
+ nse = plpgsql_ns_lookup(cp, NULL);
+ plpgsql_ns_setlocal(old_nsstate);
+
+ if (nse != NULL) {
+ pfree(cp);
+ switch (nse->itemtype) {
+ case PLPGSQL_NSTYPE_VAR:
+ plpgsql_yylval.dtype = ((PLpgSQL_var *)(plpgsql_Datums[nse->itemno]))->datatype;
+ return T_DTYPE;
+
+ default:
+ return T_ERROR;
+ }
+ }
+
+ /* ----------
+ * Word wasn't found on the namestack.
+ * Try to find a data type with that name, but ignore
+ * pg_type entries that are in fact class types.
+ * ----------
+ */
+ typeXlated = xlateSqlType(cp);
+ typeTup = SearchSysCacheTuple(TYPNAME,
+ PointerGetDatum(typeXlated), 0, 0, 0);
+ if (HeapTupleIsValid(typeTup)) {
+ PLpgSQL_type *typ;
+
+ typeStruct = (TypeTupleForm) GETSTRUCT(typeTup);
+
+ if (typeStruct->typrelid != InvalidOid) {
+ pfree(cp);
+ return T_ERROR;
+ }
+
+ typ = (PLpgSQL_type *)malloc(sizeof(PLpgSQL_type));
+
+ typ->typname = strdup(nameout(&(typeStruct->typname)));
+ typ->typoid = typeTup->t_oid;
+ fmgr_info(typeStruct->typinput, &(typ->typinput));
+ typ->typbyval = typeStruct->typbyval;
+ typ->atttypmod = -1;
+
+ plpgsql_yylval.dtype = typ;
+
+ pfree(cp);
+ return T_DTYPE;
+ }
+
+ /* ----------
+ * Nothing found - up to now it's a word without any
+ * special meaning for us.
+ * ----------
+ */
+ pfree(cp);
+ return T_ERROR;
+}
+
+
+/* ----------
+ * plpgsql_parse_dblwordtype Same lookup for word.word%TYPE
+ * ----------
+ */
+int plpgsql_parse_dblwordtype(char *string)
+{
+ char *word1;
+ char *word2;
+ PLpgSQL_nsitem *nse;
+ bool old_nsstate;
+ HeapTuple classtup;
+ Form_pg_class classStruct;
+ HeapTuple attrtup;
+ AttributeTupleForm attrStruct;
+ HeapTuple typetup;
+ TypeTupleForm typeStruct;
+ PLpgSQL_type *typ;
+
+
+ /* ----------
+ * Convert to lower case and separate the words
+ * ----------
+ */
+ word1 = plpgsql_tolower(pstrdup(string));
+ word2 = strchr(word1, '.');
+ *word2++ = '\0';
+ *(strchr(word2, '%')) = '\0';
+
+ /* ----------
+ * Lookup the first word
+ * ----------
+ */
+ nse = plpgsql_ns_lookup(word1, NULL);
+
+ /* ----------
+ * If this is a label lookup the second word in that
+ * labels namestack level
+ * ----------
+ */
+ if (nse != NULL) {
+ if (nse->itemtype == PLPGSQL_NSTYPE_LABEL) {
+ old_nsstate = plpgsql_ns_setlocal(false);
+ nse = plpgsql_ns_lookup(word2, word1);
+ plpgsql_ns_setlocal(old_nsstate);
+
+ pfree(word1);
+
+ if (nse != NULL) {
+ switch (nse->itemtype) {
+ case PLPGSQL_NSTYPE_VAR:
+ plpgsql_yylval.dtype = ((PLpgSQL_var *)(plpgsql_Datums[nse->itemno]))->datatype;
+ return T_DTYPE;
+
+ default:
+ return T_ERROR;
+ }
+ }
+ return T_ERROR;
+ }
+ pfree(word1);
+ return T_ERROR;
+ }
+
+ /* ----------
+ * First word could also be a table name
+ * ----------
+ */
+ classtup = SearchSysCacheTuple(RELNAME,
+ PointerGetDatum(word1), 0, 0, 0);
+ if (!HeapTupleIsValid(classtup)) {
+ pfree(word1);
+ return T_ERROR;
+ }
+
+ /* ----------
+ * It must be a (shared) relation class
+ * ----------
+ */
+ classStruct = (Form_pg_class)GETSTRUCT(classtup);
+ if (classStruct->relkind != 'r' && classStruct->relkind != 's') {
+ pfree(word1);
+ return T_ERROR;
+ }
+
+ /* ----------
+ * Fetch the named table field and it's type
+ * ----------
+ */
+ attrtup = SearchSysCacheTuple(ATTNAME,
+ ObjectIdGetDatum(classtup->t_oid),
+ PointerGetDatum(word2), 0, 0);
+ if (!HeapTupleIsValid(attrtup)) {
+ pfree(word1);
+ return T_ERROR;
+ }
+ attrStruct = (AttributeTupleForm)GETSTRUCT(attrtup);
+
+ typetup = SearchSysCacheTuple(TYPOID,
+ ObjectIdGetDatum(attrStruct->atttypid), 0, 0, 0);
+ if (!HeapTupleIsValid(typetup)) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "cache lookup for type %d of %s.%s failed",
+ attrStruct->atttypid, word1, word2);
+ }
+
+ /* ----------
+ * Found that - build a compiler type struct and return it
+ * ----------
+ */
+ typeStruct = (TypeTupleForm)GETSTRUCT(typetup);
+
+ typ = (PLpgSQL_type *)malloc(sizeof(PLpgSQL_type));
+
+ typ->typname = strdup(nameout(&(typeStruct->typname)));
+ typ->typoid = typetup->t_oid;
+ fmgr_info(typeStruct->typinput, &(typ->typinput));
+ typ->typbyval = typeStruct->typbyval;
+ typ->atttypmod = attrStruct->atttypmod;
+
+ plpgsql_yylval.dtype = typ;
+
+ pfree(word1);
+ return T_DTYPE;
+}
+
+
+/* ----------
+ * plpgsql_parse_wordrowtype Scanner found word%ROWTYPE.
+ * So word must be a table name.
+ * ----------
+ */
+int plpgsql_parse_wordrowtype(char *string)
+{
+ HeapTuple classtup;
+ Form_pg_class classStruct;
+ HeapTuple typetup;
+ TypeTupleForm typeStruct;
+ HeapTuple attrtup;
+ AttributeTupleForm attrStruct;
+ char *word1;
+ char *cp;
+ int i;
+ PLpgSQL_row *row;
+ PLpgSQL_var *var;
+
+ /* ----------
+ * Get the word in lower case and fetch the pg_class tuple.
+ * ----------
+ */
+ word1 = plpgsql_tolower(pstrdup(string));
+ cp = strchr(word1, '%');
+ *cp = '\0';
+
+ classtup = SearchSysCacheTuple(RELNAME,
+ PointerGetDatum(word1), 0, 0, 0);
+ if (!HeapTupleIsValid(classtup)) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "%s: no such class", word1);
+ }
+ classStruct = (Form_pg_class)GETSTRUCT(classtup);
+ if (classStruct->relkind != 'r' && classStruct->relkind != 's') {
+ plpgsql_comperrinfo();
+ elog(ERROR, "%s isn't a table", word1);
+ }
+
+ /* ----------
+ * Fetch the tables pg_type tuple too
+ * ----------
+ */
+ typetup = SearchSysCacheTuple(TYPNAME,
+ PointerGetDatum(word1), 0, 0, 0);
+ if (!HeapTupleIsValid(typetup)) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "cache lookup for %s in pg_type failed", word1);
+ }
+
+ /* ----------
+ * Create a row datum entry and all the required variables
+ * that it will point to.
+ * ----------
+ */
+ row = malloc(sizeof(PLpgSQL_row));
+ memset(row, 0, sizeof(PLpgSQL_row));
+
+ row->dtype = PLPGSQL_DTYPE_ROW;
+ row->nfields = classStruct->relnatts;
+ row->rowtypeclass = typetup->t_oid;
+ row->fieldnames = malloc(sizeof(char *) * row->nfields);
+ row->varnos = malloc(sizeof(int) * row->nfields);
+
+ for (i = 0; i < row->nfields; i++) {
+ /* ----------
+ * Get the attribute and it's type
+ * ----------
+ */
+ attrtup = SearchSysCacheTuple(ATTNUM,
+ ObjectIdGetDatum(classtup->t_oid),
+ (Datum)(i + 1), 0, 0);
+ if (!HeapTupleIsValid(attrtup)) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "cache lookup for attribute %d of class %s failed",
+ i + 1, word1);
+ }
+ attrStruct = (AttributeTupleForm)GETSTRUCT(attrtup);
+
+ typetup = SearchSysCacheTuple(TYPOID,
+ ObjectIdGetDatum(attrStruct->atttypid), 0, 0, 0);
+ if (!HeapTupleIsValid(typetup)) {
+ plpgsql_comperrinfo();
+ elog(ERROR, "cache lookup for type %d of %s.%s failed",
+ attrStruct->atttypid, word1,
+ nameout(&(attrStruct->attname)));
+ }
+ typeStruct = (TypeTupleForm)GETSTRUCT(typetup);
+
+ cp = strdup(nameout(&(attrStruct->attname)));
+
+ /* ----------
+ * Create the internal variable
+ * We know if the table definitions contain a default value
+ * or if the field is declared in the table as NOT NULL. But
+ * it's possible to create a table field as NOT NULL without
+ * a default value and that would lead to problems later when
+ * initializing the variables due to entering a block at
+ * execution time. Thus we ignore this information for now.
+ * ----------
+ */
+ var = malloc(sizeof(PLpgSQL_var));
+ var->dtype = PLPGSQL_DTYPE_VAR;
+ var->refname = malloc(strlen(word1) + strlen(cp) + 2);
+ strcpy(var->refname, word1);
+ strcat(var->refname, ".");
+ strcat(var->refname, cp);
+ var->datatype = malloc(sizeof(PLpgSQL_type));
+ var->datatype->typname = strdup(nameout(&(typeStruct->typname)));
+ var->datatype->typoid = typetup->t_oid;
+ fmgr_info(typeStruct->typinput, &(var->datatype->typinput));
+ var->datatype->typbyval = typeStruct->typbyval;
+ var->datatype->atttypmod = attrStruct->atttypmod;
+ var->isconst = false;
+ var->notnull = false;
+ var->default_val = NULL;
+ var->value = (Datum)0;
+ var->isnull = true;
+ var->shouldfree = false;
+
+ plpgsql_adddatum((PLpgSQL_datum *)var);
+
+ /* ----------
+ * Add the variable to the row.
+ * ----------
+ */
+ row->fieldnames[i] = cp;
+ row->varnos[i] = var->varno;
+ }
+
+ /* ----------
+ * Return the complete row definition
+ * ----------
+ */
+ plpgsql_yylval.row = row;
+
+ return T_ROW;
+}
+
+
+/* ----------
+ * plpgsql_adddatum Add a variable, record or row
+ * to the compilers datum list.
+ * ----------
+ */
+void plpgsql_adddatum(PLpgSQL_datum *new)
+{
+ if (plpgsql_nDatums == datums_alloc) {
+ datums_alloc *= 2;
+ plpgsql_Datums = repalloc(plpgsql_Datums, sizeof(PLpgSQL_datum *) * datums_alloc);
+ }
+
+ new->dno = plpgsql_nDatums;
+ plpgsql_Datums[plpgsql_nDatums++] = new;
+}
+
+
+/* ----------
+ * plpgsql_add_initdatums Put all datum entries created
+ * since the last call into the
+ * finishing code block so the
+ * block knows which variables to
+ * reinitialize when entered.
+ * ----------
+ */
+int plpgsql_add_initdatums(int **varnos)
+{
+ int i;
+ int n = 0;
+
+ for (i = datums_last; i < plpgsql_nDatums; i++) {
+ switch (plpgsql_Datums[i]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ n++;
+ break;
+
+ default:
+ break;
+ }
+ }
+
+ if (varnos != NULL) {
+ *varnos = (int *)malloc(sizeof(int) * n);
+
+ n = 0;
+ for (i = datums_last; i < plpgsql_nDatums; i++) {
+ switch (plpgsql_Datums[i]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ (*varnos)[n++] = plpgsql_Datums[i]->dno;
+
+ default:
+ break;
+ }
+ }
+ }
+
+ datums_last = plpgsql_nDatums;
+ return n;
+}
+
+
+/* ----------
+ * plpgsql_comperrinfo Called before elog(ERROR, ...)
+ * during compile.
+ * ----------
+ */
+void plpgsql_comperrinfo()
+{
+ elog(NOTICE, "plpgsql: ERROR during compile of %s near line %d",
+ plpgsql_error_funcname, plpgsql_error_lineno);
+}
+
+
+/* ---------
+ * plpgsql_yyerror Handle parser error
+ * ---------
+ */
+
+void plpgsql_yyerror(const char *s)
+{
+ plpgsql_error_lineno = plpgsql_yylineno;
+ plpgsql_comperrinfo();
+ elog(ERROR, "%s at or near \"%s\"", s, plpgsql_yytext);
+}
+
+
+/* ----------
+ * xlateSqlType()
+ * Convert alternate type names to internal Postgres types.
+ *
+ * Stolen from backend's main parser
+ * ----------
+ */
+static char *
+xlateSqlType(char *name)
+{
+ if (!strcasecmp(name,"int")
+ || !strcasecmp(name,"integer"))
+ return "int4";
+ else if (!strcasecmp(name, "smallint"))
+ return "int2";
+ else if (!strcasecmp(name, "real")
+ || !strcasecmp(name, "float"))
+ return "float8";
+ else if (!strcasecmp(name, "interval"))
+ return "timespan";
+ else if (!strcasecmp(name, "boolean"))
+ return "bool";
+ else
+ return name;
+} /* xlateSqlType() */
+
+
--- /dev/null
+/**********************************************************************
+ * pl_exec.c - Executor for the PL/pgSQL
+ * procedural language
+ *
+ * IDENTIFICATION
+ * $Header: /cvsroot/pgsql/contrib/plpgsql/src/Attic/pl_exec.c,v 1.1 1998/08/22 12:38:32 momjian Exp $
+ *
+ * This software is copyrighted by Jan Wieck - Hamburg.
+ *
+ * The author hereby grants permission to use, copy, modify,
+ * distribute, and license this software and its documentation
+ * for any purpose, provided that existing copyright notices are
+ * retained in all copies and that this notice is included
+ * verbatim in any distributions. No written agreement, license,
+ * or royalty fee is required for any of the authorized uses.
+ * Modifications to this software may be copyrighted by their
+ * author and need not follow the licensing terms described
+ * here, provided that the new terms are clearly indicated on
+ * the first page of each file where they apply.
+ *
+ * IN NO EVENT SHALL THE AUTHOR OR DISTRIBUTORS BE LIABLE TO ANY
+ * PARTY FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL, OR
+ * CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OF THIS
+ * SOFTWARE, ITS DOCUMENTATION, OR ANY DERIVATIVES THEREOF, EVEN
+ * IF THE AUTHOR HAVE BEEN ADVISED OF THE POSSIBILITY OF SUCH
+ * DAMAGE.
+ *
+ * THE AUTHOR AND DISTRIBUTORS SPECIFICALLY DISCLAIM ANY
+ * WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
+ * WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
+ * PURPOSE, AND NON-INFRINGEMENT. THIS SOFTWARE IS PROVIDED ON
+ * AN "AS IS" BASIS, AND THE AUTHOR AND DISTRIBUTORS HAVE NO
+ * OBLIGATION TO PROVIDE MAINTENANCE, SUPPORT, UPDATES,
+ * ENHANCEMENTS, OR MODIFICATIONS.
+ *
+ **********************************************************************/
+
+#include <stdio.h>
+#include <stdlib.h>
+#include <stdarg.h>
+#include <unistd.h>
+#include <fcntl.h>
+#include <string.h>
+#include <ctype.h>
+#include <setjmp.h>
+
+#include "plpgsql.h"
+#include "pl.tab.h"
+
+#include "executor/spi.h"
+#include "commands/trigger.h"
+#include "utils/elog.h"
+#include "utils/builtins.h"
+#include "fmgr.h"
+#include "access/heapam.h"
+
+#include "utils/syscache.h"
+#include "catalog/pg_proc.h"
+#include "catalog/pg_type.h"
+
+
+/************************************************************
+ * Make Warn_restart from tcop/postgres.c visible for us.
+ * The longjmp() mechanism of the elog(ERROR,...) makes it
+ * impossible for us to call exceptions. But at least I
+ * would like some suggestions about where in the PL function
+ * the error occured.
+ *
+ * It's ugly - Jan
+ ************************************************************/
+#if defined(nextstep)
+#define sigjmp_buf jmp_buf
+#define sigsetjmp(x,y) setjmp(x)
+#define siglongjmp longjmp
+#endif
+
+extern sigjmp_buf Warn_restart; /* in tcop/postgres.c */
+
+static PLpgSQL_function *error_info_func = NULL;
+static PLpgSQL_stmt *error_info_stmt = NULL;
+static char *error_info_text = NULL;
+
+
+/************************************************************
+ * Local function forward declarations
+ ************************************************************/
+static PLpgSQL_var *copy_var(PLpgSQL_var *var);
+static PLpgSQL_rec *copy_rec(PLpgSQL_rec *rec);
+
+static int exec_stmt_block(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_block *block);
+static int exec_stmts(PLpgSQL_execstate *estate,
+ PLpgSQL_stmts *stmts);
+static int exec_stmt(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt *stmt);
+static int exec_stmt_assign(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_assign *stmt);
+static int exec_stmt_if(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_if *stmt);
+static int exec_stmt_loop(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_loop *stmt);
+static int exec_stmt_while(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_while *stmt);
+static int exec_stmt_fori(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_fori *stmt);
+static int exec_stmt_fors(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_fors *stmt);
+static int exec_stmt_select(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_select *stmt);
+static int exec_stmt_exit(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_exit *stmt);
+static int exec_stmt_return(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_return *stmt);
+static int exec_stmt_raise(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_raise *stmt);
+static int exec_stmt_execsql(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_execsql *stmt);
+
+static void exec_assign_expr(PLpgSQL_execstate *estate,
+ PLpgSQL_datum *target,
+ PLpgSQL_expr *expr);
+static void exec_assign_value(PLpgSQL_execstate *estate,
+ PLpgSQL_datum *target,
+ Datum value, Oid valtype, bool *isNull);
+static Datum exec_eval_expr(PLpgSQL_execstate *estate,
+ PLpgSQL_expr *expr,
+ bool *isNull,
+ Oid *rettype);
+static int exec_run_select(PLpgSQL_execstate *estate,
+ PLpgSQL_expr *expr, int maxtuples);
+static void exec_move_row(PLpgSQL_execstate *estate,
+ PLpgSQL_rec *rec,
+ PLpgSQL_row *row,
+ HeapTuple tup, TupleDesc tupdesc);
+static Datum exec_cast_value(Datum value, Oid valtype,
+ Oid reqtype,
+ FmgrInfo *reqinput,
+ int16 reqtypmod,
+ bool *isnull);
+static void exec_set_found(PLpgSQL_execstate *estate, bool state);
+
+
+/* ----------
+ * plpgsql_exec_function Called by the call handler for
+ * function execution.
+ * ----------
+ */
+Datum plpgsql_exec_function(PLpgSQL_function *func,
+ FmgrValues *args, bool *isNull)
+{
+ PLpgSQL_execstate estate;
+ int i;
+ sigjmp_buf save_restart;
+ PLpgSQL_function *save_efunc;
+ PLpgSQL_stmt *save_estmt;
+ char *save_etext;
+
+ /* ----------
+ * Setup debug error info and catch elog()
+ * ----------
+ */
+ save_efunc = error_info_func;
+ save_estmt = error_info_stmt;
+ save_etext = error_info_text;
+
+ error_info_func = func;
+ error_info_stmt = NULL;
+ error_info_text = "while initialization of execution state";
+
+ memcpy(&save_restart, &Warn_restart, sizeof(save_restart));
+ if (sigsetjmp(Warn_restart, 1) != 0) {
+ memcpy(&Warn_restart, &save_restart, sizeof(Warn_restart));
+
+ /* ----------
+ * If we are the first of cascaded error catchings,
+ * print where this happened
+ * ----------
+ */
+ if (error_info_func != NULL) {
+ elog(DEBUG, "Last error occured while executing PL/pgSQL function %s",
+ error_info_func->fn_name);
+ if (error_info_stmt != NULL) {
+ char *stmttype;
+ switch (error_info_stmt->cmd_type) {
+ case PLPGSQL_STMT_BLOCK:
+ stmttype = "blocks variable initialization";
+ break;
+ case PLPGSQL_STMT_ASSIGN:
+ stmttype = "assignment";
+ break;
+ case PLPGSQL_STMT_IF:
+ stmttype = "if";
+ break;
+ case PLPGSQL_STMT_LOOP:
+ stmttype = "loop";
+ break;
+ case PLPGSQL_STMT_WHILE:
+ stmttype = "while";
+ break;
+ case PLPGSQL_STMT_FORI:
+ stmttype = "for with integer loopvar";
+ break;
+ case PLPGSQL_STMT_FORS:
+ stmttype = "for over select rows";
+ break;
+ case PLPGSQL_STMT_SELECT:
+ stmttype = "select into variables";
+ break;
+ case PLPGSQL_STMT_EXIT:
+ stmttype = "exit";
+ break;
+ case PLPGSQL_STMT_RETURN:
+ stmttype = "return";
+ break;
+ case PLPGSQL_STMT_RAISE:
+ stmttype = "raise";
+ break;
+ case PLPGSQL_STMT_EXECSQL:
+ stmttype = "SQL statement";
+ break;
+ default:
+ stmttype = "unknown";
+ break;
+ }
+ elog(DEBUG, "line %d at %s", error_info_stmt->lineno,
+ stmttype);
+ } else {
+ if (error_info_text != NULL) {
+ elog(DEBUG, "%s", error_info_text);
+ } else {
+ elog(DEBUG, "no more error information available");
+ }
+ }
+
+ error_info_func = NULL;
+ error_info_stmt = NULL;
+ error_info_text = NULL;
+ }
+
+ siglongjmp(Warn_restart, 1);
+ }
+
+
+ /* ----------
+ * Setup the execution state
+ * ----------
+ */
+ estate.retval = 0;
+ estate.retisnull = false;
+ estate.rettype = InvalidOid;
+ estate.retistuple = func->fn_retistuple;
+ estate.retisset = func->fn_retset;
+ estate.exitlabel = NULL;
+
+ estate.found_varno = func->found_varno;
+ estate.ndatums = func->ndatums;
+ estate.datums = palloc(sizeof(PLpgSQL_datum *) * estate.ndatums);
+
+ /* ----------
+ * Make local execution copies of all the datums
+ * ----------
+ */
+ for (i = 0; i < func->ndatums; i++) {
+ switch(func->datums[i]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ estate.datums[i] = (PLpgSQL_datum *)
+ copy_var((PLpgSQL_var *)(func->datums[i]));
+ break;
+
+ case PLPGSQL_DTYPE_REC:
+ estate.datums[i] = (PLpgSQL_datum *)
+ copy_rec((PLpgSQL_rec *)(func->datums[i]));
+ break;
+
+ case PLPGSQL_DTYPE_ROW:
+ case PLPGSQL_DTYPE_RECFIELD:
+ estate.datums[i] = func->datums[i];
+ break;
+
+ default:
+ elog(ERROR, "unknown dtype %d in plpgsql_exec_function()",
+ func->datums[i]->dtype);
+ }
+ }
+
+ /* ----------
+ * Put the actual call argument values into the variables
+ * ----------
+ */
+ error_info_text = "while putting call arguments to local variables";
+ for (i = 0; i < func->fn_nargs; i++) {
+ int n = func->fn_argvarnos[i];
+ switch(estate.datums[n]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ {
+ PLpgSQL_var *var = (PLpgSQL_var *)estate.datums[n];
+ var->value = (Datum)(args->data[i]);
+ var->isnull = *isNull;
+ var->shouldfree = false;
+ }
+ break;
+
+ case PLPGSQL_DTYPE_ROW:
+ {
+ HeapTuple tup;
+ TupleDesc tupdesc;
+ PLpgSQL_row *row = (PLpgSQL_row *)estate.datums[n];
+
+ tup = ((TupleTableSlot *)(args->data[i]))->val;
+ tupdesc = ((TupleTableSlot *)(args->data[i]))->ttc_tupleDescriptor;
+
+ exec_move_row(&estate, NULL, row, tup, tupdesc);
+ }
+ break;
+
+ default:
+ elog(ERROR, "unknown dtype %d in plpgsql_exec_function()",
+ func->datums[i]->dtype);
+ }
+ }
+
+ /* ----------
+ * Initialize the other variables to NULL values for now.
+ * The default values are set when the blocks are entered.
+ * ----------
+ */
+ error_info_text = "while initializing local variables to NULL";
+ for (i = estate.found_varno; i < estate.ndatums; i++) {
+ switch(estate.datums[i]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ {
+ PLpgSQL_var *var = (PLpgSQL_var *)estate.datums[i];
+ var->value = 0;
+ var->isnull = true;
+ var->shouldfree = false;
+ }
+ break;
+
+ case PLPGSQL_DTYPE_ROW:
+ case PLPGSQL_DTYPE_REC:
+ case PLPGSQL_DTYPE_RECFIELD:
+ break;
+
+ default:
+ elog(ERROR, "unknown dtype %d in plpgsql_exec_function()",
+ func->datums[i]->dtype);
+ }
+ }
+
+ /* ----------
+ * Set the magic variable FOUND to false
+ * ----------
+ */
+ exec_set_found(&estate, false);
+
+ /* ----------
+ * Now call the toplevel block of statements
+ * ----------
+ */
+ error_info_text = NULL;
+ error_info_stmt = (PLpgSQL_stmt *)(func->action);
+ if (exec_stmt_block(&estate, func->action) != PLPGSQL_RC_RETURN) {
+ error_info_stmt = NULL;
+ error_info_text = "at END of toplevel PL block";
+ elog(ERROR, "control reaches end of function without RETURN");
+ }
+
+ /* ----------
+ * We got a return value - process it
+ * ----------
+ */
+ error_info_stmt = NULL;
+ error_info_text = "while casting return value to functions return type";
+
+ *isNull = estate.retisnull;
+
+ if (!estate.retistuple) {
+ estate.retval = exec_cast_value(estate.retval, estate.rettype,
+ func->fn_rettype, &(func->fn_retinput), -1,
+ isNull);
+
+ /* ----------
+ * If the functions return type isn't by value,
+ * copy the value into upper executor memory context.
+ * ----------
+ */
+ if (!*isNull && !func->fn_retbyval) {
+ int len;
+ Datum tmp;
+
+ if (func->fn_rettyplen < 0) {
+ len = VARSIZE(estate.retval);
+ } else {
+ len = func->fn_rettyplen;
+ }
+
+ tmp = (Datum)SPI_palloc(len);
+ memcpy((void *)tmp, (void *)estate.retval, len);
+ estate.retval = tmp;
+ }
+ }
+
+ /* ----------
+ * Restore the previous error info and elog() jump target
+ * ----------
+ */
+ error_info_func = save_efunc;
+ error_info_stmt = save_estmt;
+ error_info_text = save_etext;
+ memcpy(&Warn_restart, &save_restart, sizeof(Warn_restart));
+
+ /* ----------
+ * Return the functions result
+ * ----------
+ */
+ return estate.retval;
+}
+
+
+/* ----------
+ * plpgsql_exec_trigger Called by the call handler for
+ * trigger execution.
+ * ----------
+ */
+HeapTuple plpgsql_exec_trigger(PLpgSQL_function *func,
+ TriggerData *trigdata)
+{
+ PLpgSQL_execstate estate;
+ int i;
+ sigjmp_buf save_restart;
+ PLpgSQL_function *save_efunc;
+ PLpgSQL_stmt *save_estmt;
+ char *save_etext;
+ PLpgSQL_rec *rec_new;
+ PLpgSQL_rec *rec_old;
+ PLpgSQL_var *var;
+ HeapTuple rettup;
+
+ /* ----------
+ * Setup debug error info and catch elog()
+ * ----------
+ */
+ save_efunc = error_info_func;
+ save_estmt = error_info_stmt;
+ save_etext = error_info_text;
+
+ error_info_func = func;
+ error_info_stmt = NULL;
+ error_info_text = "while initialization of execution state";
+
+ memcpy(&save_restart, &Warn_restart, sizeof(save_restart));
+ if (sigsetjmp(Warn_restart, 1) != 0) {
+ memcpy(&Warn_restart, &save_restart, sizeof(Warn_restart));
+
+ /* ----------
+ * If we are the first of cascaded error catchings,
+ * print where this happened
+ * ----------
+ */
+ if (error_info_func != NULL) {
+ elog(DEBUG, "Last error occured while executing PL/pgSQL function %s",
+ error_info_func->fn_name);
+ if (error_info_stmt != NULL) {
+ char *stmttype;
+ switch (error_info_stmt->cmd_type) {
+ case PLPGSQL_STMT_BLOCK:
+ stmttype = "blocks variable initialization";
+ break;
+ case PLPGSQL_STMT_ASSIGN:
+ stmttype = "assignment";
+ break;
+ case PLPGSQL_STMT_IF:
+ stmttype = "if";
+ break;
+ case PLPGSQL_STMT_LOOP:
+ stmttype = "loop";
+ break;
+ case PLPGSQL_STMT_WHILE:
+ stmttype = "while";
+ break;
+ case PLPGSQL_STMT_FORI:
+ stmttype = "for with integer loopvar";
+ break;
+ case PLPGSQL_STMT_FORS:
+ stmttype = "for over select rows";
+ break;
+ case PLPGSQL_STMT_SELECT:
+ stmttype = "select into variables";
+ break;
+ case PLPGSQL_STMT_EXIT:
+ stmttype = "exit";
+ break;
+ case PLPGSQL_STMT_RETURN:
+ stmttype = "return";
+ break;
+ case PLPGSQL_STMT_RAISE:
+ stmttype = "raise";
+ break;
+ case PLPGSQL_STMT_EXECSQL:
+ stmttype = "SQL statement";
+ break;
+ default:
+ stmttype = "unknown";
+ break;
+ }
+ elog(DEBUG, "line %d at %s", error_info_stmt->lineno,
+ stmttype);
+ } else {
+ if (error_info_text != NULL) {
+ elog(DEBUG, "%s", error_info_text);
+ } else {
+ elog(DEBUG, "no more error information available");
+ }
+ }
+
+ error_info_func = NULL;
+ error_info_stmt = NULL;
+ error_info_text = NULL;
+ }
+
+ siglongjmp(Warn_restart, 1);
+ }
+
+
+ /* ----------
+ * Setup the execution state
+ * ----------
+ */
+ estate.retval = 0;
+ estate.retisnull = false;
+ estate.rettype = InvalidOid;
+ estate.retistuple = func->fn_retistuple;
+ estate.retisset = func->fn_retset;
+ estate.exitlabel = NULL;
+
+ estate.found_varno = func->found_varno;
+ estate.ndatums = func->ndatums;
+ estate.datums = palloc(sizeof(PLpgSQL_datum *) * estate.ndatums);
+
+ /* ----------
+ * Make local execution copies of all the datums
+ * ----------
+ */
+ for (i = 0; i < func->ndatums; i++) {
+ switch(func->datums[i]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ estate.datums[i] = (PLpgSQL_datum *)
+ copy_var((PLpgSQL_var *)(func->datums[i]));
+ break;
+
+ case PLPGSQL_DTYPE_REC:
+ estate.datums[i] = (PLpgSQL_datum *)
+ copy_rec((PLpgSQL_rec *)(func->datums[i]));
+ break;
+
+ case PLPGSQL_DTYPE_ROW:
+ case PLPGSQL_DTYPE_RECFIELD:
+ case PLPGSQL_DTYPE_TRIGARG:
+ estate.datums[i] = func->datums[i];
+ break;
+
+ default:
+ elog(ERROR, "unknown dtype %d in plpgsql_exec_function()",
+ func->datums[i]->dtype);
+ }
+ }
+
+ /* ----------
+ * Put the trig and new tuples into the records
+ * and set the tg_op variable
+ * ----------
+ */
+ rec_new = (PLpgSQL_rec *)(estate.datums[func->new_varno]);
+ rec_old = (PLpgSQL_rec *)(estate.datums[func->old_varno]);
+ var = (PLpgSQL_var *)(estate.datums[func->tg_op_varno]);
+ var->isnull = false;
+
+ if (TRIGGER_FIRED_BY_INSERT(trigdata->tg_event)) {
+ rec_new->tup = trigdata->tg_trigtuple;
+ rec_new->tupdesc = trigdata->tg_relation->rd_att;
+ rec_old->tup = NULL;
+ rec_old->tupdesc = NULL;
+ var->value = (Datum)textin("INSERT");
+ } else
+ if (TRIGGER_FIRED_BY_UPDATE(trigdata->tg_event)) {
+ rec_new->tup = trigdata->tg_newtuple;
+ rec_new->tupdesc = trigdata->tg_relation->rd_att;
+ rec_old->tup = trigdata->tg_trigtuple;
+ rec_old->tupdesc = trigdata->tg_relation->rd_att;
+ var->value = (Datum)textin("UPDATE");
+ } else
+ if (TRIGGER_FIRED_BY_DELETE(trigdata->tg_event)) {
+ rec_new->tup = NULL;
+ rec_new->tupdesc = NULL;
+ rec_old->tup = trigdata->tg_trigtuple;
+ rec_old->tupdesc = trigdata->tg_relation->rd_att;
+ var->value = (Datum)textin("DELETE");
+ } else {
+ rec_new->tup = NULL;
+ rec_new->tupdesc = NULL;
+ var->value = (Datum)textin("UNKNOWN");
+ }
+
+ /* ----------
+ * Fill all the other special tg_ variables
+ * ----------
+ */
+ var = (PLpgSQL_var *)(estate.datums[func->tg_name_varno]);
+ var->isnull = false;
+ var->value = (Datum)namein(trigdata->tg_trigger->tgname);
+
+ var = (PLpgSQL_var *)(estate.datums[func->tg_when_varno]);
+ var->isnull = false;
+ if (TRIGGER_FIRED_BEFORE(trigdata->tg_event)) {
+ var->value = (Datum)textin("BEFORE");
+ } else
+ if (TRIGGER_FIRED_AFTER(trigdata->tg_event)) {
+ var->value = (Datum)textin("AFTER");
+ } else {
+ var->value = (Datum)textin("UNKNOWN");
+ }
+
+ var = (PLpgSQL_var *)(estate.datums[func->tg_level_varno]);
+ var->isnull = false;
+ if (TRIGGER_FIRED_FOR_ROW(trigdata->tg_event)) {
+ var->value = (Datum)textin("ROW");
+ } else
+ if (TRIGGER_FIRED_FOR_STATEMENT(trigdata->tg_event)) {
+ var->value = (Datum)textin("STATEMENT");
+ } else {
+ var->value = (Datum)textin("UNKNOWN");
+ }
+
+ var = (PLpgSQL_var *)(estate.datums[func->tg_relid_varno]);
+ var->isnull = false;
+ var->value = (Datum)(trigdata->tg_relation->rd_id);
+
+ var = (PLpgSQL_var *)(estate.datums[func->tg_relname_varno]);
+ var->isnull = false;
+ var->value = (Datum)namein(nameout(&(trigdata->tg_relation->rd_rel->relname)));
+
+ var = (PLpgSQL_var *)(estate.datums[func->tg_nargs_varno]);
+ var->isnull = false;
+ var->value = (Datum)(trigdata->tg_trigger->tgnargs);
+
+ /* ----------
+ * Put the actual call argument values into the special
+ * execution state variables
+ * ----------
+ */
+ error_info_text = "while putting call arguments to local variables";
+ estate.trig_nargs = trigdata->tg_trigger->tgnargs;
+ if (estate.trig_nargs == 0) {
+ estate.trig_argv = NULL;
+ } else {
+ estate.trig_argv = palloc(sizeof(Datum) * estate.trig_nargs);
+ for (i = 0; i < trigdata->tg_trigger->tgnargs; i++) {
+ estate.trig_argv[i] = (Datum)textin(trigdata->tg_trigger->tgargs[i]);
+ }
+ }
+
+ /* ----------
+ * Initialize the other variables to NULL values for now.
+ * The default values are set when the blocks are entered.
+ * ----------
+ */
+ error_info_text = "while initializing local variables to NULL";
+ for (i = estate.found_varno; i < estate.ndatums; i++) {
+ switch(estate.datums[i]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ {
+ PLpgSQL_var *var = (PLpgSQL_var *)estate.datums[i];
+ var->value = 0;
+ var->isnull = true;
+ var->shouldfree = false;
+ }
+ break;
+
+ case PLPGSQL_DTYPE_ROW:
+ case PLPGSQL_DTYPE_REC:
+ case PLPGSQL_DTYPE_RECFIELD:
+ case PLPGSQL_DTYPE_TRIGARG:
+ break;
+
+ default:
+ elog(ERROR, "unknown dtype %d in plpgsql_exec_trigger()",
+ func->datums[i]->dtype);
+ }
+ }
+
+ /* ----------
+ * Set the magic variable FOUND to false
+ * ----------
+ */
+ exec_set_found(&estate, false);
+
+ /* ----------
+ * Now call the toplevel block of statements
+ * ----------
+ */
+ error_info_text = NULL;
+ error_info_stmt = (PLpgSQL_stmt *)(func->action);
+ if (exec_stmt_block(&estate, func->action) != PLPGSQL_RC_RETURN) {
+ error_info_stmt = NULL;
+ error_info_text = "at END of toplevel PL block";
+ elog(ERROR, "control reaches end of trigger procedure without RETURN");
+ }
+
+ /* ----------
+ * Check that the returned tuple structure has the same attributes,
+ * the relation that fired the trigger has.
+ *
+ * XXX This way it is possible, that the trigger returns a tuple
+ * where attributes don't have the correct atttypmod's length.
+ * It's up to the trigger's programmer to ensure that this
+ * doesn't happen. Jan
+ * ----------
+ */
+ if (estate.retisnull) {
+ rettup = NULL;
+ } else {
+ TupleDesc td1 = trigdata->tg_relation->rd_att;
+ TupleDesc td2 = estate.rettupdesc;
+ int i;
+
+ if (td1->natts != td2->natts) {
+ elog(ERROR, "returned tuple structure doesn't match table of trigger event");
+ }
+ for (i = 1; i <= td1->natts; i++) {
+ if (SPI_gettypeid(td1, i) != SPI_gettypeid(td2, i)) {
+ elog(ERROR, "returned tuple structure doesn't match table of trigger event");
+ }
+ }
+
+ rettup = SPI_copytuple((HeapTuple)(estate.retval));
+ }
+
+ /* ----------
+ * Restore the previous error info and elog() jump target
+ * ----------
+ */
+ error_info_func = save_efunc;
+ error_info_stmt = save_estmt;
+ error_info_text = save_etext;
+ memcpy(&Warn_restart, &save_restart, sizeof(Warn_restart));
+
+ /* ----------
+ * Return the triggers result
+ * ----------
+ */
+ return rettup;
+}
+
+
+/* ----------
+ * Support functions for copying local execution variables
+ * ----------
+ */
+static PLpgSQL_var *copy_var(PLpgSQL_var *var)
+{
+ PLpgSQL_var *new = palloc(sizeof(PLpgSQL_var));
+ memcpy(new, var, sizeof(PLpgSQL_var));
+
+ return new;
+}
+
+
+static PLpgSQL_rec *copy_rec(PLpgSQL_rec *rec)
+{
+ PLpgSQL_rec *new = palloc(sizeof(PLpgSQL_rec));
+ memcpy(new, rec, sizeof(PLpgSQL_rec));
+
+ return new;
+}
+
+
+/* ----------
+ * exec_stmt_block Execute a block of statements
+ * ----------
+ */
+static int exec_stmt_block(PLpgSQL_execstate *estate, PLpgSQL_stmt_block *block)
+{
+ int rc;
+ int i;
+ int n;
+
+ /* ----------
+ * First initialize all variables declared in this block
+ * ----------
+ */
+ for (i = 0; i < block->n_initvars; i++) {
+ n = block->initvarnos[i];
+
+ switch (estate->datums[n]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ {
+ PLpgSQL_var *var = (PLpgSQL_var *)(estate->datums[n]);
+
+ if (!var->isconst || var->isnull) {
+ if (var->default_val == NULL) {
+ var->value = (Datum)0;
+ var->isnull = true;
+ if (var->notnull) {
+ elog(ERROR, "variable '%s' declared NOT NULL cannot default to NULL", var->refname);
+ }
+ } else {
+ exec_assign_expr(estate, (PLpgSQL_datum *)var,
+ var->default_val);
+ }
+ }
+ }
+ break;
+
+ case PLPGSQL_DTYPE_REC:
+ {
+ PLpgSQL_rec *rec = (PLpgSQL_rec *)(estate->datums[n]);
+
+ rec->tup = NULL;
+ rec->tupdesc = NULL;
+ }
+ break;
+
+ case PLPGSQL_DTYPE_RECFIELD:
+ break;
+
+ default:
+ elog(ERROR, "unknown dtype %d in exec_stmt_block()", estate->datums[n]->dtype);
+ }
+
+ }
+
+ /* ----------
+ * Execute the statements in the block's body
+ * ----------
+ */
+ rc = exec_stmts(estate, block->body);
+
+ /* ----------
+ * Handle the return code.
+ * ----------
+ */
+ switch(rc) {
+ case PLPGSQL_RC_OK:
+ return PLPGSQL_RC_OK;
+
+ case PLPGSQL_RC_EXIT:
+ if (estate->exitlabel == NULL) {
+ return PLPGSQL_RC_OK;
+ }
+ if (block->label == NULL) {
+ return PLPGSQL_RC_EXIT;
+ }
+ if (strcmp(block->label, estate->exitlabel)) {
+ return PLPGSQL_RC_EXIT;
+ }
+ estate->exitlabel = NULL;
+ return PLPGSQL_RC_OK;
+
+ case PLPGSQL_RC_RETURN:
+ return PLPGSQL_RC_RETURN;
+
+ default:
+ elog(ERROR, "unknown rc %d from exec_stmt()", rc);
+ }
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmts Iterate over a list of statements
+ * as long as their return code is OK
+ * ----------
+ */
+static int exec_stmts(PLpgSQL_execstate *estate, PLpgSQL_stmts *stmts)
+{
+ int rc;
+ int i;
+
+ for (i = 0; i < stmts->stmts_used; i++) {
+ rc = exec_stmt(estate, (PLpgSQL_stmt *)(stmts->stmts[i]));
+ if (rc != PLPGSQL_RC_OK) {
+ return rc;
+ }
+ }
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmt Distribute one statement to the statements
+ * type specific execution function.
+ * ----------
+ */
+static int exec_stmt(PLpgSQL_execstate *estate, PLpgSQL_stmt *stmt)
+{
+ PLpgSQL_stmt *save_estmt;
+ int rc = -1;
+
+ save_estmt = error_info_stmt;
+ error_info_stmt = stmt;
+
+ switch (stmt->cmd_type) {
+ case PLPGSQL_STMT_BLOCK:
+ rc = exec_stmt_block(estate, (PLpgSQL_stmt_block *)stmt);
+ break;
+
+ case PLPGSQL_STMT_ASSIGN:
+ rc = exec_stmt_assign(estate, (PLpgSQL_stmt_assign *)stmt);
+ break;
+
+ case PLPGSQL_STMT_IF:
+ rc = exec_stmt_if(estate, (PLpgSQL_stmt_if *)stmt);
+ break;
+
+ case PLPGSQL_STMT_LOOP:
+ rc = exec_stmt_loop(estate, (PLpgSQL_stmt_loop *)stmt);
+ break;
+
+ case PLPGSQL_STMT_WHILE:
+ rc = exec_stmt_while(estate, (PLpgSQL_stmt_while *)stmt);
+ break;
+
+ case PLPGSQL_STMT_FORI:
+ rc = exec_stmt_fori(estate, (PLpgSQL_stmt_fori *)stmt);
+ break;
+
+ case PLPGSQL_STMT_FORS:
+ rc = exec_stmt_fors(estate, (PLpgSQL_stmt_fors *)stmt);
+ break;
+
+ case PLPGSQL_STMT_SELECT:
+ rc = exec_stmt_select(estate, (PLpgSQL_stmt_select *)stmt);
+ break;
+
+ case PLPGSQL_STMT_EXIT:
+ rc = exec_stmt_exit(estate, (PLpgSQL_stmt_exit *)stmt);
+ break;
+
+ case PLPGSQL_STMT_RETURN:
+ rc = exec_stmt_return(estate, (PLpgSQL_stmt_return *)stmt);
+ break;
+
+ case PLPGSQL_STMT_RAISE:
+ rc = exec_stmt_raise(estate, (PLpgSQL_stmt_raise *)stmt);
+ break;
+
+ case PLPGSQL_STMT_EXECSQL:
+ rc = exec_stmt_execsql(estate, (PLpgSQL_stmt_execsql *)stmt);
+ break;
+
+ default:
+ error_info_stmt = save_estmt;
+ elog(ERROR, "unknown cmdtype %d in exec_stmt",
+ stmt->cmd_type);
+ }
+
+ error_info_stmt = save_estmt;
+
+ return rc;
+}
+
+
+/* ----------
+ * exec_stmt_assign Evaluate an expression and
+ * put the result into a variable.
+ * ----------
+ */
+static int exec_stmt_assign(PLpgSQL_execstate *estate, PLpgSQL_stmt_assign *stmt)
+{
+ if (stmt->varno < 0) {
+ exec_assign_expr(estate, NULL, stmt->expr);
+ } else {
+ exec_assign_expr(estate, estate->datums[stmt->varno], stmt->expr);
+ }
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmt_if Evaluate a bool expression and
+ * execute the true or false body
+ * conditionally.
+ * ----------
+ */
+static int exec_stmt_if(PLpgSQL_execstate *estate, PLpgSQL_stmt_if *stmt)
+{
+ Datum value;
+ Oid valtype;
+ bool isnull = false;
+
+ value = exec_eval_expr(estate, stmt->cond, &isnull, &valtype);
+
+ if (value) {
+ if (stmt->true_body != NULL) {
+ return exec_stmts(estate, stmt->true_body);
+ }
+ } else {
+ if (stmt->false_body != NULL) {
+ return exec_stmts(estate, stmt->false_body);
+ }
+ }
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmt_loop Loop over statements until
+ * an exit occurs.
+ * ----------
+ */
+static int exec_stmt_loop(PLpgSQL_execstate *estate, PLpgSQL_stmt_loop *stmt)
+{
+ int rc;
+
+ for (;;) {
+ rc = exec_stmts(estate, stmt->body);
+
+ switch (rc) {
+ case PLPGSQL_RC_OK:
+ break;
+
+ case PLPGSQL_RC_EXIT:
+ if (estate->exitlabel == NULL) {
+ return PLPGSQL_RC_OK;
+ }
+ if (stmt->label == NULL) {
+ return PLPGSQL_RC_EXIT;
+ }
+ if (strcmp(stmt->label, estate->exitlabel)) {
+ return PLPGSQL_RC_EXIT;
+ }
+ estate->exitlabel = NULL;
+ return PLPGSQL_RC_OK;
+
+ case PLPGSQL_RC_RETURN:
+ return PLPGSQL_RC_RETURN;
+
+ default:
+ elog(ERROR, "unknown rc %d from exec_stmts()", rc);
+ }
+ }
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmt_while Loop over statements as long
+ * as an expression evaluates to
+ * true or an exit occurs.
+ * ----------
+ */
+static int exec_stmt_while(PLpgSQL_execstate *estate, PLpgSQL_stmt_while *stmt)
+{
+ Datum value;
+ Oid valtype;
+ bool isnull = false;
+ int rc;
+
+ for (;;) {
+ value = exec_eval_expr(estate, stmt->cond, &isnull, &valtype);
+ if (!value) {
+ break;
+ }
+
+ rc = exec_stmts(estate, stmt->body);
+
+ switch (rc) {
+ case PLPGSQL_RC_OK:
+ break;
+
+ case PLPGSQL_RC_EXIT:
+ if (estate->exitlabel == NULL) {
+ return PLPGSQL_RC_OK;
+ }
+ if (stmt->label == NULL) {
+ return PLPGSQL_RC_EXIT;
+ }
+ if (strcmp(stmt->label, estate->exitlabel)) {
+ return PLPGSQL_RC_EXIT;
+ }
+ estate->exitlabel = NULL;
+ return PLPGSQL_RC_OK;
+
+ case PLPGSQL_RC_RETURN:
+ return PLPGSQL_RC_RETURN;
+
+ default:
+ elog(ERROR, "unknown rc %d from exec_stmts()", rc);
+ }
+ }
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmt_fori Iterate an integer variable
+ * from a lower to an upper value.
+ * Loop can be left with exit.
+ * ----------
+ */
+static int exec_stmt_fori(PLpgSQL_execstate *estate, PLpgSQL_stmt_fori *stmt)
+{
+ PLpgSQL_var *var;
+ Datum value;
+ Oid valtype;
+ bool isnull = false;
+ int rc;
+
+ /* ----------
+ * Get the value of the lower bound into the loop var
+ * ----------
+ */
+ value = exec_eval_expr(estate, stmt->lower, &isnull, &valtype);
+ var = (PLpgSQL_var *)(estate->datums[stmt->var->varno]);
+
+ value = exec_cast_value(value, valtype, var->datatype->typoid,
+ &(var->datatype->typinput),
+ var->datatype->atttypmod, &isnull);
+ if (isnull) {
+ elog(ERROR, "lower bound of FOR loop cannot be NULL");
+ }
+ var->value = value;
+ var->isnull = false;
+
+ /* ----------
+ * Get the value of the upper bound
+ * ----------
+ */
+ value = exec_eval_expr(estate, stmt->upper, &isnull, &valtype);
+ value = exec_cast_value(value, valtype, var->datatype->typoid,
+ &(var->datatype->typinput),
+ var->datatype->atttypmod, &isnull);
+ if (isnull) {
+ elog(ERROR, "upper bound of FOR loop cannot be NULL");
+ }
+
+ /* ----------
+ * Now do the loop
+ * ----------
+ */
+ exec_set_found(estate, false);
+ for (;;) {
+ /* ----------
+ * Check bounds
+ * ----------
+ */
+ if (stmt->reverse) {
+ if ((int4)(var->value) < (int4)value) {
+ break;
+ }
+ } else {
+ if ((int4)(var->value) > (int4)value) {
+ break;
+ }
+ }
+ exec_set_found(estate, true);
+
+ /* ----------
+ * Execute the statements
+ * ----------
+ */
+ rc = exec_stmts(estate, stmt->body);
+
+ /* ----------
+ * Check returncode
+ * ----------
+ */
+ switch (rc) {
+ case PLPGSQL_RC_OK:
+ break;
+
+ case PLPGSQL_RC_EXIT:
+ if (estate->exitlabel == NULL) {
+ return PLPGSQL_RC_OK;
+ }
+ if (stmt->label == NULL) {
+ return PLPGSQL_RC_EXIT;
+ }
+ if (strcmp(stmt->label, estate->exitlabel)) {
+ return PLPGSQL_RC_EXIT;
+ }
+ estate->exitlabel = NULL;
+ return PLPGSQL_RC_OK;
+
+ case PLPGSQL_RC_RETURN:
+ return PLPGSQL_RC_RETURN;
+
+ default:
+ elog(ERROR, "unknown rc %d from exec_stmts()", rc);
+ }
+
+ /* ----------
+ * Increase/decrease loop var
+ * ----------
+ */
+ if (stmt->reverse) {
+ ((int4)(var->value))--;
+ } else {
+ ((int4)(var->value))++;
+ }
+ }
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmt_fors Execute a query, assign each
+ * tuple to a record or row and
+ * execute a group of statements
+ * for it.
+ * ----------
+ */
+static int exec_stmt_fors(PLpgSQL_execstate *estate, PLpgSQL_stmt_fors *stmt)
+{
+ PLpgSQL_rec *rec = NULL;
+ PLpgSQL_row *row = NULL;
+ SPITupleTable *tuptab;
+ int rc;
+ int i;
+ int n;
+
+ /* ----------
+ * Initialize the global found variable to false
+ * ----------
+ */
+ exec_set_found(estate, false);
+
+ /* ----------
+ * Determine if we assign to a record or a row
+ * ----------
+ */
+ if (stmt->rec != NULL) {
+ rec = (PLpgSQL_rec *)(estate->datums[stmt->rec->recno]);
+ } else {
+ if (stmt->row != NULL) {
+ row = (PLpgSQL_row *)(estate->datums[stmt->row->rowno]);
+ } else {
+ elog(ERROR, "unsupported target in exec_stmt_fors()");
+ }
+ }
+
+ /* ----------
+ * Run the query
+ * ----------
+ */
+ exec_run_select(estate, stmt->query, 0);
+ n = SPI_processed;
+
+ /* ----------
+ * If the query didn't return any row, set the target
+ * to NULL and return.
+ * ----------
+ */
+ if (n == 0) {
+ exec_move_row(estate, rec, row, NULL, NULL);
+ return PLPGSQL_RC_OK;
+ }
+
+ /* ----------
+ * There are tuples, so set found to true
+ * ----------
+ */
+ exec_set_found(estate, true);
+
+ /* ----------
+ * Now do the loop
+ * ----------
+ */
+ tuptab = SPI_tuptable;
+ SPI_tuptable = NULL;
+
+ for (i = 0; i < n; i++) {
+ /* ----------
+ * Assign the tuple to the target
+ * ----------
+ */
+ exec_move_row(estate, rec, row, tuptab->vals[i], tuptab->tupdesc);
+
+ /* ----------
+ * Execute the statements
+ * ----------
+ */
+ rc = exec_stmts(estate, stmt->body);
+
+ /* ----------
+ * Check returncode
+ * ----------
+ */
+ switch (rc) {
+ case PLPGSQL_RC_OK:
+ break;
+
+ case PLPGSQL_RC_EXIT:
+ if (estate->exitlabel == NULL) {
+ return PLPGSQL_RC_OK;
+ }
+ if (stmt->label == NULL) {
+ return PLPGSQL_RC_EXIT;
+ }
+ if (strcmp(stmt->label, estate->exitlabel)) {
+ return PLPGSQL_RC_EXIT;
+ }
+ estate->exitlabel = NULL;
+ return PLPGSQL_RC_OK;
+
+ case PLPGSQL_RC_RETURN:
+ return PLPGSQL_RC_RETURN;
+
+ default:
+ elog(ERROR, "unknown rc %d from exec_stmts()", rc);
+ }
+ }
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmt_select Run a query and assign the first
+ * row to a record or rowtype.
+ * ----------
+ */
+static int exec_stmt_select(PLpgSQL_execstate *estate, PLpgSQL_stmt_select *stmt)
+{
+ PLpgSQL_rec *rec = NULL;
+ PLpgSQL_row *row = NULL;
+ SPITupleTable *tuptab;
+ int n;
+
+ /* ----------
+ * Initialize the global found variable to false
+ * ----------
+ */
+ exec_set_found(estate, false);
+
+ /* ----------
+ * Determine if we assign to a record or a row
+ * ----------
+ */
+ if (stmt->rec != NULL) {
+ rec = (PLpgSQL_rec *)(estate->datums[stmt->rec->recno]);
+ } else {
+ if (stmt->row != NULL) {
+ row = (PLpgSQL_row *)(estate->datums[stmt->row->rowno]);
+ } else {
+ elog(ERROR, "unsupported target in exec_stmt_select()");
+ }
+ }
+
+ /* ----------
+ * Run the query
+ * ----------
+ */
+ exec_run_select(estate, stmt->query, 1);
+ n = SPI_processed;
+
+ /* ----------
+ * If the query didn't return any row, set the target
+ * to NULL and return.
+ * ----------
+ */
+ if (n == 0) {
+ exec_move_row(estate, rec, row, NULL, NULL);
+ return PLPGSQL_RC_OK;
+ }
+
+ /* ----------
+ * Put the result into the target and set found to true
+ * ----------
+ */
+ tuptab = SPI_tuptable;
+ SPI_tuptable = NULL;
+
+ exec_move_row(estate, rec, row, tuptab->vals[0], tuptab->tupdesc);
+
+ exec_set_found(estate, true);
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmt_exit Start exiting loop(s) or blocks
+ * ----------
+ */
+static int exec_stmt_exit(PLpgSQL_execstate *estate, PLpgSQL_stmt_exit *stmt)
+{
+ Datum value;
+ Oid valtype;
+ bool isnull = false;
+
+ /* ----------
+ * If the exit has a condition, check that it's true
+ * ----------
+ */
+ if (stmt->cond != NULL) {
+ value = exec_eval_expr(estate, stmt->cond, &isnull, &valtype);
+ if (!value) {
+ return PLPGSQL_RC_OK;
+ }
+ }
+
+ estate->exitlabel = stmt->label;
+ return PLPGSQL_RC_EXIT;
+}
+
+
+/* ----------
+ * exec_stmt_return Evaluate an expression and start
+ * returning from the function.
+ * ----------
+ */
+static int exec_stmt_return(PLpgSQL_execstate *estate, PLpgSQL_stmt_return *stmt)
+{
+ if (estate->retistuple) {
+ if (stmt->retrecno >= 0) {
+ PLpgSQL_rec *rec = (PLpgSQL_rec *)(estate->datums[stmt->retrecno]);
+
+ estate->retval = (Datum)(rec->tup);
+ estate->rettupdesc = rec->tupdesc;
+ estate->retisnull = !HeapTupleIsValid(rec->tup);
+
+ return PLPGSQL_RC_RETURN;
+ }
+
+ if (stmt->expr == NULL) {
+ estate->retval = (Datum)0;
+ estate->rettupdesc = NULL;
+ estate->retisnull = true;
+ } else {
+ exec_run_select(estate, stmt->expr, 1);
+ estate->retval = (Datum) SPI_copytuple(SPI_tuptable->vals[0]);
+ estate->rettupdesc = SPI_tuptable->tupdesc;
+ estate->retisnull = false;
+ }
+ return PLPGSQL_RC_RETURN;
+ }
+
+ estate->retval = exec_eval_expr(estate, stmt->expr,
+ &(estate->retisnull),
+ &(estate->rettype));
+
+ return PLPGSQL_RC_RETURN;
+}
+
+
+/* ----------
+ * exec_stmt_raise Build a message and throw it with
+ * elog()
+ * ----------
+ */
+static int exec_stmt_raise(PLpgSQL_execstate *estate, PLpgSQL_stmt_raise *stmt)
+{
+ HeapTuple typetup;
+ TypeTupleForm typeStruct;
+ FmgrInfo finfo_output;
+ char *extval;
+ int pidx = 0;
+ char c[2] = {0, 0};
+ char *cp;
+ PLpgSQL_dstring ds;
+ PLpgSQL_var *var;
+ PLpgSQL_rec *rec;
+ PLpgSQL_recfield *recfield;
+ int fno;
+
+ plpgsql_dstring_init(&ds);
+
+ for (cp = stmt->message; *cp; cp++) {
+ /* ----------
+ * Occurences of a single % are replaced by the next
+ * arguments external representation. Double %'s are
+ * left as is so elog() will also don't touch them.
+ * ----------
+ */
+ if ((c[0] = *cp) == '%') {
+ cp++;
+ if (*cp == '%') {
+ plpgsql_dstring_append(&ds, c);
+ plpgsql_dstring_append(&ds, c);
+ continue;
+ }
+ cp--;
+ if (pidx >= stmt->nparams) {
+ plpgsql_dstring_append(&ds, c);
+ plpgsql_dstring_append(&ds, c);
+ continue;
+ }
+ switch(estate->datums[stmt->params[pidx]]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ var = (PLpgSQL_var *)
+ (estate->datums[stmt->params[pidx]]);
+ if (var->isnull) {
+ extval = "<NULL>";
+ } else {
+ typetup = SearchSysCacheTuple(TYPOID,
+ ObjectIdGetDatum(var->datatype->typoid), 0, 0, 0);
+ if (!HeapTupleIsValid(typetup)) {
+ elog(ERROR, "cache lookup for type %d failed (1)", var->datatype->typoid);
+ }
+ typeStruct = (TypeTupleForm) GETSTRUCT(typetup);
+
+ fmgr_info(typeStruct->typoutput, &finfo_output);
+ extval = (char *)(*fmgr_faddr(&finfo_output))(var->value, &(var->isnull), var->datatype->atttypmod);
+ }
+ plpgsql_dstring_append(&ds, extval);
+ break;
+
+ case PLPGSQL_DTYPE_RECFIELD:
+ recfield = (PLpgSQL_recfield *)
+ (estate->datums[stmt->params[pidx]]);
+ rec = (PLpgSQL_rec *)
+ (estate->datums[recfield->recno]);
+ if (!HeapTupleIsValid(rec->tup)) {
+ extval = "<NULL>";
+ } else {
+ fno = SPI_fnumber(rec->tupdesc, recfield->fieldname);
+ if (fno == SPI_ERROR_NOATTRIBUTE) {
+ elog(ERROR, "record %s has no field %s", rec->refname, recfield->fieldname);
+ }
+ extval = SPI_getvalue(rec->tup, rec->tupdesc, fno);
+ }
+ plpgsql_dstring_append(&ds, extval);
+ break;
+
+ case PLPGSQL_DTYPE_TRIGARG:
+ {
+ PLpgSQL_trigarg *trigarg;
+ int value;
+ Oid valtype;
+ bool valisnull = false;
+
+ trigarg = (PLpgSQL_trigarg *)
+ (estate->datums[stmt->params[pidx]]);
+ value = (int)exec_eval_expr(estate, trigarg->argnum,
+ &valisnull, &valtype);
+ if (valisnull) {
+ extval = "<INDEX_IS_NULL>";
+ } else {
+ if (value < 0 || value >= estate->trig_nargs) {
+ extval = "<OUT_OF_RANGE>";
+ } else {
+ extval = textout((text *)(estate->trig_argv[value]));
+ }
+ }
+ plpgsql_dstring_append(&ds, extval);
+ }
+ break;
+
+ default:
+ c[0] = '?';
+ plpgsql_dstring_append(&ds, c);
+ break;
+ }
+ pidx++;
+ continue;
+ }
+
+ /* ----------
+ * Occurences of single ' are removed. double ' are reduced
+ * to single ones.
+ * ----------
+ */
+ if (*cp == '\'') {
+ cp++;
+ if (*cp == '\'') {
+ plpgsql_dstring_append(&ds, c);
+ } else {
+ cp--;
+ }
+ continue;
+ }
+ plpgsql_dstring_append(&ds, c);
+ }
+
+ /* ----------
+ * Now suppress debug info and throw the elog()
+ * ----------
+ */
+ if (stmt->elog_level == ERROR) {
+ error_info_func = NULL;
+ error_info_stmt = NULL;
+ error_info_text = NULL;
+ }
+ elog(stmt->elog_level, "%s", plpgsql_dstring_get(&ds));
+ plpgsql_dstring_free(&ds);
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_stmt_execsql Execute an SQL statement not
+ * returning any data.
+ * ----------
+ */
+static int exec_stmt_execsql(PLpgSQL_execstate *estate,
+ PLpgSQL_stmt_execsql *stmt)
+{
+ PLpgSQL_var *var;
+ PLpgSQL_rec *rec;
+ PLpgSQL_recfield *recfield;
+ PLpgSQL_trigarg *trigarg;
+ int tgargno;
+ Oid tgargoid;
+ int fno;
+ int i;
+ Datum *values;
+ char *nulls;
+ int rc;
+ PLpgSQL_expr *expr = stmt->sqlstmt;
+ bool isnull;
+
+ /* ----------
+ * On the first call for this expression generate the plan
+ * ----------
+ */
+ if (expr->plan == NULL) {
+ void *plan;
+ Oid *argtypes;
+
+ argtypes = malloc(sizeof(Oid *) * (expr->nparams + 1));
+
+ for (i = 0; i < expr->nparams; i++) {
+ switch (estate->datums[expr->params[i]]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ var = (PLpgSQL_var *)(estate->datums[expr->params[i]]);
+ argtypes[i] = var->datatype->typoid;
+ break;
+
+ case PLPGSQL_DTYPE_RECFIELD:
+ recfield = (PLpgSQL_recfield *)(estate->datums[expr->params[i]]);
+ rec = (PLpgSQL_rec *)(estate->datums[recfield->recno]);
+
+ if (!HeapTupleIsValid(rec->tup)) {
+ elog(ERROR, "record %s is unassigned yet", rec->refname);
+ }
+ fno = SPI_fnumber(rec->tupdesc, recfield->fieldname);
+ if (fno == SPI_ERROR_NOATTRIBUTE) {
+ elog(ERROR, "record %s has no field %s", rec->refname, recfield->fieldname);
+ }
+ argtypes[i] = SPI_gettypeid(rec->tupdesc, fno);
+ break;
+
+ case PLPGSQL_DTYPE_TRIGARG:
+ argtypes[i] = (Oid)TEXTOID;
+ break;
+
+ default:
+ elog(ERROR, "unknown parameter dtype %d in exec_stmt_execsql()", estate->datums[expr->params[i]]->dtype);
+ }
+ }
+
+ plan = SPI_prepare(expr->query, expr->nparams, argtypes);
+ if (plan == NULL) {
+ elog(ERROR, "SPI_prepare() failed on \"%s\"", expr->query);
+ }
+ expr->plan = SPI_saveplan(plan);
+ expr->plan_argtypes = argtypes;
+ }
+
+ /* ----------
+ * Now build up the values and nulls arguments for SPI_execp()
+ * ----------
+ */
+ values = palloc(sizeof(Datum) * (expr->nparams + 1));
+ nulls = palloc(expr->nparams + 1);
+
+ for (i = 0; i < expr->nparams; i++) {
+ switch (estate->datums[expr->params[i]]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ var = (PLpgSQL_var *)(estate->datums[expr->params[i]]);
+ values[i] = var->value;
+ if (var->isnull) {
+ nulls[i] = 'n';
+ } else {
+ nulls[i] = ' ';
+ }
+ break;
+
+ case PLPGSQL_DTYPE_RECFIELD:
+ recfield = (PLpgSQL_recfield *)(estate->datums[expr->params[i]]);
+ rec = (PLpgSQL_rec *)(estate->datums[recfield->recno]);
+
+ if (!HeapTupleIsValid(rec->tup)) {
+ elog(ERROR, "record %s is unassigned yet", rec->refname);
+ }
+ fno = SPI_fnumber(rec->tupdesc, recfield->fieldname);
+ if (fno == SPI_ERROR_NOATTRIBUTE) {
+ elog(ERROR, "record %s has no field %s", rec->refname, recfield->fieldname);
+ }
+
+ if (expr->plan_argtypes[i] != SPI_gettypeid(rec->tupdesc, fno)) {
+ elog(ERROR, "type of %s.%s doesn't match that when preparing the plan", rec->refname, recfield->fieldname);
+ }
+
+ values[i] = SPI_getbinval(rec->tup, rec->tupdesc, fno, &isnull);
+ if (isnull) {
+ nulls[i] = 'n';
+ } else {
+ nulls[i] = ' ';
+ }
+ break;
+
+ case PLPGSQL_DTYPE_TRIGARG:
+ trigarg = (PLpgSQL_trigarg *)(estate->datums[expr->params[i]]);
+ tgargno = (int)exec_eval_expr(estate, trigarg->argnum,
+ &isnull, &tgargoid);
+ if (isnull || tgargno < 0 || tgargno >= estate->trig_nargs) {
+ values[i] = 0;
+ nulls[i] = 'n';
+ } else {
+ values[i] = estate->trig_argv[tgargno];
+ nulls[i] = ' ';
+ }
+ break;
+
+ default:
+ elog(ERROR, "unknown parameter dtype %d in exec_stmt_execsql()", estate->datums[expr->params[i]]->dtype);
+ }
+ }
+ nulls[i] = '\0';
+
+ /* ----------
+ * Execute the plan
+ * ----------
+ */
+ rc = SPI_execp(expr->plan, values, nulls, 0);
+ switch(rc) {
+ case SPI_OK_UTILITY:
+ case SPI_OK_SELINTO:
+ case SPI_OK_INSERT:
+ case SPI_OK_DELETE:
+ case SPI_OK_UPDATE:
+ break;
+
+ case SPI_OK_SELECT:
+ elog(ERROR, "unexpected SELECT query in exec_stmt_execsql()");
+
+ default:
+ elog(ERROR, "error executing query \"%s\"",
+ expr->query);
+ }
+ pfree(values);
+ pfree(nulls);
+
+ return PLPGSQL_RC_OK;
+}
+
+
+/* ----------
+ * exec_assign_expr Put an expressions result into
+ * a variable.
+ * ----------
+ */
+static void exec_assign_expr(PLpgSQL_execstate *estate, PLpgSQL_datum *target,
+ PLpgSQL_expr *expr)
+{
+ Datum value;
+ Oid valtype;
+ bool isnull = false;
+
+ value = exec_eval_expr(estate, expr, &isnull, &valtype);
+ if (target != NULL) {
+ exec_assign_value(estate, target, value, valtype, &isnull);
+ }
+}
+
+
+/* ----------
+ * exec_assign_value Put a value into a target field
+ * ----------
+ */
+static void exec_assign_value(PLpgSQL_execstate *estate,
+ PLpgSQL_datum *target,
+ Datum value, Oid valtype, bool *isNull)
+{
+ PLpgSQL_var *var;
+ PLpgSQL_rec *rec;
+ PLpgSQL_recfield *recfield;
+ int fno;
+ int i;
+ int natts;
+ Datum *values;
+ char *nulls;
+ bool attisnull;
+ Oid atttype;
+ int4 atttypmod;
+ HeapTuple typetup;
+ TypeTupleForm typeStruct;
+ FmgrInfo finfo_input;
+
+ switch (target->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ /* ----------
+ * Target field is a variable - that's easy
+ * ----------
+ */
+ var = (PLpgSQL_var *)target;
+ var->value = exec_cast_value(value, valtype, var->datatype->typoid,
+ &(var->datatype->typinput),
+ var->datatype->atttypmod, isNull);
+
+ if (isNull && var->notnull) {
+ elog(ERROR, "NULL assignment to variable '%s' declared NOT NULL", var->refname);
+ }
+
+ var->isnull = *isNull;
+ break;
+
+ case PLPGSQL_DTYPE_RECFIELD:
+ /* ----------
+ * Target field is a record
+ * ----------
+ */
+ recfield = (PLpgSQL_recfield *)target;
+ rec = (PLpgSQL_rec *)(estate->datums[recfield->recno]);
+
+ /* ----------
+ * Check that there is already a tuple in the record.
+ * We need that because records don't have any predefined
+ * field structure.
+ * ----------
+ */
+ if (!HeapTupleIsValid(rec->tup)) {
+ elog(ERROR, "record %s is unassigned yet - don't know it's tuple structure", rec->refname);
+ }
+
+ /* ----------
+ * Get the number of the records field to change and the
+ * number of attributes in the tuple.
+ * ----------
+ */
+ fno = SPI_fnumber(rec->tupdesc, recfield->fieldname);
+ if (fno == SPI_ERROR_NOATTRIBUTE) {
+ elog(ERROR, "record %s has no field %s", rec->refname, recfield->fieldname);
+ }
+ fno--;
+ natts = rec->tupdesc->natts;
+
+ /* ----------
+ * We loop over the attributes of the rec's current tuple
+ * and collect the values in a Datum array along with the
+ * nulls information.
+ * ----------
+ */
+ values = palloc(sizeof(Datum) * natts);
+ nulls = palloc(natts + 1);
+
+ for (i = 0; i < natts; i++) {
+ /* ----------
+ * If this isn't the field we assign to, just use the
+ * value that's already in the tuple.
+ * ----------
+ */
+ if (i != fno) {
+ values[i] = SPI_getbinval(rec->tup, rec->tupdesc,
+ i + 1, &attisnull);
+ if (attisnull) {
+ nulls[i] = 'n';
+ } else {
+ nulls[i] = ' ';
+ }
+ continue;
+ }
+
+ /* ----------
+ * This is the field to change. Get it's type
+ * and cast the value we insert to that type.
+ * ----------
+ */
+ atttype = SPI_gettypeid(rec->tupdesc, i + 1);
+ atttypmod = rec->tupdesc->attrs[i]->atttypmod;
+ typetup = SearchSysCacheTuple(TYPOID,
+ ObjectIdGetDatum(atttype), 0, 0, 0);
+ if (!HeapTupleIsValid(typetup)) {
+ elog(ERROR, "cache lookup for type %d failed", atttype);
+ }
+ typeStruct = (TypeTupleForm) GETSTRUCT(typetup);
+ fmgr_info(typeStruct->typinput, &finfo_input);
+
+ attisnull = *isNull;
+ values[i] = exec_cast_value(value, valtype,
+ atttype, &finfo_input, atttypmod, &attisnull);
+ if (attisnull) {
+ nulls[i] = 'n';
+ } else {
+ nulls[i] = ' ';
+ }
+ }
+
+ /* ----------
+ * Now call heap_formtuple() to create a new tuple
+ * that replaces the old one in the record.
+ * ----------
+ */
+ nulls[i] = '\0';
+ rec->tup = heap_formtuple(rec->tupdesc, values, nulls);
+ pfree(values);
+ pfree(nulls);
+
+ break;
+
+ default:
+ elog(ERROR, "unknown dtype %d in exec_assign_value()",
+ target->dtype);
+ }
+}
+
+
+/* ----------
+ * exec_eval_expr Evaluate an expression and return
+ * the result Datum.
+ * ----------
+ */
+static Datum exec_eval_expr(PLpgSQL_execstate *estate,
+ PLpgSQL_expr *expr,
+ bool *isNull,
+ Oid *rettype)
+{
+ int rc;
+
+ rc = exec_run_select(estate, expr, 2);
+ if (rc != SPI_OK_SELECT) {
+ elog(ERROR, "query \"%s\" didn't return data", expr->query);
+ }
+
+ /* ----------
+ * If there are no rows selected, the result is NULL.
+ * ----------
+ */
+ if (SPI_processed == 0) {
+ *isNull = true;
+ return (Datum)0;
+ }
+
+ /* ----------
+ * Check that the expression returned one single Datum
+ * ----------
+ */
+ if (SPI_processed > 1) {
+ elog(ERROR, "query \"%s\" didn't return a single value", expr->query);
+ }
+ if (SPI_tuptable->tupdesc->natts != 1) {
+ elog(ERROR, "query \"%s\" didn't return a single value", expr->query);
+ }
+
+ /* ----------
+ * Return the result and it's type
+ * ----------
+ */
+ *rettype = SPI_gettypeid(SPI_tuptable->tupdesc, 1);
+ return SPI_getbinval(SPI_tuptable->vals[0], SPI_tuptable->tupdesc, 1, isNull);
+}
+
+
+/* ----------
+ * exec_run_select Execute a select query
+ * ----------
+ */
+static int exec_run_select(PLpgSQL_execstate *estate,
+ PLpgSQL_expr *expr, int maxtuples)
+{
+ PLpgSQL_var *var;
+ PLpgSQL_rec *rec;
+ PLpgSQL_recfield *recfield;
+ PLpgSQL_trigarg *trigarg;
+ int tgargno;
+ Oid tgargoid;
+ int i;
+ Datum *values;
+ char *nulls;
+ int rc;
+ int fno;
+ bool isnull;
+
+ /* ----------
+ * On the first call for this expression generate the plan
+ * ----------
+ */
+ if (expr->plan == NULL) {
+ void *plan;
+ Oid *argtypes;
+
+ /* ----------
+ * Setup the argtypes array
+ * ----------
+ */
+ argtypes = malloc(sizeof(Oid *) * (expr->nparams + 1));
+
+ for (i = 0; i < expr->nparams; i++) {
+ switch (estate->datums[expr->params[i]]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ var = (PLpgSQL_var *)(estate->datums[expr->params[i]]);
+ argtypes[i] = var->datatype->typoid;
+ break;
+
+ case PLPGSQL_DTYPE_RECFIELD:
+ recfield = (PLpgSQL_recfield *)(estate->datums[expr->params[i]]);
+ rec = (PLpgSQL_rec *)(estate->datums[recfield->recno]);
+
+ if (!HeapTupleIsValid(rec->tup)) {
+ elog(ERROR, "record %s is unassigned yet", rec->refname);
+ }
+ fno = SPI_fnumber(rec->tupdesc, recfield->fieldname);
+ if (fno == SPI_ERROR_NOATTRIBUTE) {
+ elog(ERROR, "record %s has no field %s", rec->refname, recfield->fieldname);
+ }
+ argtypes[i] = SPI_gettypeid(rec->tupdesc, fno);
+ break;
+
+ case PLPGSQL_DTYPE_TRIGARG:
+ argtypes[i] = (Oid)TEXTOID;
+ break;
+
+ default:
+ elog(ERROR, "unknown parameter dtype %d in exec_run_select()", estate->datums[expr->params[i]]);
+ }
+ }
+
+ /* ----------
+ * Generate and save the plan
+ * ----------
+ */
+ plan = SPI_prepare(expr->query, expr->nparams, argtypes);
+ if (plan == NULL) {
+ elog(ERROR, "SPI_prepare() failed on \"%s\"", expr->query);
+ }
+ expr->plan = SPI_saveplan(plan);
+ expr->plan_argtypes = argtypes;
+ }
+
+ /* ----------
+ * Now build up the values and nulls arguments for SPI_execp()
+ * ----------
+ */
+ values = palloc(sizeof(Datum) * (expr->nparams + 1));
+ nulls = palloc(expr->nparams + 1);
+
+ for (i = 0; i < expr->nparams; i++) {
+ switch (estate->datums[expr->params[i]]->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ var = (PLpgSQL_var *)(estate->datums[expr->params[i]]);
+ values[i] = var->value;
+ if (var->isnull) {
+ nulls[i] = 'n';
+ } else {
+ nulls[i] = ' ';
+ }
+ break;
+
+ case PLPGSQL_DTYPE_RECFIELD:
+ recfield = (PLpgSQL_recfield *)(estate->datums[expr->params[i]]);
+ rec = (PLpgSQL_rec *)(estate->datums[recfield->recno]);
+
+ if (!HeapTupleIsValid(rec->tup)) {
+ elog(ERROR, "record %s is unassigned yet", rec->refname);
+ }
+ fno = SPI_fnumber(rec->tupdesc, recfield->fieldname);
+ if (fno == SPI_ERROR_NOATTRIBUTE) {
+ elog(ERROR, "record %s has no field %s", rec->refname, recfield->fieldname);
+ }
+
+ if (expr->plan_argtypes[i] != SPI_gettypeid(rec->tupdesc, fno)) {
+ elog(ERROR, "type of %s.%s doesn't match that when preparing the plan", rec->refname, recfield->fieldname);
+ }
+
+ values[i] = SPI_getbinval(rec->tup, rec->tupdesc, fno, &isnull);
+ if (isnull) {
+ nulls[i] = 'n';
+ } else {
+ nulls[i] = ' ';
+ }
+ break;
+
+ case PLPGSQL_DTYPE_TRIGARG:
+ trigarg = (PLpgSQL_trigarg *)(estate->datums[expr->params[i]]);
+ tgargno = (int)exec_eval_expr(estate, trigarg->argnum,
+ &isnull, &tgargoid);
+ if (isnull || tgargno < 0 || tgargno >= estate->trig_nargs) {
+ values[i] = 0;
+ nulls[i] = 'n';
+ } else {
+ values[i] = estate->trig_argv[tgargno];
+ nulls[i] = ' ';
+ }
+ break;
+
+ default:
+ elog(ERROR, "unknown parameter dtype %d in exec_eval_expr()", estate->datums[expr->params[i]]);
+ }
+ }
+ nulls[i] = '\0';
+
+ /* ----------
+ * Execute the query
+ * ----------
+ */
+ rc = SPI_execp(expr->plan, values, nulls, maxtuples);
+ if (rc != SPI_OK_SELECT) {
+ elog(ERROR, "query \"%s\" isn't a SELECT", expr->query);
+ }
+ pfree(values);
+ pfree(nulls);
+
+ return rc;
+}
+
+
+/* ----------
+ * exec_move_row Move one tuples values into a
+ * record or row
+ * ----------
+ */
+static void exec_move_row(PLpgSQL_execstate *estate,
+ PLpgSQL_rec *rec,
+ PLpgSQL_row *row,
+ HeapTuple tup, TupleDesc tupdesc)
+{
+ PLpgSQL_var *var;
+ int i;
+ Datum value;
+ Oid valtype;
+ bool isnull;
+
+ /* ----------
+ * Record is simple - just put the tuple and it's descriptor
+ * into the record
+ * ----------
+ */
+ if (rec != NULL) {
+ if (HeapTupleIsValid(tup)) {
+ rec->tup = tup;
+ rec->tupdesc = tupdesc;
+ } else {
+ rec->tup = NULL;
+ rec->tupdesc = NULL;
+ }
+
+ return;
+ }
+
+
+ /* ----------
+ * Row is a bit more complicated in that we assign the single
+ * attributes of the query to the variables the row points to.
+ * ----------
+ */
+ if (row != NULL) {
+ if (HeapTupleIsValid(tup)) {
+ if (row->nfields != tupdesc->natts) {
+ elog(ERROR, "query didn't return correct # of attributes for %s",
+ row->refname);
+ }
+
+ for (i = 0; i < row->nfields; i++) {
+ var = (PLpgSQL_var *)(estate->datums[row->varnos[i]]);
+
+ valtype = SPI_gettypeid(tupdesc, i + 1);
+ value = SPI_getbinval(tup, tupdesc, i + 1, &isnull);
+ exec_assign_value(estate, estate->datums[row->varnos[i]],
+ value, valtype, &isnull);
+
+ }
+ } else {
+ for (i = 0; i < row->nfields; i++) {
+ bool nullval = true;
+
+ exec_assign_value(estate, estate->datums[row->varnos[i]],
+ (Datum) 0, 0, &nullval);
+ }
+ }
+
+ return;
+ }
+
+ elog(ERROR, "unsupported target in exec_move_row()");
+}
+
+
+/* ----------
+ * exec_cast_value Cast a value if required
+ * ----------
+ */
+static Datum exec_cast_value(Datum value, Oid valtype,
+ Oid reqtype,
+ FmgrInfo *reqinput,
+ int16 reqtypmod,
+ bool *isnull)
+{
+ if (!*isnull) {
+ /* ----------
+ * If the type of the queries return value isn't
+ * that of the variable, convert it.
+ * ----------
+ */
+ if (valtype != reqtype || reqtypmod > 0) {
+ HeapTuple typetup;
+ TypeTupleForm typeStruct;
+ FmgrInfo finfo_output;
+ char *extval;
+
+ typetup = SearchSysCacheTuple(TYPOID,
+ ObjectIdGetDatum(valtype), 0, 0, 0);
+ if (!HeapTupleIsValid(typetup)) {
+ elog(ERROR, "cache lookup for type %d failed", valtype);
+ }
+ typeStruct = (TypeTupleForm) GETSTRUCT(typetup);
+
+ fmgr_info(typeStruct->typoutput, &finfo_output);
+ extval = (char *)(*fmgr_faddr(&finfo_output))(value, &isnull, -1);
+ value = (Datum)(*fmgr_faddr(reqinput))(extval, &isnull, reqtypmod);
+ }
+ }
+
+ return value;
+}
+
+
+/* ----------
+ * exec_set_found Set the global found variable
+ * to true/false
+ * ----------
+ */
+static void exec_set_found(PLpgSQL_execstate *estate, bool state)
+{
+ PLpgSQL_var *var;
+
+ var = (PLpgSQL_var *)(estate->datums[estate->found_varno]);
+ var->value = (Datum) state;
+ var->isnull = false;
+}
+
+
--- /dev/null
+/**********************************************************************
+ * pl_funcs.c - Misc functins for the PL/pgSQL
+ * procedural language
+ *
+ * IDENTIFICATION
+ * $Header: /cvsroot/pgsql/contrib/plpgsql/src/Attic/pl_funcs.c,v 1.1 1998/08/22 12:38:32 momjian Exp $
+ *
+ * This software is copyrighted by Jan Wieck - Hamburg.
+ *
+ * The author hereby grants permission to use, copy, modify,
+ * distribute, and license this software and its documentation
+ * for any purpose, provided that existing copyright notices are
+ * retained in all copies and that this notice is included
+ * verbatim in any distributions. No written agreement, license,
+ * or royalty fee is required for any of the authorized uses.
+ * Modifications to this software may be copyrighted by their
+ * author and need not follow the licensing terms described
+ * here, provided that the new terms are clearly indicated on
+ * the first page of each file where they apply.
+ *
+ * IN NO EVENT SHALL THE AUTHOR OR DISTRIBUTORS BE LIABLE TO ANY
+ * PARTY FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL, OR
+ * CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OF THIS
+ * SOFTWARE, ITS DOCUMENTATION, OR ANY DERIVATIVES THEREOF, EVEN
+ * IF THE AUTHOR HAVE BEEN ADVISED OF THE POSSIBILITY OF SUCH
+ * DAMAGE.
+ *
+ * THE AUTHOR AND DISTRIBUTORS SPECIFICALLY DISCLAIM ANY
+ * WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
+ * WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
+ * PURPOSE, AND NON-INFRINGEMENT. THIS SOFTWARE IS PROVIDED ON
+ * AN "AS IS" BASIS, AND THE AUTHOR AND DISTRIBUTORS HAVE NO
+ * OBLIGATION TO PROVIDE MAINTENANCE, SUPPORT, UPDATES,
+ * ENHANCEMENTS, OR MODIFICATIONS.
+ *
+ **********************************************************************/
+
+#include <stdio.h>
+#include <stdlib.h>
+#include <stdarg.h>
+#include <unistd.h>
+#include <fcntl.h>
+#include <string.h>
+#include <ctype.h>
+
+#include "plpgsql.h"
+#include "pl.tab.h"
+
+
+/* ----------
+ * Local variables for the namestack handling
+ * ----------
+ */
+static PLpgSQL_ns *ns_current = NULL;
+static bool ns_localmode = false;
+
+
+/* ----------
+ * plpgsql_dstring_init Dynamic string initialization
+ * ----------
+ */
+void plpgsql_dstring_init(PLpgSQL_dstring *ds)
+{
+ ds->value = palloc(ds->alloc = 512);
+ ds->used = 0;
+}
+
+
+/* ----------
+ * plpgsql_dstring_free Dynamic string destruction
+ * ----------
+ */
+void plpgsql_dstring_free(PLpgSQL_dstring *ds)
+{
+ pfree(ds->value);
+}
+
+
+/* ----------
+ * plpgsql_dstring_append Dynamic string extending
+ * ----------
+ */
+void plpgsql_dstring_append(PLpgSQL_dstring *ds, char *str)
+{
+ int len = strlen(str);
+
+ if (ds->used + len + 1 > ds->alloc) {
+ ds->alloc *= 2;
+ ds->value = repalloc(ds->value, ds->alloc);
+ }
+
+ strcpy(&(ds->value[ds->used]), str);
+ ds->used += len;
+}
+
+
+/* ----------
+ * plpgsql_dstring_get Dynamic string get value
+ * ----------
+ */
+char *plpgsql_dstring_get(PLpgSQL_dstring *ds)
+{
+ return ds->value;
+}
+
+
+/* ----------
+ * plpgsql_ns_init Initialize the namestack
+ * ----------
+ */
+void plpgsql_ns_init(void)
+{
+ ns_current = NULL;
+ ns_localmode = false;
+}
+
+
+/* ----------
+ * plpgsql_ns_setlocal Tell plpgsql_ns_lookup to or to
+ * not look into the current level
+ * only.
+ * ----------
+ */
+bool plpgsql_ns_setlocal(bool flag)
+{
+ bool oldstate;
+
+ oldstate = ns_localmode;
+ ns_localmode = flag;
+ return oldstate;
+}
+
+
+/* ----------
+ * plpgsql_ns_push Enter a new namestack level
+ * ----------
+ */
+void plpgsql_ns_push(char *label)
+{
+ PLpgSQL_ns *new;
+
+ new = palloc(sizeof(PLpgSQL_ns));
+ memset(new, 0, sizeof(PLpgSQL_ns));
+ new->upper = ns_current;
+ ns_current = new;
+
+ plpgsql_ns_additem(PLPGSQL_NSTYPE_LABEL, 0, label);
+}
+
+
+/* ----------
+ * plpgsql_ns_pop Return to the previous level
+ * ----------
+ */
+void plpgsql_ns_pop()
+{
+ int i;
+ PLpgSQL_ns *old;
+
+ old = ns_current;
+ ns_current = old->upper;
+
+ for (i = 0; i < old->items_used; i++) {
+ pfree(old->items[i]);
+ }
+ pfree(old->items);
+ pfree(old);
+}
+
+
+/* ----------
+ * plpgsql_ns_additem Add an item to the current
+ * namestack level
+ * ----------
+ */
+void plpgsql_ns_additem(int itemtype, int itemno, char *name)
+{
+ PLpgSQL_ns *ns = ns_current;
+ PLpgSQL_nsitem *nse;
+
+ if (name == NULL)
+ name = "";
+
+ if (ns->items_used == ns->items_alloc) {
+ if (ns->items_alloc == 0) {
+ ns->items_alloc = 32;
+ ns->items = palloc(sizeof(PLpgSQL_nsitem *) * ns->items_alloc);
+ } else {
+ ns->items_alloc *= 2;
+ ns->items = repalloc(ns->items,
+ sizeof(PLpgSQL_nsitem *) * ns->items_alloc);
+ }
+ }
+
+ nse = palloc(sizeof(PLpgSQL_nsitem) + strlen(name));
+ nse->itemtype = itemtype;
+ nse->itemno = itemno;
+ strcpy(nse->name, name);
+ ns->items[ns->items_used++] = nse;
+}
+
+
+/* ----------
+ * plpgsql_ns_lookup Lookup for a word in the namestack
+ * ----------
+ */
+PLpgSQL_nsitem *plpgsql_ns_lookup(char *name, char *label)
+{
+ PLpgSQL_ns *ns;
+ int i;
+
+ /* ----------
+ * If a label is specified, lookup only in that
+ * ----------
+ */
+ if (label != NULL) {
+ for (ns = ns_current; ns != NULL; ns = ns->upper) {
+ if (!strcmp(ns->items[0]->name, label)) {
+ for (i = 1; i < ns->items_used; i++) {
+ if (!strcmp(ns->items[i]->name, name)) {
+ return ns->items[i];
+ }
+ }
+ return NULL; /* name not found in specified label */
+ }
+ }
+ return NULL; /* label not found */
+ }
+
+ /* ----------
+ * No label given, lookup for visible labels ignoring localmode
+ * ----------
+ */
+ for (ns = ns_current; ns != NULL; ns = ns->upper) {
+ if (!strcmp(ns->items[0]->name, name)) {
+ return ns->items[0];
+ }
+ }
+
+ /* ----------
+ * Finally lookup name in the namestack
+ * ----------
+ */
+ for (ns = ns_current; ns != NULL; ns = ns->upper) {
+ for (i = 1; i < ns->items_used; i++) {
+ if (!strcmp(ns->items[i]->name, name))
+ return ns->items[i];
+ }
+ if (ns_localmode) {
+ return NULL; /* name not found in current namespace */
+ }
+ }
+
+ return NULL;
+}
+
+
+/* ----------
+ * plpgsql_ns_rename Rename a namespace entry
+ * ----------
+ */
+void plpgsql_ns_rename(char *oldname, char *newname)
+{
+ PLpgSQL_ns *ns;
+ PLpgSQL_nsitem *newitem;
+ int i;
+
+ /* ----------
+ * Lookup in the current namespace only
+ * ----------
+ */
+ /* ----------
+ * Lookup name in the namestack
+ * ----------
+ */
+ for (ns = ns_current; ns != NULL; ns = ns->upper) {
+ for (i = 1; i < ns->items_used; i++) {
+ if (!strcmp(ns->items[i]->name, oldname)) {
+ newitem = palloc(sizeof(PLpgSQL_nsitem) + strlen(newname));
+ newitem->itemtype = ns->items[i]->itemtype;
+ newitem->itemno = ns->items[i]->itemno;
+ strcpy(newitem->name, newname);
+
+ pfree(oldname);
+ pfree(newname);
+
+ pfree(ns->items[i]);
+ ns->items[i] = newitem;
+ return;
+ }
+ }
+ }
+
+ elog(ERROR, "there is no variable '%s' in the current block", oldname);
+}
+
+
+/* ----------
+ * plpgsql_tolower Translate a string in place to
+ * lower case
+ * ----------
+ */
+char *plpgsql_tolower(char *s)
+{
+ char *cp;
+
+ for (cp = s; *cp; cp++) {
+ if (isupper(*cp)) *cp = tolower(*cp);
+ }
+
+ return s;
+}
+
+
+
+
+
+/**********************************************************************
+ * Debug functions for analyzing the compiled code
+ **********************************************************************/
+static int dump_indent;
+
+static void dump_ind();
+static void dump_stmt(PLpgSQL_stmt *stmt);
+static void dump_block(PLpgSQL_stmt_block *block);
+static void dump_assign(PLpgSQL_stmt_assign *stmt);
+static void dump_if(PLpgSQL_stmt_if *stmt);
+static void dump_loop(PLpgSQL_stmt_loop *stmt);
+static void dump_while(PLpgSQL_stmt_while *stmt);
+static void dump_fori(PLpgSQL_stmt_fori *stmt);
+static void dump_fors(PLpgSQL_stmt_fors *stmt);
+static void dump_select(PLpgSQL_stmt_select *stmt);
+static void dump_exit(PLpgSQL_stmt_exit *stmt);
+static void dump_return(PLpgSQL_stmt_return *stmt);
+static void dump_raise(PLpgSQL_stmt_raise *stmt);
+static void dump_execsql(PLpgSQL_stmt_execsql *stmt);
+static void dump_expr(PLpgSQL_expr *expr);
+
+
+static void dump_ind()
+{
+ int i;
+ for (i = 0; i < dump_indent; i++) {
+ printf(" ");
+ }
+}
+
+static void dump_stmt(PLpgSQL_stmt *stmt)
+{
+ printf("%3d:", stmt->lineno);
+ switch (stmt->cmd_type) {
+ case PLPGSQL_STMT_BLOCK:
+ dump_block((PLpgSQL_stmt_block *)stmt);
+ break;
+ case PLPGSQL_STMT_ASSIGN:
+ dump_assign((PLpgSQL_stmt_assign *)stmt);
+ break;
+ case PLPGSQL_STMT_IF:
+ dump_if((PLpgSQL_stmt_if *)stmt);
+ break;
+ case PLPGSQL_STMT_LOOP:
+ dump_loop((PLpgSQL_stmt_loop *)stmt);
+ break;
+ case PLPGSQL_STMT_WHILE:
+ dump_while((PLpgSQL_stmt_while *)stmt);
+ break;
+ case PLPGSQL_STMT_FORI:
+ dump_fori((PLpgSQL_stmt_fori *)stmt);
+ break;
+ case PLPGSQL_STMT_FORS:
+ dump_fors((PLpgSQL_stmt_fors *)stmt);
+ break;
+ case PLPGSQL_STMT_SELECT:
+ dump_select((PLpgSQL_stmt_select *)stmt);
+ break;
+ case PLPGSQL_STMT_EXIT:
+ dump_exit((PLpgSQL_stmt_exit *)stmt);
+ break;
+ case PLPGSQL_STMT_RETURN:
+ dump_return((PLpgSQL_stmt_return *)stmt);
+ break;
+ case PLPGSQL_STMT_RAISE:
+ dump_raise((PLpgSQL_stmt_raise *)stmt);
+ break;
+ case PLPGSQL_STMT_EXECSQL:
+ dump_execsql((PLpgSQL_stmt_execsql *)stmt);
+ break;
+ default:
+ elog(ERROR, "plpgsql_dump: unknown cmd_type %d\n", stmt->cmd_type);
+ break;
+ }
+}
+
+static void dump_block(PLpgSQL_stmt_block *block)
+{
+ int i;
+ char *name;
+
+ if (block->label == NULL) {
+ name = "*unnamed*";
+ } else {
+ name = block->label;
+ }
+
+ dump_ind();
+ printf("BLOCK <<%s>>\n", name);
+
+ dump_indent += 2;
+ for (i = 0; i < block->body->stmts_used; i++) {
+ dump_stmt((PLpgSQL_stmt *)(block->body->stmts[i]));
+ }
+ dump_indent -= 2;
+
+ dump_ind();
+ printf(" END -- %s\n", name);
+}
+
+static void dump_assign(PLpgSQL_stmt_assign *stmt)
+{
+ dump_ind();
+ printf("ASSIGN var %d := ", stmt->varno);
+ dump_expr(stmt->expr);
+ printf("\n");
+}
+
+static void dump_if(PLpgSQL_stmt_if *stmt)
+{
+ int i;
+
+ dump_ind();
+ printf("IF ");
+ dump_expr(stmt->cond);
+ printf(" THEN\n");
+
+ dump_indent += 2;
+ for (i = 0; i < stmt->true_body->stmts_used; i++) {
+ dump_stmt((PLpgSQL_stmt *)(stmt->true_body->stmts[i]));
+ }
+ dump_indent -= 2;
+
+ dump_ind();
+ printf(" ELSE\n");
+
+ dump_indent += 2;
+ for (i = 0; i < stmt->false_body->stmts_used; i++) {
+ dump_stmt((PLpgSQL_stmt *)(stmt->false_body->stmts[i]));
+ }
+ dump_indent -= 2;
+
+ dump_ind();
+ printf(" ENDIF\n");
+}
+
+static void dump_loop(PLpgSQL_stmt_loop *stmt)
+{
+ int i;
+
+ dump_ind();
+ printf("LOOP\n");
+
+ dump_indent += 2;
+ for (i = 0; i < stmt->body->stmts_used; i++) {
+ dump_stmt((PLpgSQL_stmt *)(stmt->body->stmts[i]));
+ }
+ dump_indent -= 2;
+
+ dump_ind();
+ printf(" ENDLOOP\n");
+}
+
+static void dump_while(PLpgSQL_stmt_while *stmt)
+{
+ int i;
+
+ dump_ind();
+ printf("WHILE ");
+ dump_expr(stmt->cond);
+ printf("\n");
+
+ dump_indent += 2;
+ for (i = 0; i < stmt->body->stmts_used; i++) {
+ dump_stmt((PLpgSQL_stmt *)(stmt->body->stmts[i]));
+ }
+ dump_indent -= 2;
+
+ dump_ind();
+ printf(" ENDWHILE\n");
+}
+
+static void dump_fori(PLpgSQL_stmt_fori *stmt)
+{
+ int i;
+
+ dump_ind();
+ printf("FORI %s %s\n", stmt->var->refname, (stmt->reverse) ? "REVERSE" : "NORMAL");
+
+ dump_indent += 2;
+ dump_ind();
+ printf(" lower = ");
+ dump_expr(stmt->lower);
+ printf("\n");
+ dump_ind();
+ printf(" upper = ");
+ dump_expr(stmt->upper);
+ printf("\n");
+
+ for (i = 0; i < stmt->body->stmts_used; i++) {
+ dump_stmt((PLpgSQL_stmt *)(stmt->body->stmts[i]));
+ }
+ dump_indent -= 2;
+
+ dump_ind();
+ printf(" ENDFORI\n");
+}
+
+static void dump_fors(PLpgSQL_stmt_fors *stmt)
+{
+ int i;
+
+ dump_ind();
+ printf("FORS %s ", (stmt->rec != NULL) ? stmt->rec->refname : stmt->row->refname);
+ dump_expr(stmt->query);
+ printf("\n");
+
+ dump_indent += 2;
+ for (i = 0; i < stmt->body->stmts_used; i++) {
+ dump_stmt((PLpgSQL_stmt *)(stmt->body->stmts[i]));
+ }
+ dump_indent -= 2;
+
+ dump_ind();
+ printf(" ENDFORS\n");
+}
+
+static void dump_select(PLpgSQL_stmt_select *stmt)
+{
+ dump_ind();
+ printf("SELECT ");
+ dump_expr(stmt->query);
+ printf("\n");
+
+ dump_indent += 2;
+ if (stmt->rec != NULL) {
+ dump_ind();
+ printf(" target = %d %s\n", stmt->rec->recno, stmt->rec->refname);
+ }
+ if (stmt->row != NULL) {
+ dump_ind();
+ printf(" target = %d %s\n", stmt->row->rowno, stmt->row->refname);
+ }
+ dump_indent -= 2;
+
+}
+
+static void dump_exit(PLpgSQL_stmt_exit *stmt)
+{
+ dump_ind();
+ printf("EXIT lbl='%s'", stmt->label);
+ if (stmt->cond != NULL) {
+ printf(" WHEN ");
+ dump_expr(stmt->cond);
+ }
+ printf("\n");
+}
+
+static void dump_return(PLpgSQL_stmt_return *stmt)
+{
+ dump_ind();
+ printf("RETURN ");
+ if (stmt->retrecno >= 0) {
+ printf("record %d", stmt->retrecno);
+ } else {
+ if (stmt->expr == NULL) {
+ printf("NULL");
+ } else {
+ dump_expr(stmt->expr);
+ }
+ }
+ printf("\n");
+}
+
+static void dump_raise(PLpgSQL_stmt_raise *stmt)
+{
+ int i;
+
+ dump_ind();
+ printf("RAISE '%s'", stmt->message);
+ for (i = 0; i < stmt->nparams; i++) {
+ printf(" %d", stmt->params[i]);
+ }
+ printf("\n");
+}
+
+static void dump_execsql(PLpgSQL_stmt_execsql *stmt)
+{
+ dump_ind();
+ printf("EXECSQL ");
+ dump_expr(stmt->sqlstmt);
+ printf("\n");
+}
+
+static void dump_expr(PLpgSQL_expr *expr)
+{
+ int i;
+ printf("'%s", expr->query);
+ if (expr->nparams > 0) {
+ printf(" {");
+ for(i = 0; i < expr->nparams; i++) {
+ if (i > 0) printf(", ");
+ printf("$%d=%d", i+1, expr->params[i]);
+ }
+ printf("}");
+ }
+ printf("'");
+}
+
+void plpgsql_dumptree(PLpgSQL_function *func)
+{
+ int i;
+ PLpgSQL_datum *d;
+
+ printf("\nExecution tree of successfully compiled PL/pgSQL function %s:\n",
+ func->fn_name);
+
+ printf("\nFunctions data area:\n");
+ for (i = 0; i < func->ndatums; i++) {
+ d = func->datums[i];
+
+ printf(" entry %d: ", i);
+ switch (d->dtype) {
+ case PLPGSQL_DTYPE_VAR:
+ {
+ PLpgSQL_var *var = (PLpgSQL_var *)d;
+ printf("VAR %-16s type %s (typoid %d) atttypmod %d\n",
+ var->refname, var->datatype->typname,
+ var->datatype->typoid,
+ var->datatype->atttypmod);
+ }
+ break;
+ case PLPGSQL_DTYPE_ROW:
+ {
+ PLpgSQL_row *row = (PLpgSQL_row *)d;
+ int i;
+ printf("ROW %-16s fields", row->refname);
+ for (i = 0; i < row->nfields; i++) {
+ printf(" %s=var %d", row->fieldnames[i],
+ row->varnos[i]);
+ }
+ printf("\n");
+ }
+ break;
+ case PLPGSQL_DTYPE_REC:
+ printf("REC %s\n", ((PLpgSQL_rec *)d)->refname);
+ break;
+ case PLPGSQL_DTYPE_RECFIELD:
+ printf("RECFIELD %-16s of REC %d\n", ((PLpgSQL_recfield *)d)->fieldname, ((PLpgSQL_recfield *)d)->recno);
+ break;
+ case PLPGSQL_DTYPE_TRIGARG:
+ printf("TRIGARG ");
+ dump_expr(((PLpgSQL_trigarg *)d)->argnum);
+ printf("\n");
+ break;
+ default:
+ printf("??? unknown data type %d\n", d->dtype);
+ }
+ }
+ printf("\nFunctions statements:\n");
+
+ dump_indent = 0;
+ printf("%3d:", func->action->lineno);
+ dump_block(func->action);
+ printf("\nEnd of execution tree of function %s\n\n", func->fn_name);
+}
+
+
--- /dev/null
+/**********************************************************************
+ * pl_handler.c - Handler for the PL/pgSQL
+ * procedural language
+ *
+ * IDENTIFICATION
+ * $Header: /cvsroot/pgsql/contrib/plpgsql/src/Attic/pl_handler.c,v 1.1 1998/08/22 12:38:32 momjian Exp $
+ *
+ * This software is copyrighted by Jan Wieck - Hamburg.
+ *
+ * The author hereby grants permission to use, copy, modify,
+ * distribute, and license this software and its documentation
+ * for any purpose, provided that existing copyright notices are
+ * retained in all copies and that this notice is included
+ * verbatim in any distributions. No written agreement, license,
+ * or royalty fee is required for any of the authorized uses.
+ * Modifications to this software may be copyrighted by their
+ * author and need not follow the licensing terms described
+ * here, provided that the new terms are clearly indicated on
+ * the first page of each file where they apply.
+ *
+ * IN NO EVENT SHALL THE AUTHOR OR DISTRIBUTORS BE LIABLE TO ANY
+ * PARTY FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL, OR
+ * CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OF THIS
+ * SOFTWARE, ITS DOCUMENTATION, OR ANY DERIVATIVES THEREOF, EVEN
+ * IF THE AUTHOR HAVE BEEN ADVISED OF THE POSSIBILITY OF SUCH
+ * DAMAGE.
+ *
+ * THE AUTHOR AND DISTRIBUTORS SPECIFICALLY DISCLAIM ANY
+ * WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
+ * WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
+ * PURPOSE, AND NON-INFRINGEMENT. THIS SOFTWARE IS PROVIDED ON
+ * AN "AS IS" BASIS, AND THE AUTHOR AND DISTRIBUTORS HAVE NO
+ * OBLIGATION TO PROVIDE MAINTENANCE, SUPPORT, UPDATES,
+ * ENHANCEMENTS, OR MODIFICATIONS.
+ *
+ **********************************************************************/
+
+#include <stdio.h>
+#include <stdlib.h>
+#include <stdarg.h>
+#include <unistd.h>
+#include <fcntl.h>
+#include <string.h>
+
+#include "plpgsql.h"
+#include "pl.tab.h"
+
+#include "executor/spi.h"
+#include "commands/trigger.h"
+#include "utils/elog.h"
+#include "utils/builtins.h"
+#include "fmgr.h"
+#include "access/heapam.h"
+
+#include "utils/syscache.h"
+#include "catalog/pg_proc.h"
+#include "catalog/pg_type.h"
+
+
+static PLpgSQL_function *compiled_functions = NULL;
+
+
+Datum plpgsql_call_handler(FmgrInfo *proinfo,
+ FmgrValues *proargs, bool *isNull);
+
+static Datum plpgsql_func_handler(FmgrInfo *proinfo,
+ FmgrValues *proargs, bool *isNull);
+
+static HeapTuple plpgsql_trigger_handler(FmgrInfo *proinfo);
+
+
+/* ----------
+ * plpgsql_call_handler - This is the only visible function
+ * of the PL interpreter. The PostgreSQL
+ * function manager and trigger manager
+ * call this function for execution of
+ * PL/pgSQL procedures.
+ * ----------
+ */
+Datum
+plpgsql_call_handler(FmgrInfo *proinfo,
+ FmgrValues *proargs,
+ bool *isNull)
+{
+ Datum retval;
+
+ /* ----------
+ * Connect to SPI manager
+ * ----------
+ */
+ if (SPI_connect() != SPI_OK_CONNECT) {
+ elog(ERROR, "plpgsql: cannot connect to SPI manager");
+ }
+
+ /* ----------
+ * Determine if called as function or trigger and
+ * call appropriate subhandler
+ * ----------
+ */
+ if (CurrentTriggerData == NULL) {
+ retval = plpgsql_func_handler(proinfo, proargs, isNull);
+ } else {
+ retval = (Datum)plpgsql_trigger_handler(proinfo);
+ }
+
+ /* ----------
+ * Disconnect from SPI manager
+ * ----------
+ */
+ if (SPI_finish() != SPI_OK_FINISH) {
+ elog(ERROR, "plpgsql: SPI_finish() failed");
+ }
+
+ return retval;
+}
+
+
+/* ----------
+ * plpgsql_func_handler() - Handler for regular function calls
+ * ----------
+ */
+static Datum
+plpgsql_func_handler(FmgrInfo *proinfo,
+ FmgrValues *proargs,
+ bool *isNull)
+{
+ PLpgSQL_function *func;
+
+ /* ----------
+ * Check if we already compiled this function
+ * ----------
+ */
+ for (func = compiled_functions; func != NULL; func = func->next) {
+ if (proinfo->fn_oid == func->fn_oid)
+ break;
+ }
+
+ /* ----------
+ * If not, do so and add it to the compiled ones
+ * ----------
+ */
+ if (func == NULL) {
+ func = plpgsql_compile(proinfo->fn_oid, T_FUNCTION);
+
+ func->next = compiled_functions;
+ compiled_functions = func;
+ }
+
+ return plpgsql_exec_function(func, proargs, isNull);
+}
+
+
+/* ----------
+ * plpgsql_trigger_handler() - Handler for trigger calls
+ * ----------
+ */
+static HeapTuple
+plpgsql_trigger_handler(FmgrInfo *proinfo)
+{
+ TriggerData *trigdata;
+ PLpgSQL_function *func;
+
+ /* ----------
+ * Save the current trigger data local
+ * ----------
+ */
+ trigdata = CurrentTriggerData;
+ CurrentTriggerData = NULL;
+
+ /* ----------
+ * Check if we already compiled this trigger procedure
+ * ----------
+ */
+ for (func = compiled_functions; func != NULL; func = func->next) {
+ if (proinfo->fn_oid == func->fn_oid)
+ break;
+ }
+
+ /* ----------
+ * If not, do so and add it to the compiled ones
+ * ----------
+ */
+ if (func == NULL) {
+ func = plpgsql_compile(proinfo->fn_oid, T_TRIGGER);
+
+ func->next = compiled_functions;
+ compiled_functions = func;
+ }
+
+ return plpgsql_exec_trigger(func, trigdata);
+}
+
+
--- /dev/null
+/**********************************************************************
+ * plpgsql.h - Definitions for the PL/pgSQL
+ * procedural language
+ *
+ * IDENTIFICATION
+ * $Header: /cvsroot/pgsql/contrib/plpgsql/src/Attic/plpgsql.h,v 1.1 1998/08/22 12:38:33 momjian Exp $
+ *
+ * This software is copyrighted by Jan Wieck - Hamburg.
+ *
+ * The author hereby grants permission to use, copy, modify,
+ * distribute, and license this software and its documentation
+ * for any purpose, provided that existing copyright notices are
+ * retained in all copies and that this notice is included
+ * verbatim in any distributions. No written agreement, license,
+ * or royalty fee is required for any of the authorized uses.
+ * Modifications to this software may be copyrighted by their
+ * author and need not follow the licensing terms described
+ * here, provided that the new terms are clearly indicated on
+ * the first page of each file where they apply.
+ *
+ * IN NO EVENT SHALL THE AUTHOR OR DISTRIBUTORS BE LIABLE TO ANY
+ * PARTY FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL, OR
+ * CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OF THIS
+ * SOFTWARE, ITS DOCUMENTATION, OR ANY DERIVATIVES THEREOF, EVEN
+ * IF THE AUTHOR HAVE BEEN ADVISED OF THE POSSIBILITY OF SUCH
+ * DAMAGE.
+ *
+ * THE AUTHOR AND DISTRIBUTORS SPECIFICALLY DISCLAIM ANY
+ * WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
+ * WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
+ * PURPOSE, AND NON-INFRINGEMENT. THIS SOFTWARE IS PROVIDED ON
+ * AN "AS IS" BASIS, AND THE AUTHOR AND DISTRIBUTORS HAVE NO
+ * OBLIGATION TO PROVIDE MAINTENANCE, SUPPORT, UPDATES,
+ * ENHANCEMENTS, OR MODIFICATIONS.
+ *
+ **********************************************************************/
+#ifndef PLPGSQL_H
+#define PLPGSQL_H
+
+#include <stdio.h>
+#include <stdarg.h>
+#include "postgres.h"
+#include "executor/spi.h"
+#include "commands/trigger.h"
+#include "fmgr.h"
+
+/**********************************************************************
+ * Definitions
+ **********************************************************************/
+
+/* ----------
+ * Compilers namestack item types
+ * ----------
+ */
+enum {
+ PLPGSQL_NSTYPE_LABEL,
+ PLPGSQL_NSTYPE_VAR,
+ PLPGSQL_NSTYPE_ROW,
+ PLPGSQL_NSTYPE_REC,
+ PLPGSQL_NSTYPE_RECFIELD
+};
+
+/* ----------
+ * Datum array node types
+ * ----------
+ */
+enum {
+ PLPGSQL_DTYPE_VAR,
+ PLPGSQL_DTYPE_ROW,
+ PLPGSQL_DTYPE_REC,
+ PLPGSQL_DTYPE_RECFIELD,
+ PLPGSQL_DTYPE_EXPR,
+ PLPGSQL_DTYPE_TRIGARG
+};
+
+/* ----------
+ * Execution tree node types
+ * ----------
+ */
+enum {
+ PLPGSQL_STMT_BLOCK,
+ PLPGSQL_STMT_ASSIGN,
+ PLPGSQL_STMT_IF,
+ PLPGSQL_STMT_LOOP,
+ PLPGSQL_STMT_WHILE,
+ PLPGSQL_STMT_FORI,
+ PLPGSQL_STMT_FORS,
+ PLPGSQL_STMT_SELECT,
+ PLPGSQL_STMT_EXIT,
+ PLPGSQL_STMT_RETURN,
+ PLPGSQL_STMT_RAISE,
+ PLPGSQL_STMT_EXECSQL
+};
+
+
+/* ----------
+ * Execution node return codes
+ * ----------
+ */
+enum {
+ PLPGSQL_RC_OK,
+ PLPGSQL_RC_EXIT,
+ PLPGSQL_RC_RETURN
+};
+
+/**********************************************************************
+ * Node and structure definitions
+ **********************************************************************/
+
+
+typedef struct { /* Dynamic string control structure */
+ int alloc;
+ int used;
+ char *value;
+} PLpgSQL_dstring;
+
+
+typedef struct { /* Postgres base data type */
+ char *typname;
+ Oid typoid;
+ FmgrInfo typinput;
+ bool typbyval;
+ int16 atttypmod;
+} PLpgSQL_type;
+
+
+typedef struct { /* Generic datum array item */
+ int dtype;
+ int dno;
+} PLpgSQL_datum;
+
+
+typedef struct { /* SQL Query to plan and execute */
+ int dtype;
+ int exprno;
+ char *query;
+ void *plan;
+ Oid *plan_argtypes;
+ int nparams;
+ int params[1];
+} PLpgSQL_expr;
+
+
+typedef struct { /* Local variable */
+ int dtype;
+ int varno;
+ char *refname;
+ int lineno;
+
+ PLpgSQL_type *datatype;
+ int isconst;
+ int notnull;
+ PLpgSQL_expr *default_val;
+
+ Datum value;
+ bool isnull;
+ int shouldfree;
+} PLpgSQL_var;
+
+
+typedef struct { /* Rowtype */
+ int dtype;
+ int rowno;
+ char *refname;
+ int lineno;
+ Oid rowtypeclass;
+
+ int nfields;
+ char **fieldnames;
+ int *varnos;
+} PLpgSQL_row;
+
+
+typedef struct { /* Record of undefined structure */
+ int dtype;
+ int recno;
+ char *refname;
+ int lineno;
+
+ HeapTuple tup;
+ TupleDesc tupdesc;
+} PLpgSQL_rec;
+
+
+typedef struct { /* Field in record */
+ int dtype;
+ int rfno;
+ char *fieldname;
+ int recno;
+} PLpgSQL_recfield;
+
+
+typedef struct { /* Positional argument to trigger */
+ int dtype;
+ int dno;
+ PLpgSQL_expr *argnum;
+} PLpgSQL_trigarg;
+
+
+typedef struct { /* Item in the compilers namestack */
+ int itemtype;
+ int itemno;
+ char name[1];
+} PLpgSQL_nsitem;
+
+
+typedef struct PLpgSQL_ns { /* Compiler namestack level */
+ int items_alloc;
+ int items_used;
+ PLpgSQL_nsitem **items;
+ struct PLpgSQL_ns *upper;
+} PLpgSQL_ns;
+
+
+typedef struct { /* List of execution nodes */
+ int stmts_alloc;
+ int stmts_used;
+ struct PLpgSQL_stmt **stmts;
+} PLpgSQL_stmts;
+
+
+typedef struct { /* Generic execution node */
+ int cmd_type;
+ int lineno;
+} PLpgSQL_stmt;
+
+
+typedef struct { /* Block of statements */
+ int cmd_type;
+ int lineno;
+ char *label;
+ PLpgSQL_stmts *body;
+ int n_initvars;
+ int *initvarnos;
+} PLpgSQL_stmt_block;
+
+
+typedef struct { /* Assign statement */
+ int cmd_type;
+ int lineno;
+ int varno;
+ PLpgSQL_expr *expr;
+} PLpgSQL_stmt_assign;
+
+
+typedef struct { /* IF statement */
+ int cmd_type;
+ int lineno;
+ PLpgSQL_expr *cond;
+ PLpgSQL_stmts *true_body;
+ PLpgSQL_stmts *false_body;
+} PLpgSQL_stmt_if;
+
+
+typedef struct { /* Unconditional LOOP statement */
+ int cmd_type;
+ int lineno;
+ char *label;
+ PLpgSQL_stmts *body;
+} PLpgSQL_stmt_loop;
+
+
+typedef struct { /* WHILE cond LOOP statement */
+ int cmd_type;
+ int lineno;
+ char *label;
+ PLpgSQL_expr *cond;
+ PLpgSQL_stmts *body;
+} PLpgSQL_stmt_while;
+
+
+typedef struct { /* FOR statement with integer loopvar */
+ int cmd_type;
+ int lineno;
+ char *label;
+ PLpgSQL_var *var;
+ PLpgSQL_expr *lower;
+ PLpgSQL_expr *upper;
+ int reverse;
+ PLpgSQL_stmts *body;
+} PLpgSQL_stmt_fori;
+
+
+typedef struct { /* FOR statement running over SELECT */
+ int cmd_type;
+ int lineno;
+ char *label;
+ PLpgSQL_rec *rec;
+ PLpgSQL_row *row;
+ PLpgSQL_expr *query;
+ PLpgSQL_stmts *body;
+} PLpgSQL_stmt_fors;
+
+
+typedef struct { /* SELECT ... INTO statement */
+ int cmd_type;
+ int lineno;
+ PLpgSQL_rec *rec;
+ PLpgSQL_row *row;
+ PLpgSQL_expr *query;
+} PLpgSQL_stmt_select;
+
+
+typedef struct { /* EXIT statement */
+ int cmd_type;
+ int lineno;
+ char *label;
+ PLpgSQL_expr *cond;
+} PLpgSQL_stmt_exit;
+
+
+typedef struct { /* RETURN statement */
+ int cmd_type;
+ int lineno;
+ bool retistuple;
+ PLpgSQL_expr *expr;
+ int retrecno;
+} PLpgSQL_stmt_return;
+
+
+typedef struct { /* RAISE statement */
+ int cmd_type;
+ int lineno;
+ int elog_level;
+ char *message;
+ int nparams;
+ int *params;
+} PLpgSQL_stmt_raise;
+
+
+typedef struct { /* Generic SQL statement to execute */
+ int cmd_type;
+ int lineno;
+ PLpgSQL_expr *sqlstmt;
+} PLpgSQL_stmt_execsql;
+
+
+typedef struct PLpgSQL_function { /* Complete compiled function */
+ Oid fn_oid;
+ char *fn_name;
+ int fn_functype;
+ Oid fn_rettype;
+ int fn_rettyplen;
+ bool fn_retbyval;
+ FmgrInfo fn_retinput;
+ bool fn_retistuple;
+ bool fn_retset;
+
+ int fn_nargs;
+ int fn_argvarnos[MAXFMGRARGS];
+ int found_varno;
+ int new_varno;
+ int old_varno;
+ int tg_name_varno;
+ int tg_when_varno;
+ int tg_level_varno;
+ int tg_op_varno;
+ int tg_relid_varno;
+ int tg_relname_varno;
+ int tg_nargs_varno;
+
+ int ndatums;
+ PLpgSQL_datum **datums;
+ PLpgSQL_stmt_block *action;
+ struct PLpgSQL_function *next;
+} PLpgSQL_function;
+
+
+typedef struct { /* Runtime execution data */
+ Datum retval;
+ bool retisnull;
+ Oid rettype;
+ bool retistuple;
+ TupleDesc rettupdesc;
+ bool retisset;
+ char *exitlabel;
+
+ int trig_nargs;
+ Datum *trig_argv;
+
+ int found_varno;
+ int ndatums;
+ PLpgSQL_datum **datums;
+} PLpgSQL_execstate;
+
+
+/**********************************************************************
+ * Global variable declarations
+ **********************************************************************/
+
+extern int plpgsql_DumpExecTree;
+extern int plpgsql_SpaceScanned;
+extern int plpgsql_nDatums;
+extern PLpgSQL_datum **plpgsql_Datums;
+
+extern int plpgsql_error_lineno;
+extern char *plpgsql_error_funcname;
+
+extern PLpgSQL_function *plpgsql_curr_compile;
+
+
+/**********************************************************************
+ * Function declarations
+ **********************************************************************/
+
+
+extern char *pstrdup(char *s);
+
+
+/* ----------
+ * Functions in pl_comp.c
+ * ----------
+ */
+extern PLpgSQL_function *plpgsql_compile(Oid fn_oid, int functype);
+extern int plpgsql_parse_word(char *word);
+extern int plpgsql_parse_dblword(char *string);
+extern int plpgsql_parse_tripword(char *string);
+extern int plpgsql_parse_wordtype(char *string);
+extern int plpgsql_parse_dblwordtype(char *string);
+extern int plpgsql_parse_wordrowtype(char *string);
+extern void plpgsql_adddatum(PLpgSQL_datum *new);
+extern int plpgsql_add_initdatums(int **varnos);
+extern void plpgsql_comperrinfo(void);
+
+
+/* ----------
+ * Functions in pl_exec.c
+ * ----------
+ */
+extern Datum plpgsql_exec_function(PLpgSQL_function *func,
+ FmgrValues *args, bool *isNull);
+extern HeapTuple plpgsql_exec_trigger(PLpgSQL_function *func,
+ TriggerData *trigdata);
+
+
+/* ----------
+ * Functions for the dynamic string handling in pl_funcs.c
+ * ----------
+ */
+extern void plpgsql_dstring_init(PLpgSQL_dstring *ds);
+extern void plpgsql_dstring_free(PLpgSQL_dstring *ds);
+extern void plpgsql_dstring_append(PLpgSQL_dstring *ds, char *str);
+extern char *plpgsql_dstring_get(PLpgSQL_dstring *ds);
+
+/* ----------
+ * Functions for the namestack handling in pl_funcs.c
+ * ----------
+ */
+extern void plpgsql_ns_init(void);
+extern bool plpgsql_ns_setlocal(bool flag);
+extern void plpgsql_ns_push(char *label);
+extern void plpgsql_ns_pop(void);
+extern void plpgsql_ns_additem(int itemtype, int itemno, char *name);
+extern PLpgSQL_nsitem *plpgsql_ns_lookup(char *name, char *nsname);
+extern void plpgsql_ns_rename(char *oldname, char *newname);
+
+/* ----------
+ * Other functions in pl_funcs.c
+ * ----------
+ */
+extern void plpgsql_dumptree(PLpgSQL_function *func);
+extern char *plpgsql_tolower(char *s);
+
+/* ----------
+ * Externs in gram.y and scan.l
+ * ----------
+ */
+extern PLpgSQL_expr *plpgsql_read_expression(int until, char *s);
+extern void plpgsql_yyrestart(FILE *fp);
+extern int plpgsql_yylex();
+extern void plpgsql_setinput(char *s, int functype);
+extern int plpgsql_yyparse();
+
+
+#endif /* PLPGSQL_H */
--- /dev/null
+%{
+/**********************************************************************
+ * scan.l - Scanner for the PL/pgSQL
+ * procedural language
+ *
+ * IDENTIFICATION
+ * $Header: /cvsroot/pgsql/contrib/plpgsql/src/Attic/scan.l,v 1.1 1998/08/22 12:38:33 momjian Exp $
+ *
+ * This software is copyrighted by Jan Wieck - Hamburg.
+ *
+ * The author hereby grants permission to use, copy, modify,
+ * distribute, and license this software and its documentation
+ * for any purpose, provided that existing copyright notices are
+ * retained in all copies and that this notice is included
+ * verbatim in any distributions. No written agreement, license,
+ * or royalty fee is required for any of the authorized uses.
+ * Modifications to this software may be copyrighted by their
+ * author and need not follow the licensing terms described
+ * here, provided that the new terms are clearly indicated on
+ * the first page of each file where they apply.
+ *
+ * IN NO EVENT SHALL THE AUTHOR OR DISTRIBUTORS BE LIABLE TO ANY
+ * PARTY FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL, OR
+ * CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OF THIS
+ * SOFTWARE, ITS DOCUMENTATION, OR ANY DERIVATIVES THEREOF, EVEN
+ * IF THE AUTHOR HAVE BEEN ADVISED OF THE POSSIBILITY OF SUCH
+ * DAMAGE.
+ *
+ * THE AUTHOR AND DISTRIBUTORS SPECIFICALLY DISCLAIM ANY
+ * WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
+ * WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR
+ * PURPOSE, AND NON-INFRINGEMENT. THIS SOFTWARE IS PROVIDED ON
+ * AN "AS IS" BASIS, AND THE AUTHOR AND DISTRIBUTORS HAVE NO
+ * OBLIGATION TO PROVIDE MAINTENANCE, SUPPORT, UPDATES,
+ * ENHANCEMENTS, OR MODIFICATIONS.
+ *
+ **********************************************************************/
+
+static char *plpgsql_source;
+static int plpgsql_bytes_left;
+static int scanner_functype;
+static int scanner_typereported;
+int plpgsql_SpaceScanned = 0;
+
+static void plpgsql_input(char *buf, int *result, int max);
+#define YY_INPUT(buf,res,max) plpgsql_input(buf, &res, max)
+%}
+
+WS [[:alpha:]_]
+WC [[:alnum:]_]
+
+%x IN_STRING IN_COMMENT
+
+%%
+ /* ----------
+ * Local variable in scanner to remember where
+ * a string or comment started
+ * ----------
+ */
+ int start_lineno = 0;
+
+ /* ----------
+ * Reset the state when entering the scanner
+ * ----------
+ */
+ BEGIN INITIAL;
+ plpgsql_SpaceScanned = 0;
+
+ /* ----------
+ * On the first call to a new source report the
+ * functions type (T_FUNCTION or T_TRIGGER)
+ * ----------
+ */
+ if (!scanner_typereported) {
+ scanner_typereported = 1;
+ return scanner_functype;
+ }
+
+ /* ----------
+ * The keyword rules
+ * ----------
+ */
+:= { return K_ASSIGN; }
+= { return K_ASSIGN; }
+\.\. { return K_DOTDOT; }
+alias { return K_ALIAS; }
+begin { return K_BEGIN; }
+bpchar { return T_BPCHAR; }
+char { return T_CHAR; }
+constant { return K_CONSTANT; }
+debug { return K_DEBUG; }
+declare { return K_DECLARE; }
+default { return K_DEFAULT; }
+else { return K_ELSE; }
+end { return K_END; }
+exception { return K_EXCEPTION; }
+exit { return K_EXIT; }
+for { return K_FOR; }
+from { return K_FROM; }
+if { return K_IF; }
+in { return K_IN; }
+into { return K_INTO; }
+loop { return K_LOOP; }
+not { return K_NOT; }
+notice { return K_NOTICE; }
+null { return K_NULL; }
+perform { return K_PERFORM; }
+raise { return K_RAISE; }
+record { return K_RECORD; }
+rename { return K_RENAME; }
+return { return K_RETURN; }
+reverse { return K_REVERSE; }
+select { return K_SELECT; }
+then { return K_THEN; }
+to { return K_TO; }
+type { return K_TYPE; }
+varchar { return T_VARCHAR; }
+when { return K_WHEN; }
+while { return K_WHILE; }
+
+^#option { return O_OPTION; }
+dump { return O_DUMP; }
+
+
+ /* ----------
+ * Special word rules
+ * ----------
+ */
+{WS}{WC}* { return plpgsql_parse_word(yytext); }
+{WS}{WC}*\.{WS}{WC}* { return plpgsql_parse_dblword(yytext); }
+{WS}{WC}*\.{WS}{WC}*\.{WS}{WC}* { return plpgsql_parse_tripword(yytext); }
+{WS}{WC}*%TYPE { return plpgsql_parse_wordtype(yytext); }
+{WS}{WC}*\.{WS}{WC}*%TYPE { return plpgsql_parse_dblwordtype(yytext); }
+{WS}{WC}*%ROWTYPE { return plpgsql_parse_wordrowtype(yytext); }
+
+\$[0-9]+ { return plpgsql_parse_word(yytext); }
+[0-9]+ { return T_NUMBER; }
+
+ /* ----------
+ * Ignore whitespaces but remember this happened
+ * ----------
+ */
+[ \t\n]+ { plpgsql_SpaceScanned = 1; }
+
+ /* ----------
+ * Eat up comments
+ * ----------
+ */
+--[^\n]* ;
+\/\* { start_lineno = yylineno;
+ BEGIN IN_COMMENT;
+ }
+<IN_COMMENT>\*\/ { BEGIN INITIAL; }
+<IN_COMMENT>\n ;
+<IN_COMMENT>. ;
+<IN_COMMENT><<EOF>> { plpgsql_comperrinfo();
+ elog(ERROR, "unterminated comment starting on line %d",
+ start_lineno);
+ }
+
+ /* ----------
+ * Collect anything inside of ''s and return one STRING
+ * ----------
+ */
+' { start_lineno = yylineno;
+ BEGIN IN_STRING;
+ yymore();
+ }
+<IN_STRING>\\. |
+<IN_STRING>'' { yymore(); }
+<IN_STRING>' { BEGIN INITIAL;
+ return T_STRING;
+ }
+<IN_STRING><<EOF>> { plpgsql_comperrinfo();
+ elog(ERROR, "unterminated string starting on line %d",
+ start_lineno);
+ }
+<IN_STRING>[^'\\]* { yymore(); }
+
+ /* ----------
+ * Any unmatched character is returned as is
+ * ----------
+ */
+. { return yytext[0]; }
+
+%%
+
+int yywrap()
+{
+ return 1;
+}
+
+
+static void plpgsql_input(char *buf, int *result, int max)
+{
+ int n = max;
+ if (n > plpgsql_bytes_left) {
+ n = plpgsql_bytes_left;
+ }
+
+ if (n == 0) {
+ *result = YY_NULL;
+ return;
+ }
+
+ *result = n;
+ memcpy(buf, plpgsql_source, n);
+ plpgsql_source += n;
+ plpgsql_bytes_left -= n;
+}
+
+
+void plpgsql_setinput(char *source, int functype)
+{
+ yyrestart(NULL);
+ yylineno = 1;
+
+ plpgsql_source = source;
+ if (*plpgsql_source == '\n')
+ plpgsql_source++;
+ plpgsql_bytes_left = strlen(plpgsql_source);
+
+ scanner_functype = functype;
+ scanner_typereported = 0;
+}
+
+
--- /dev/null
+Test suite for PL/pgSQL
+
+Scenario:
+
+ A building with a modern TP cabel installation where any
+ of the wall connectors can be used to plug in phones,
+ ethernet interfaces or local office hubs. The backside
+ of the wall connectors is wired to one of several patch-
+ fields in the building.
+
+ In the patchfields, there are hubs and all the slots
+ representing the wall connectors. In addition there are
+ slots that can represent a phone line from the central
+ phone system.
+
+ Triggers ensure consistency of the patching information.
+
+ Functions are used to build up powerful views that let
+ you look behind the wall when looking at a patchfield
+ or into a room.
+
+
--- /dev/null
+QUERY: create table Room (
+ roomno char(8),
+ comment text
+);
+QUERY: create unique index Room_rno on Room using btree (roomno bpchar_ops);
+QUERY: create table WSlot (
+ slotname char(20),
+ roomno char(8),
+ slotlink char(20),
+ backlink char(20)
+);
+QUERY: create unique index WSlot_name on WSlot using btree (slotname bpchar_ops);
+QUERY: create table PField (
+ name text,
+ comment text
+);
+QUERY: create unique index PField_name on PField using btree (name text_ops);
+QUERY: create table PSlot (
+ slotname char(20),
+ pfname text,
+ slotlink char(20),
+ backlink char(20)
+);
+QUERY: create unique index PSlot_name on PSlot using btree (slotname bpchar_ops);
+QUERY: create table PLine (
+ slotname char(20),
+ phonenumber char(20),
+ comment text,
+ backlink char(20)
+);
+QUERY: create unique index PLine_name on PLine using btree (slotname bpchar_ops);
+QUERY: create table Hub (
+ name char(14),
+ comment text,
+ nslots integer
+);
+QUERY: create unique index Hub_name on Hub using btree (name bpchar_ops);
+QUERY: create table HSlot (
+ slotname char(20),
+ hubname char(14),
+ slotno integer,
+ slotlink char(20)
+);
+QUERY: create unique index HSlot_name on HSlot using btree (slotname bpchar_ops);
+QUERY: create index HSlot_hubname on HSlot using btree (hubname bpchar_ops);
+QUERY: create table System (
+ name text,
+ comment text
+);
+QUERY: create unique index System_name on System using btree (name text_ops);
+QUERY: create table IFace (
+ slotname char(20),
+ sysname text,
+ ifname text,
+ slotlink char(20)
+);
+QUERY: create unique index IFace_name on IFace using btree (slotname bpchar_ops);
+QUERY: create table PHone (
+ slotname char(20),
+ comment text,
+ slotlink char(20)
+);
+QUERY: create unique index PHone_name on PHone using btree (slotname bpchar_ops);
--- /dev/null
+QUERY: insert into Room values ('001', 'Entrance');
+QUERY: insert into Room values ('002', 'Office');
+QUERY: insert into Room values ('003', 'Office');
+QUERY: insert into Room values ('004', 'Technical');
+QUERY: insert into Room values ('101', 'Office');
+QUERY: insert into Room values ('102', 'Conference');
+QUERY: insert into Room values ('103', 'Restroom');
+QUERY: insert into Room values ('104', 'Technical');
+QUERY: insert into Room values ('105', 'Office');
+QUERY: insert into Room values ('106', 'Office');
+QUERY: insert into WSlot values ('WS.001.1a', '001', '', '');
+QUERY: insert into WSlot values ('WS.001.1b', '001', '', '');
+QUERY: insert into WSlot values ('WS.001.2a', '001', '', '');
+QUERY: insert into WSlot values ('WS.001.2b', '001', '', '');
+QUERY: insert into WSlot values ('WS.001.3a', '001', '', '');
+QUERY: insert into WSlot values ('WS.001.3b', '001', '', '');
+QUERY: insert into WSlot values ('WS.002.1a', '002', '', '');
+QUERY: insert into WSlot values ('WS.002.1b', '002', '', '');
+QUERY: insert into WSlot values ('WS.002.2a', '002', '', '');
+QUERY: insert into WSlot values ('WS.002.2b', '002', '', '');
+QUERY: insert into WSlot values ('WS.002.3a', '002', '', '');
+QUERY: insert into WSlot values ('WS.002.3b', '002', '', '');
+QUERY: insert into WSlot values ('WS.003.1a', '003', '', '');
+QUERY: insert into WSlot values ('WS.003.1b', '003', '', '');
+QUERY: insert into WSlot values ('WS.003.2a', '003', '', '');
+QUERY: insert into WSlot values ('WS.003.2b', '003', '', '');
+QUERY: insert into WSlot values ('WS.003.3a', '003', '', '');
+QUERY: insert into WSlot values ('WS.003.3b', '003', '', '');
+QUERY: insert into WSlot values ('WS.101.1a', '101', '', '');
+QUERY: insert into WSlot values ('WS.101.1b', '101', '', '');
+QUERY: insert into WSlot values ('WS.101.2a', '101', '', '');
+QUERY: insert into WSlot values ('WS.101.2b', '101', '', '');
+QUERY: insert into WSlot values ('WS.101.3a', '101', '', '');
+QUERY: insert into WSlot values ('WS.101.3b', '101', '', '');
+QUERY: insert into WSlot values ('WS.102.1a', '102', '', '');
+QUERY: insert into WSlot values ('WS.102.1b', '102', '', '');
+QUERY: insert into WSlot values ('WS.102.2a', '102', '', '');
+QUERY: insert into WSlot values ('WS.102.2b', '102', '', '');
+QUERY: insert into WSlot values ('WS.102.3a', '102', '', '');
+QUERY: insert into WSlot values ('WS.102.3b', '102', '', '');
+QUERY: insert into WSlot values ('WS.105.1a', '105', '', '');
+QUERY: insert into WSlot values ('WS.105.1b', '105', '', '');
+QUERY: insert into WSlot values ('WS.105.2a', '105', '', '');
+QUERY: insert into WSlot values ('WS.105.2b', '105', '', '');
+QUERY: insert into WSlot values ('WS.105.3a', '105', '', '');
+QUERY: insert into WSlot values ('WS.105.3b', '105', '', '');
+QUERY: insert into WSlot values ('WS.106.1a', '106', '', '');
+QUERY: insert into WSlot values ('WS.106.1b', '106', '', '');
+QUERY: insert into WSlot values ('WS.106.2a', '106', '', '');
+QUERY: insert into WSlot values ('WS.106.2b', '106', '', '');
+QUERY: insert into WSlot values ('WS.106.3a', '106', '', '');
+QUERY: insert into WSlot values ('WS.106.3b', '106', '', '');
+QUERY: insert into PField values ('PF0_1', 'Wallslots basement');
+QUERY: insert into PSlot values ('PS.base.a1', 'PF0_1', '', '');
+QUERY: insert into PSlot values ('PS.base.a2', 'PF0_1', '', '');
+QUERY: insert into PSlot values ('PS.base.a3', 'PF0_1', '', '');
+QUERY: insert into PSlot values ('PS.base.a4', 'PF0_1', '', '');
+QUERY: insert into PSlot values ('PS.base.a5', 'PF0_1', '', '');
+QUERY: insert into PSlot values ('PS.base.a6', 'PF0_1', '', '');
+QUERY: insert into PSlot values ('PS.base.b1', 'PF0_1', '', 'WS.002.1a');
+QUERY: insert into PSlot values ('PS.base.b2', 'PF0_1', '', 'WS.002.1b');
+QUERY: insert into PSlot values ('PS.base.b3', 'PF0_1', '', 'WS.002.2a');
+QUERY: insert into PSlot values ('PS.base.b4', 'PF0_1', '', 'WS.002.2b');
+QUERY: insert into PSlot values ('PS.base.b5', 'PF0_1', '', 'WS.002.3a');
+QUERY: insert into PSlot values ('PS.base.b6', 'PF0_1', '', 'WS.002.3b');
+QUERY: insert into PSlot values ('PS.base.c1', 'PF0_1', '', 'WS.003.1a');
+QUERY: insert into PSlot values ('PS.base.c2', 'PF0_1', '', 'WS.003.1b');
+QUERY: insert into PSlot values ('PS.base.c3', 'PF0_1', '', 'WS.003.2a');
+QUERY: insert into PSlot values ('PS.base.c4', 'PF0_1', '', 'WS.003.2b');
+QUERY: insert into PSlot values ('PS.base.c5', 'PF0_1', '', 'WS.003.3a');
+QUERY: insert into PSlot values ('PS.base.c6', 'PF0_1', '', 'WS.003.3b');
+QUERY: insert into PField values ('PF0_X', 'Phonelines basement');
+QUERY: insert into PSlot values ('PS.base.ta1', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.ta2', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.ta3', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.ta4', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.ta5', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.ta6', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.tb1', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.tb2', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.tb3', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.tb4', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.tb5', 'PF0_X', '', '');
+QUERY: insert into PSlot values ('PS.base.tb6', 'PF0_X', '', '');
+QUERY: insert into PField values ('PF1_1', 'Wallslots 1st floor');
+QUERY: insert into PSlot values ('PS.1st.a1', 'PF1_1', '', 'WS.101.1a');
+QUERY: insert into PSlot values ('PS.1st.a2', 'PF1_1', '', 'WS.101.1b');
+QUERY: insert into PSlot values ('PS.1st.a3', 'PF1_1', '', 'WS.101.2a');
+QUERY: insert into PSlot values ('PS.1st.a4', 'PF1_1', '', 'WS.101.2b');
+QUERY: insert into PSlot values ('PS.1st.a5', 'PF1_1', '', 'WS.101.3a');
+QUERY: insert into PSlot values ('PS.1st.a6', 'PF1_1', '', 'WS.101.3b');
+QUERY: insert into PSlot values ('PS.1st.b1', 'PF1_1', '', 'WS.102.1a');
+QUERY: insert into PSlot values ('PS.1st.b2', 'PF1_1', '', 'WS.102.1b');
+QUERY: insert into PSlot values ('PS.1st.b3', 'PF1_1', '', 'WS.102.2a');
+QUERY: insert into PSlot values ('PS.1st.b4', 'PF1_1', '', 'WS.102.2b');
+QUERY: insert into PSlot values ('PS.1st.b5', 'PF1_1', '', 'WS.102.3a');
+QUERY: insert into PSlot values ('PS.1st.b6', 'PF1_1', '', 'WS.102.3b');
+QUERY: insert into PSlot values ('PS.1st.c1', 'PF1_1', '', 'WS.105.1a');
+QUERY: insert into PSlot values ('PS.1st.c2', 'PF1_1', '', 'WS.105.1b');
+QUERY: insert into PSlot values ('PS.1st.c3', 'PF1_1', '', 'WS.105.2a');
+QUERY: insert into PSlot values ('PS.1st.c4', 'PF1_1', '', 'WS.105.2b');
+QUERY: insert into PSlot values ('PS.1st.c5', 'PF1_1', '', 'WS.105.3a');
+QUERY: insert into PSlot values ('PS.1st.c6', 'PF1_1', '', 'WS.105.3b');
+QUERY: insert into PSlot values ('PS.1st.d1', 'PF1_1', '', 'WS.106.1a');
+QUERY: insert into PSlot values ('PS.1st.d2', 'PF1_1', '', 'WS.106.1b');
+QUERY: insert into PSlot values ('PS.1st.d3', 'PF1_1', '', 'WS.106.2a');
+QUERY: insert into PSlot values ('PS.1st.d4', 'PF1_1', '', 'WS.106.2b');
+QUERY: insert into PSlot values ('PS.1st.d5', 'PF1_1', '', 'WS.106.3a');
+QUERY: insert into PSlot values ('PS.1st.d6', 'PF1_1', '', 'WS.106.3b');
+QUERY: update PSlot set backlink = 'WS.001.1a' where slotname = 'PS.base.a1';
+QUERY: update PSlot set backlink = 'WS.001.1b' where slotname = 'PS.base.a3';
+QUERY: select * from WSlot where roomno = '001' order by slotname;
+slotname | roomno| slotlink|backlink
+--------------------+--------+--------------------+--------------------
+WS.001.1a |001 | |PS.base.a1
+WS.001.1b |001 | |PS.base.a3
+WS.001.2a |001 | |
+WS.001.2b |001 | |
+WS.001.3a |001 | |
+WS.001.3b |001 | |
+(6 rows)
+
+QUERY: select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+slotname |pfname| slotlink|backlink
+--------------------+------+--------------------+--------------------
+PS.base.a1 |PF0_1 | |WS.001.1a
+PS.base.a2 |PF0_1 | |
+PS.base.a3 |PF0_1 | |WS.001.1b
+PS.base.a4 |PF0_1 | |
+PS.base.a5 |PF0_1 | |
+PS.base.a6 |PF0_1 | |
+(6 rows)
+
+QUERY: update PSlot set backlink = 'WS.001.2a' where slotname = 'PS.base.a3';
+QUERY: select * from WSlot where roomno = '001' order by slotname;
+slotname | roomno| slotlink|backlink
+--------------------+--------+--------------------+--------------------
+WS.001.1a |001 | |PS.base.a1
+WS.001.1b |001 | |
+WS.001.2a |001 | |PS.base.a3
+WS.001.2b |001 | |
+WS.001.3a |001 | |
+WS.001.3b |001 | |
+(6 rows)
+
+QUERY: select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+slotname |pfname| slotlink|backlink
+--------------------+------+--------------------+--------------------
+PS.base.a1 |PF0_1 | |WS.001.1a
+PS.base.a2 |PF0_1 | |
+PS.base.a3 |PF0_1 | |WS.001.2a
+PS.base.a4 |PF0_1 | |
+PS.base.a5 |PF0_1 | |
+PS.base.a6 |PF0_1 | |
+(6 rows)
+
+QUERY: update PSlot set backlink = 'WS.001.1b' where slotname = 'PS.base.a2';
+QUERY: select * from WSlot where roomno = '001' order by slotname;
+slotname | roomno| slotlink|backlink
+--------------------+--------+--------------------+--------------------
+WS.001.1a |001 | |PS.base.a1
+WS.001.1b |001 | |PS.base.a2
+WS.001.2a |001 | |PS.base.a3
+WS.001.2b |001 | |
+WS.001.3a |001 | |
+WS.001.3b |001 | |
+(6 rows)
+
+QUERY: select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+slotname |pfname| slotlink|backlink
+--------------------+------+--------------------+--------------------
+PS.base.a1 |PF0_1 | |WS.001.1a
+PS.base.a2 |PF0_1 | |WS.001.1b
+PS.base.a3 |PF0_1 | |WS.001.2a
+PS.base.a4 |PF0_1 | |
+PS.base.a5 |PF0_1 | |
+PS.base.a6 |PF0_1 | |
+(6 rows)
+
+QUERY: update WSlot set backlink = 'PS.base.a4' where slotname = 'WS.001.2b';
+QUERY: update WSlot set backlink = 'PS.base.a6' where slotname = 'WS.001.3a';
+QUERY: select * from WSlot where roomno = '001' order by slotname;
+slotname | roomno| slotlink|backlink
+--------------------+--------+--------------------+--------------------
+WS.001.1a |001 | |PS.base.a1
+WS.001.1b |001 | |PS.base.a2
+WS.001.2a |001 | |PS.base.a3
+WS.001.2b |001 | |PS.base.a4
+WS.001.3a |001 | |PS.base.a6
+WS.001.3b |001 | |
+(6 rows)
+
+QUERY: select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+slotname |pfname| slotlink|backlink
+--------------------+------+--------------------+--------------------
+PS.base.a1 |PF0_1 | |WS.001.1a
+PS.base.a2 |PF0_1 | |WS.001.1b
+PS.base.a3 |PF0_1 | |WS.001.2a
+PS.base.a4 |PF0_1 | |WS.001.2b
+PS.base.a5 |PF0_1 | |
+PS.base.a6 |PF0_1 | |WS.001.3a
+(6 rows)
+
+QUERY: update WSlot set backlink = 'PS.base.a6' where slotname = 'WS.001.3b';
+QUERY: select * from WSlot where roomno = '001' order by slotname;
+slotname | roomno| slotlink|backlink
+--------------------+--------+--------------------+--------------------
+WS.001.1a |001 | |PS.base.a1
+WS.001.1b |001 | |PS.base.a2
+WS.001.2a |001 | |PS.base.a3
+WS.001.2b |001 | |PS.base.a4
+WS.001.3a |001 | |
+WS.001.3b |001 | |PS.base.a6
+(6 rows)
+
+QUERY: select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+slotname |pfname| slotlink|backlink
+--------------------+------+--------------------+--------------------
+PS.base.a1 |PF0_1 | |WS.001.1a
+PS.base.a2 |PF0_1 | |WS.001.1b
+PS.base.a3 |PF0_1 | |WS.001.2a
+PS.base.a4 |PF0_1 | |WS.001.2b
+PS.base.a5 |PF0_1 | |
+PS.base.a6 |PF0_1 | |WS.001.3b
+(6 rows)
+
+QUERY: update WSlot set backlink = 'PS.base.a5' where slotname = 'WS.001.3a';
+QUERY: select * from WSlot where roomno = '001' order by slotname;
+slotname | roomno| slotlink|backlink
+--------------------+--------+--------------------+--------------------
+WS.001.1a |001 | |PS.base.a1
+WS.001.1b |001 | |PS.base.a2
+WS.001.2a |001 | |PS.base.a3
+WS.001.2b |001 | |PS.base.a4
+WS.001.3a |001 | |PS.base.a5
+WS.001.3b |001 | |PS.base.a6
+(6 rows)
+
+QUERY: select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+slotname |pfname| slotlink|backlink
+--------------------+------+--------------------+--------------------
+PS.base.a1 |PF0_1 | |WS.001.1a
+PS.base.a2 |PF0_1 | |WS.001.1b
+PS.base.a3 |PF0_1 | |WS.001.2a
+PS.base.a4 |PF0_1 | |WS.001.2b
+PS.base.a5 |PF0_1 | |WS.001.3a
+PS.base.a6 |PF0_1 | |WS.001.3b
+(6 rows)
+
+QUERY: insert into PField values ('PF1_2', 'Phonelines 1st floor');
+QUERY: insert into PSlot values ('PS.1st.ta1', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.ta2', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.ta3', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.ta4', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.ta5', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.ta6', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.tb1', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.tb2', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.tb3', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.tb4', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.tb5', 'PF1_2', '', '');
+QUERY: insert into PSlot values ('PS.1st.tb6', 'PF1_2', '', '');
+QUERY: update PField set name = 'PF0_2' where name = 'PF0_X';
+QUERY: select * from PSlot order by slotname;
+slotname |pfname| slotlink|backlink
+--------------------+------+--------------------+--------------------
+PS.1st.a1 |PF1_1 | |WS.101.1a
+PS.1st.a2 |PF1_1 | |WS.101.1b
+PS.1st.a3 |PF1_1 | |WS.101.2a
+PS.1st.a4 |PF1_1 | |WS.101.2b
+PS.1st.a5 |PF1_1 | |WS.101.3a
+PS.1st.a6 |PF1_1 | |WS.101.3b
+PS.1st.b1 |PF1_1 | |WS.102.1a
+PS.1st.b2 |PF1_1 | |WS.102.1b
+PS.1st.b3 |PF1_1 | |WS.102.2a
+PS.1st.b4 |PF1_1 | |WS.102.2b
+PS.1st.b5 |PF1_1 | |WS.102.3a
+PS.1st.b6 |PF1_1 | |WS.102.3b
+PS.1st.c1 |PF1_1 | |WS.105.1a
+PS.1st.c2 |PF1_1 | |WS.105.1b
+PS.1st.c3 |PF1_1 | |WS.105.2a
+PS.1st.c4 |PF1_1 | |WS.105.2b
+PS.1st.c5 |PF1_1 | |WS.105.3a
+PS.1st.c6 |PF1_1 | |WS.105.3b
+PS.1st.d1 |PF1_1 | |WS.106.1a
+PS.1st.d2 |PF1_1 | |WS.106.1b
+PS.1st.d3 |PF1_1 | |WS.106.2a
+PS.1st.d4 |PF1_1 | |WS.106.2b
+PS.1st.d5 |PF1_1 | |WS.106.3a
+PS.1st.d6 |PF1_1 | |WS.106.3b
+PS.1st.ta1 |PF1_2 | |
+PS.1st.ta2 |PF1_2 | |
+PS.1st.ta3 |PF1_2 | |
+PS.1st.ta4 |PF1_2 | |
+PS.1st.ta5 |PF1_2 | |
+PS.1st.ta6 |PF1_2 | |
+PS.1st.tb1 |PF1_2 | |
+PS.1st.tb2 |PF1_2 | |
+PS.1st.tb3 |PF1_2 | |
+PS.1st.tb4 |PF1_2 | |
+PS.1st.tb5 |PF1_2 | |
+PS.1st.tb6 |PF1_2 | |
+PS.base.a1 |PF0_1 | |WS.001.1a
+PS.base.a2 |PF0_1 | |WS.001.1b
+PS.base.a3 |PF0_1 | |WS.001.2a
+PS.base.a4 |PF0_1 | |WS.001.2b
+PS.base.a5 |PF0_1 | |WS.001.3a
+PS.base.a6 |PF0_1 | |WS.001.3b
+PS.base.b1 |PF0_1 | |WS.002.1a
+PS.base.b2 |PF0_1 | |WS.002.1b
+PS.base.b3 |PF0_1 | |WS.002.2a
+PS.base.b4 |PF0_1 | |WS.002.2b
+PS.base.b5 |PF0_1 | |WS.002.3a
+PS.base.b6 |PF0_1 | |WS.002.3b
+PS.base.c1 |PF0_1 | |WS.003.1a
+PS.base.c2 |PF0_1 | |WS.003.1b
+PS.base.c3 |PF0_1 | |WS.003.2a
+PS.base.c4 |PF0_1 | |WS.003.2b
+PS.base.c5 |PF0_1 | |WS.003.3a
+PS.base.c6 |PF0_1 | |WS.003.3b
+PS.base.ta1 |PF0_2 | |
+PS.base.ta2 |PF0_2 | |
+PS.base.ta3 |PF0_2 | |
+PS.base.ta4 |PF0_2 | |
+PS.base.ta5 |PF0_2 | |
+PS.base.ta6 |PF0_2 | |
+PS.base.tb1 |PF0_2 | |
+PS.base.tb2 |PF0_2 | |
+PS.base.tb3 |PF0_2 | |
+PS.base.tb4 |PF0_2 | |
+PS.base.tb5 |PF0_2 | |
+PS.base.tb6 |PF0_2 | |
+(66 rows)
+
+QUERY: select * from WSlot order by slotname;
+slotname | roomno| slotlink|backlink
+--------------------+--------+--------------------+--------------------
+WS.001.1a |001 | |PS.base.a1
+WS.001.1b |001 | |PS.base.a2
+WS.001.2a |001 | |PS.base.a3
+WS.001.2b |001 | |PS.base.a4
+WS.001.3a |001 | |PS.base.a5
+WS.001.3b |001 | |PS.base.a6
+WS.002.1a |002 | |PS.base.b1
+WS.002.1b |002 | |PS.base.b2
+WS.002.2a |002 | |PS.base.b3
+WS.002.2b |002 | |PS.base.b4
+WS.002.3a |002 | |PS.base.b5
+WS.002.3b |002 | |PS.base.b6
+WS.003.1a |003 | |PS.base.c1
+WS.003.1b |003 | |PS.base.c2
+WS.003.2a |003 | |PS.base.c3
+WS.003.2b |003 | |PS.base.c4
+WS.003.3a |003 | |PS.base.c5
+WS.003.3b |003 | |PS.base.c6
+WS.101.1a |101 | |PS.1st.a1
+WS.101.1b |101 | |PS.1st.a2
+WS.101.2a |101 | |PS.1st.a3
+WS.101.2b |101 | |PS.1st.a4
+WS.101.3a |101 | |PS.1st.a5
+WS.101.3b |101 | |PS.1st.a6
+WS.102.1a |102 | |PS.1st.b1
+WS.102.1b |102 | |PS.1st.b2
+WS.102.2a |102 | |PS.1st.b3
+WS.102.2b |102 | |PS.1st.b4
+WS.102.3a |102 | |PS.1st.b5
+WS.102.3b |102 | |PS.1st.b6
+WS.105.1a |105 | |PS.1st.c1
+WS.105.1b |105 | |PS.1st.c2
+WS.105.2a |105 | |PS.1st.c3
+WS.105.2b |105 | |PS.1st.c4
+WS.105.3a |105 | |PS.1st.c5
+WS.105.3b |105 | |PS.1st.c6
+WS.106.1a |106 | |PS.1st.d1
+WS.106.1b |106 | |PS.1st.d2
+WS.106.2a |106 | |PS.1st.d3
+WS.106.2b |106 | |PS.1st.d4
+WS.106.3a |106 | |PS.1st.d5
+WS.106.3b |106 | |PS.1st.d6
+(42 rows)
+
+QUERY: insert into PLine values ('PL.001', '-0', 'Central call', 'PS.base.ta1');
+QUERY: insert into PLine values ('PL.002', '-101', '', 'PS.base.ta2');
+QUERY: insert into PLine values ('PL.003', '-102', '', 'PS.base.ta3');
+QUERY: insert into PLine values ('PL.004', '-103', '', 'PS.base.ta5');
+QUERY: insert into PLine values ('PL.005', '-104', '', 'PS.base.ta6');
+QUERY: insert into PLine values ('PL.006', '-106', '', 'PS.base.tb2');
+QUERY: insert into PLine values ('PL.007', '-108', '', 'PS.base.tb3');
+QUERY: insert into PLine values ('PL.008', '-109', '', 'PS.base.tb4');
+QUERY: insert into PLine values ('PL.009', '-121', '', 'PS.base.tb5');
+QUERY: insert into PLine values ('PL.010', '-122', '', 'PS.base.tb6');
+QUERY: insert into PLine values ('PL.015', '-134', '', 'PS.1st.ta1');
+QUERY: insert into PLine values ('PL.016', '-137', '', 'PS.1st.ta3');
+QUERY: insert into PLine values ('PL.017', '-139', '', 'PS.1st.ta4');
+QUERY: insert into PLine values ('PL.018', '-362', '', 'PS.1st.tb1');
+QUERY: insert into PLine values ('PL.019', '-363', '', 'PS.1st.tb2');
+QUERY: insert into PLine values ('PL.020', '-364', '', 'PS.1st.tb3');
+QUERY: insert into PLine values ('PL.021', '-365', '', 'PS.1st.tb5');
+QUERY: insert into PLine values ('PL.022', '-367', '', 'PS.1st.tb6');
+QUERY: insert into PLine values ('PL.028', '-501', 'Fax entrance', 'PS.base.ta2');
+QUERY: insert into PLine values ('PL.029', '-502', 'Fax 1st floor', 'PS.1st.ta1');
+QUERY: insert into PHone values ('PH.hc001', 'Hicom standard', 'WS.001.1a');
+QUERY: update PSlot set slotlink = 'PS.base.ta1' where slotname = 'PS.base.a1';
+QUERY: insert into PHone values ('PH.hc002', 'Hicom standard', 'WS.002.1a');
+QUERY: update PSlot set slotlink = 'PS.base.ta5' where slotname = 'PS.base.b1';
+QUERY: insert into PHone values ('PH.hc003', 'Hicom standard', 'WS.002.2a');
+QUERY: update PSlot set slotlink = 'PS.base.tb2' where slotname = 'PS.base.b3';
+QUERY: insert into PHone values ('PH.fax001', 'Canon fax', 'WS.001.2a');
+QUERY: update PSlot set slotlink = 'PS.base.ta2' where slotname = 'PS.base.a3';
+QUERY: insert into Hub values ('base.hub1', 'Patchfield PF0_1 hub', 16);
+QUERY: insert into System values ('orion', 'PC');
+QUERY: insert into IFace values ('IF', 'orion', 'eth0', 'WS.002.1b');
+QUERY: update PSlot set slotlink = 'HS.base.hub1.1' where slotname = 'PS.base.b2';
+QUERY: select * from PField_v1 where pfname = 'PF0_1' order by slotname;
+pfname|slotname |backside |patch
+------+--------------------+--------------------------------------------------------+---------------------------------------------
+PF0_1 |PS.base.a1 |WS.001.1a in room 001 -> Phone PH.hc001 (Hicom standard)|PS.base.ta1 -> Phone line -0 (Central call)
+PF0_1 |PS.base.a2 |WS.001.1b in room 001 -> - |-
+PF0_1 |PS.base.a3 |WS.001.2a in room 001 -> Phone PH.fax001 (Canon fax) |PS.base.ta2 -> Phone line -501 (Fax entrance)
+PF0_1 |PS.base.a4 |WS.001.2b in room 001 -> - |-
+PF0_1 |PS.base.a5 |WS.001.3a in room 001 -> - |-
+PF0_1 |PS.base.a6 |WS.001.3b in room 001 -> - |-
+PF0_1 |PS.base.b1 |WS.002.1a in room 002 -> Phone PH.hc002 (Hicom standard)|PS.base.ta5 -> Phone line -103
+PF0_1 |PS.base.b2 |WS.002.1b in room 002 -> orion IF eth0 (PC) |Patchfield PF0_1 hub slot 1
+PF0_1 |PS.base.b3 |WS.002.2a in room 002 -> Phone PH.hc003 (Hicom standard)|PS.base.tb2 -> Phone line -106
+PF0_1 |PS.base.b4 |WS.002.2b in room 002 -> - |-
+PF0_1 |PS.base.b5 |WS.002.3a in room 002 -> - |-
+PF0_1 |PS.base.b6 |WS.002.3b in room 002 -> - |-
+PF0_1 |PS.base.c1 |WS.003.1a in room 003 -> - |-
+PF0_1 |PS.base.c2 |WS.003.1b in room 003 -> - |-
+PF0_1 |PS.base.c3 |WS.003.2a in room 003 -> - |-
+PF0_1 |PS.base.c4 |WS.003.2b in room 003 -> - |-
+PF0_1 |PS.base.c5 |WS.003.3a in room 003 -> - |-
+PF0_1 |PS.base.c6 |WS.003.3b in room 003 -> - |-
+(18 rows)
+
+QUERY: select * from PField_v1 where pfname = 'PF0_2' order by slotname;
+pfname|slotname |backside |patch
+------+--------------------+------------------------------+----------------------------------------------------------------------
+PF0_2 |PS.base.ta1 |Phone line -0 (Central call) |PS.base.a1 -> WS.001.1a in room 001 -> Phone PH.hc001 (Hicom standard)
+PF0_2 |PS.base.ta2 |Phone line -501 (Fax entrance)|PS.base.a3 -> WS.001.2a in room 001 -> Phone PH.fax001 (Canon fax)
+PF0_2 |PS.base.ta3 |Phone line -102 |-
+PF0_2 |PS.base.ta4 |- |-
+PF0_2 |PS.base.ta5 |Phone line -103 |PS.base.b1 -> WS.002.1a in room 002 -> Phone PH.hc002 (Hicom standard)
+PF0_2 |PS.base.ta6 |Phone line -104 |-
+PF0_2 |PS.base.tb1 |- |-
+PF0_2 |PS.base.tb2 |Phone line -106 |PS.base.b3 -> WS.002.2a in room 002 -> Phone PH.hc003 (Hicom standard)
+PF0_2 |PS.base.tb3 |Phone line -108 |-
+PF0_2 |PS.base.tb4 |Phone line -109 |-
+PF0_2 |PS.base.tb5 |Phone line -121 |-
+PF0_2 |PS.base.tb6 |Phone line -122 |-
+(12 rows)
+
+QUERY: insert into PField values ('PF1_1', 'should fail due to unique index');
+ERROR: Cannot insert a duplicate key into a unique index
+QUERY: update PSlot set backlink = 'WS.not.there' where slotname = 'PS.base.a1';
+ERROR: WS.not.there does not exists
+QUERY: update PSlot set backlink = 'XX.illegal' where slotname = 'PS.base.a1';
+ERROR: illegal backlink beginning with XX
+QUERY: update PSlot set slotlink = 'PS.not.there' where slotname = 'PS.base.a1';
+ERROR: PS.not.there does not exists
+QUERY: update PSlot set slotlink = 'XX.illegal' where slotname = 'PS.base.a1';
+ERROR: illegal slotlink beginning with XX
+QUERY: insert into HSlot values ('HS', 'base.hub1', 1, '');
+ERROR: Cannot insert a duplicate key into a unique index
+QUERY: insert into HSlot values ('HS', 'base.hub1', 20, '');
+ERROR: no manual manipulation of HSlot
+QUERY: delete from HSlot;
+ERROR: no manual manipulation of HSlot
+QUERY: insert into IFace values ('IF', 'notthere', 'eth0', '');
+ERROR: system "notthere" does not exist
+QUERY: insert into IFace values ('IF', 'orion', 'ethernet_interface_name_too_long', '');
+ERROR: IFace slotname "IF.orion.ethernet_interface_name_too_long" too long (20 char max)
--- /dev/null
+QUERY: create function tg_room_au() returns opaque as '
+begin
+ if new.roomno != old.roomno then
+ update WSlot set roomno = new.roomno where roomno = old.roomno;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_room_au after update
+ on Room for each row execute procedure tg_room_au();
+QUERY: create function tg_room_ad() returns opaque as '
+begin
+ delete from WSlot where roomno = old.roomno;
+ return old;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_room_ad after delete
+ on Room for each row execute procedure tg_room_ad();
+QUERY: create function tg_wslot_biu() returns opaque as '
+begin
+ if count(*) = 0 from Room where roomno = new.roomno then
+ raise exception ''Room % does not exist'', new.roomno;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_wslot_biu before insert or update
+ on WSlot for each row execute procedure tg_wslot_biu();
+QUERY: create function tg_pfield_au() returns opaque as '
+begin
+ if new.name != old.name then
+ update PSlot set pfname = new.name where pfname = old.name;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_pfield_au after update
+ on PField for each row execute procedure tg_pfield_au();
+QUERY: create function tg_pfield_ad() returns opaque as '
+begin
+ delete from PSlot where pfname = old.name;
+ return old;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_pfield_ad after delete
+ on PField for each row execute procedure tg_pfield_ad();
+QUERY: create function tg_pslot_biu() returns opaque as '
+declare
+ pfrec record;
+ rename new to ps;
+begin
+ select into pfrec * from PField where name = ps.pfname;
+ if not found then
+ raise exception ''Patchfield "%" does not exist'', ps.pfname;
+ end if;
+ return ps;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_pslot_biu before insert or update
+ on PSlot for each row execute procedure tg_pslot_biu();
+QUERY: create function tg_system_au() returns opaque as '
+begin
+ if new.name != old.name then
+ update IFace set sysname = new.name where sysname = old.name;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_system_au after update
+ on System for each row execute procedure tg_system_au();
+QUERY: create function tg_iface_biu() returns opaque as '
+declare
+ sname text;
+ sysrec record;
+begin
+ select into sysrec * from system where name = new.sysname;
+ if not found then
+ raise exception ''system "%" does not exist'', new.sysname;
+ end if;
+ sname := ''IF.'' || new.sysname;
+ sname := sname || ''.'';
+ sname := sname || new.ifname;
+ if length(sname) > 20 then
+ raise exception ''IFace slotname "%" too long (20 char max)'', sname;
+ end if;
+ new.slotname := sname;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_iface_biu before insert or update
+ on IFace for each row execute procedure tg_iface_biu();
+QUERY: create function tg_hub_a() returns opaque as '
+declare
+ hname text;
+ dummy integer;
+begin
+ if tg_op = ''INSERT'' then
+ dummy := tg_hub_adjustslots(new.name, 0, new.nslots);
+ return new;
+ end if;
+ if tg_op = ''UPDATE'' then
+ if new.name != old.name then
+ update HSlot set hubname = new.name where hubname = old.name;
+ end if;
+ dummy := tg_hub_adjustslots(new.name, old.nslots, new.nslots);
+ return new;
+ end if;
+ if tg_op = ''DELETE'' then
+ dummy := tg_hub_adjustslots(old.name, old.nslots, 0);
+ return old;
+ end if;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_hub_a after insert or update or delete
+ on Hub for each row execute procedure tg_hub_a();
+QUERY: create function tg_hub_adjustslots(bpchar, integer, integer)
+returns integer as '
+declare
+ hname alias for $1;
+ oldnslots alias for $2;
+ newnslots alias for $3;
+begin
+ if newnslots = oldnslots then
+ return 0;
+ end if;
+ if newnslots < oldnslots then
+ delete from HSlot where hubname = hname and slotno > newnslots;
+ return 0;
+ end if;
+ for i in oldnslots + 1 .. newnslots loop
+ insert into HSlot (slotname, hubname, slotno, slotlink)
+ values (''HS.dummy'', hname, i, '''');
+ end loop;
+ return 0;
+end;
+' language 'plpgsql';
+QUERY: create function tg_hslot_biu() returns opaque as '
+declare
+ sname text;
+ xname HSlot.slotname%TYPE;
+ hubrec record;
+begin
+ select into hubrec * from Hub where name = new.hubname;
+ if not found then
+ raise exception ''no manual manipulation of HSlot'';
+ end if;
+ if new.slotno < 1 or new.slotno > hubrec.nslots then
+ raise exception ''no manual manipulation of HSlot'';
+ end if;
+ if tg_op = ''UPDATE'' then
+ if new.hubname != old.hubname then
+ if count(*) > 0 from Hub where name = old.hubname then
+ raise exception ''no manual manipulation of HSlot'';
+ end if;
+ end if;
+ end if;
+ sname := ''HS.'' || trim(new.hubname);
+ sname := sname || ''.'';
+ sname := sname || new.slotno::text;
+ if length(sname) > 20 then
+ raise exception ''HSlot slotname "%" too long (20 char max)'', sname;
+ end if;
+ new.slotname := sname;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_hslot_biu before insert or update
+ on HSlot for each row execute procedure tg_hslot_biu();
+QUERY: create function tg_hslot_bd() returns opaque as '
+declare
+ hubrec record;
+begin
+ select into hubrec * from Hub where name = old.hubname;
+ if not found then
+ return old;
+ end if;
+ if old.slotno > hubrec.nslots then
+ return old;
+ end if;
+ raise exception ''no manual manipulation of HSlot'';
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_hslot_bd before delete
+ on HSlot for each row execute procedure tg_hslot_bd();
+QUERY: create function tg_chkslotname() returns opaque as '
+begin
+ if substr(new.slotname, 1, 2) != tg_argv[0] then
+ raise exception ''slotname must begin with %'', tg_argv[0];
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_chkslotname before insert
+ on PSlot for each row execute procedure tg_chkslotname('PS');
+QUERY: create trigger tg_chkslotname before insert
+ on WSlot for each row execute procedure tg_chkslotname('WS');
+QUERY: create trigger tg_chkslotname before insert
+ on PLine for each row execute procedure tg_chkslotname('PL');
+QUERY: create trigger tg_chkslotname before insert
+ on IFace for each row execute procedure tg_chkslotname('IF');
+QUERY: create trigger tg_chkslotname before insert
+ on PHone for each row execute procedure tg_chkslotname('PH');
+QUERY: create function tg_chkslotlink() returns opaque as '
+begin
+ if new.slotlink isnull then
+ new.slotlink := '''';
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_chkslotlink before insert or update
+ on PSlot for each row execute procedure tg_chkslotlink();
+QUERY: create trigger tg_chkslotlink before insert or update
+ on WSlot for each row execute procedure tg_chkslotlink();
+QUERY: create trigger tg_chkslotlink before insert or update
+ on IFace for each row execute procedure tg_chkslotlink();
+QUERY: create trigger tg_chkslotlink before insert or update
+ on HSlot for each row execute procedure tg_chkslotlink();
+QUERY: create trigger tg_chkslotlink before insert or update
+ on PHone for each row execute procedure tg_chkslotlink();
+QUERY: create function tg_chkbacklink() returns opaque as '
+begin
+ if new.backlink isnull then
+ new.backlink := '''';
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_chkbacklink before insert or update
+ on PSlot for each row execute procedure tg_chkbacklink();
+QUERY: create trigger tg_chkbacklink before insert or update
+ on WSlot for each row execute procedure tg_chkbacklink();
+QUERY: create trigger tg_chkbacklink before insert or update
+ on PLine for each row execute procedure tg_chkbacklink();
+QUERY: create function tg_pslot_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from PSlot where slotname = old.slotname;
+ insert into PSlot (
+ slotname,
+ pfname,
+ slotlink,
+ backlink
+ ) values (
+ new.slotname,
+ new.pfname,
+ new.slotlink,
+ new.backlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_pslot_bu before update
+ on PSlot for each row execute procedure tg_pslot_bu();
+QUERY: create function tg_wslot_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from WSlot where slotname = old.slotname;
+ insert into WSlot (
+ slotname,
+ roomno,
+ slotlink,
+ backlink
+ ) values (
+ new.slotname,
+ new.roomno,
+ new.slotlink,
+ new.backlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_wslot_bu before update
+ on WSlot for each row execute procedure tg_Wslot_bu();
+QUERY: create function tg_pline_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from PLine where slotname = old.slotname;
+ insert into PLine (
+ slotname,
+ phonenumber,
+ comment,
+ backlink
+ ) values (
+ new.slotname,
+ new.phonenumber,
+ new.comment,
+ new.backlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_pline_bu before update
+ on PLine for each row execute procedure tg_pline_bu();
+QUERY: create function tg_iface_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from IFace where slotname = old.slotname;
+ insert into IFace (
+ slotname,
+ sysname,
+ ifname,
+ slotlink
+ ) values (
+ new.slotname,
+ new.sysname,
+ new.ifname,
+ new.slotlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_iface_bu before update
+ on IFace for each row execute procedure tg_iface_bu();
+QUERY: create function tg_hslot_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname or new.hubname != old.hubname then
+ delete from HSlot where slotname = old.slotname;
+ insert into HSlot (
+ slotname,
+ hubname,
+ slotno,
+ slotlink
+ ) values (
+ new.slotname,
+ new.hubname,
+ new.slotno,
+ new.slotlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_hslot_bu before update
+ on HSlot for each row execute procedure tg_hslot_bu();
+QUERY: create function tg_phone_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from PHone where slotname = old.slotname;
+ insert into PHone (
+ slotname,
+ comment,
+ slotlink
+ ) values (
+ new.slotname,
+ new.comment,
+ new.slotlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_phone_bu before update
+ on PHone for each row execute procedure tg_phone_bu();
+QUERY: create function tg_backlink_a() returns opaque as '
+declare
+ dummy integer;
+begin
+ if tg_op = ''INSERT'' then
+ if new.backlink != '''' then
+ dummy := tg_backlink_set(new.backlink, new.slotname);
+ end if;
+ return new;
+ end if;
+ if tg_op = ''UPDATE'' then
+ if new.backlink != old.backlink then
+ if old.backlink != '''' then
+ dummy := tg_backlink_unset(old.backlink, old.slotname);
+ end if;
+ if new.backlink != '''' then
+ dummy := tg_backlink_set(new.backlink, new.slotname);
+ end if;
+ else
+ if new.slotname != old.slotname and new.backlink != '''' then
+ dummy := tg_slotlink_set(new.backlink, new.slotname);
+ end if;
+ end if;
+ return new;
+ end if;
+ if tg_op = ''DELETE'' then
+ if old.backlink != '''' then
+ dummy := tg_backlink_unset(old.backlink, old.slotname);
+ end if;
+ return old;
+ end if;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_backlink_a after insert or update or delete
+ on PSlot for each row execute procedure tg_backlink_a('PS');
+QUERY: create trigger tg_backlink_a after insert or update or delete
+ on WSlot for each row execute procedure tg_backlink_a('WS');
+QUERY: create trigger tg_backlink_a after insert or update or delete
+ on PLine for each row execute procedure tg_backlink_a('PL');
+QUERY: create function tg_backlink_set(bpchar, bpchar)
+returns integer as '
+declare
+ myname alias for $1;
+ blname alias for $2;
+ mytype char(2);
+ link char(4);
+ rec record;
+begin
+ mytype := substr(myname, 1, 2);
+ link := mytype || substr(blname, 1, 2);
+ if link = ''PLPL'' then
+ raise exception
+ ''backlink between two phone lines does not make sense'';
+ end if;
+ if link in (''PLWS'', ''WSPL'') then
+ raise exception
+ ''direct link of phone line to wall slot not permitted'';
+ end if;
+ if mytype = ''PS'' then
+ select into rec * from PSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.backlink != blname then
+ update PSlot set backlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''WS'' then
+ select into rec * from WSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.backlink != blname then
+ update WSlot set backlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''PL'' then
+ select into rec * from PLine where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.backlink != blname then
+ update PLine set backlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ raise exception ''illegal backlink beginning with %'', mytype;
+end;
+' language 'plpgsql';
+QUERY: create function tg_backlink_unset(bpchar, bpchar)
+returns integer as '
+declare
+ myname alias for $1;
+ blname alias for $2;
+ mytype char(2);
+ rec record;
+begin
+ mytype := substr(myname, 1, 2);
+ if mytype = ''PS'' then
+ select into rec * from PSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.backlink = blname then
+ update PSlot set backlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''WS'' then
+ select into rec * from WSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.backlink = blname then
+ update WSlot set backlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''PL'' then
+ select into rec * from PLine where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.backlink = blname then
+ update PLine set backlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+end;
+' language 'plpgsql';
+QUERY: create function tg_slotlink_a() returns opaque as '
+declare
+ dummy integer;
+begin
+ if tg_op = ''INSERT'' then
+ if new.slotlink != '''' then
+ dummy := tg_slotlink_set(new.slotlink, new.slotname);
+ end if;
+ return new;
+ end if;
+ if tg_op = ''UPDATE'' then
+ if new.slotlink != old.slotlink then
+ if old.slotlink != '''' then
+ dummy := tg_slotlink_unset(old.slotlink, old.slotname);
+ end if;
+ if new.slotlink != '''' then
+ dummy := tg_slotlink_set(new.slotlink, new.slotname);
+ end if;
+ else
+ if new.slotname != old.slotname and new.slotlink != '''' then
+ dummy := tg_slotlink_set(new.slotlink, new.slotname);
+ end if;
+ end if;
+ return new;
+ end if;
+ if tg_op = ''DELETE'' then
+ if old.slotlink != '''' then
+ dummy := tg_slotlink_unset(old.slotlink, old.slotname);
+ end if;
+ return old;
+ end if;
+end;
+' language 'plpgsql';
+QUERY: create trigger tg_slotlink_a after insert or update or delete
+ on PSlot for each row execute procedure tg_slotlink_a('PS');
+QUERY: create trigger tg_slotlink_a after insert or update or delete
+ on WSlot for each row execute procedure tg_slotlink_a('WS');
+QUERY: create trigger tg_slotlink_a after insert or update or delete
+ on IFace for each row execute procedure tg_slotlink_a('IF');
+QUERY: create trigger tg_slotlink_a after insert or update or delete
+ on HSlot for each row execute procedure tg_slotlink_a('HS');
+QUERY: create trigger tg_slotlink_a after insert or update or delete
+ on PHone for each row execute procedure tg_slotlink_a('PH');
+QUERY: create function tg_slotlink_set(bpchar, bpchar)
+returns integer as '
+declare
+ myname alias for $1;
+ blname alias for $2;
+ mytype char(2);
+ link char(4);
+ rec record;
+begin
+ mytype := substr(myname, 1, 2);
+ link := mytype || substr(blname, 1, 2);
+ if link = ''PHPH'' then
+ raise exception
+ ''slotlink between two phones does not make sense'';
+ end if;
+ if link in (''PHHS'', ''HSPH'') then
+ raise exception
+ ''link of phone to hub does not make sense'';
+ end if;
+ if link in (''PHIF'', ''IFPH'') then
+ raise exception
+ ''link of phone to hub does not make sense'';
+ end if;
+ if link in (''PSWS'', ''WSPS'') then
+ raise exception
+ ''slotlink from patchslot to wallslot not permitted'';
+ end if;
+ if mytype = ''PS'' then
+ select into rec * from PSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update PSlot set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''WS'' then
+ select into rec * from WSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update WSlot set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''IF'' then
+ select into rec * from IFace where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update IFace set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''HS'' then
+ select into rec * from HSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update HSlot set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''PH'' then
+ select into rec * from PHone where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update PHone set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ raise exception ''illegal slotlink beginning with %'', mytype;
+end;
+' language 'plpgsql';
+QUERY: create function tg_slotlink_unset(bpchar, bpchar)
+returns integer as '
+declare
+ myname alias for $1;
+ blname alias for $2;
+ mytype char(2);
+ rec record;
+begin
+ mytype := substr(myname, 1, 2);
+ if mytype = ''PS'' then
+ select into rec * from PSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update PSlot set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''WS'' then
+ select into rec * from WSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update WSlot set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''IF'' then
+ select into rec * from IFace where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update IFace set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''HS'' then
+ select into rec * from HSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update HSlot set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''PH'' then
+ select into rec * from PHone where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update PHone set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+end;
+' language 'plpgsql';
--- /dev/null
+QUERY: create function pslot_backlink_view(bpchar)
+returns text as '
+<<outer>>
+declare
+ rec record;
+ bltype char(2);
+ retval text;
+begin
+ select into rec * from PSlot where slotname = $1;
+ if not found then
+ return '''';
+ end if;
+ if rec.backlink = '''' then
+ return ''-'';
+ end if;
+ bltype := substr(rec.backlink, 1, 2);
+ if bltype = ''PL'' then
+ declare
+ rec record;
+ begin
+ select into rec * from PLine where slotname = outer.rec.backlink;
+ retval := ''Phone line '' || trim(rec.phonenumber);
+ if rec.comment != '''' then
+ retval := retval || '' ('';
+ retval := retval || rec.comment;
+ retval := retval || '')'';
+ end if;
+ return retval;
+ end;
+ end if;
+ if bltype = ''WS'' then
+ select into rec * from WSlot where slotname = rec.backlink;
+ retval := trim(rec.slotname) || '' in room '';
+ retval := retval || trim(rec.roomno);
+ retval := retval || '' -> '';
+ return retval || wslot_slotlink_view(rec.slotname);
+ end if;
+ return rec.backlink;
+end;
+' language 'plpgsql';
+QUERY: create function pslot_slotlink_view(bpchar)
+returns text as '
+declare
+ psrec record;
+ sltype char(2);
+ retval text;
+begin
+ select into psrec * from PSlot where slotname = $1;
+ if not found then
+ return '''';
+ end if;
+ if psrec.slotlink = '''' then
+ return ''-'';
+ end if;
+ sltype := substr(psrec.slotlink, 1, 2);
+ if sltype = ''PS'' then
+ retval := trim(psrec.slotlink) || '' -> '';
+ return retval || pslot_backlink_view(psrec.slotlink);
+ end if;
+ if sltype = ''HS'' then
+ retval := comment from Hub H, HSlot HS
+ where HS.slotname = psrec.slotlink
+ and H.name = HS.hubname;
+ retval := retval || '' slot '';
+ retval := retval || slotno::text from HSlot
+ where slotname = psrec.slotlink;
+ return retval;
+ end if;
+ return psrec.slotlink;
+end;
+' language 'plpgsql';
+QUERY: create function wslot_slotlink_view(bpchar)
+returns text as '
+declare
+ rec record;
+ sltype char(2);
+ retval text;
+begin
+ select into rec * from WSlot where slotname = $1;
+ if not found then
+ return '''';
+ end if;
+ if rec.slotlink = '''' then
+ return ''-'';
+ end if;
+ sltype := substr(rec.slotlink, 1, 2);
+ if sltype = ''PH'' then
+ select into rec * from PHone where slotname = rec.slotlink;
+ retval := ''Phone '' || trim(rec.slotname);
+ if rec.comment != '''' then
+ retval := retval || '' ('';
+ retval := retval || rec.comment;
+ retval := retval || '')'';
+ end if;
+ return retval;
+ end if;
+ if sltype = ''IF'' then
+ declare
+ syrow System%RowType;
+ ifrow IFace%ROWTYPE;
+ begin
+ select into ifrow * from IFace where slotname = rec.slotlink;
+ select into syrow * from System where name = ifrow.sysname;
+ retval := syrow.name || '' IF '';
+ retval := retval || ifrow.ifname;
+ if syrow.comment != '''' then
+ retval := retval || '' ('';
+ retval := retval || syrow.comment;
+ retval := retval || '')'';
+ end if;
+ return retval;
+ end;
+ end if;
+ return rec.slotlink;
+end;
+' language 'plpgsql';
+QUERY: create view Pfield_v1 as select PF.pfname, PF.slotname,
+ pslot_backlink_view(PF.slotname) as backside,
+ pslot_slotlink_view(PF.slotname) as patch
+ from PSlot PF;
--- /dev/null
+--
+-- PL/pgSQL language declaration
+--
+-- $Header: /cvsroot/pgsql/contrib/plpgsql/test/Attic/mklang.sql,v 1.1 1998/08/22 12:38:36 momjian Exp $
+--
+
+create function plpgsql_call_handler() returns opaque
+ as '/usr/local/pgsql/lib/plpgsql.so'
+ language 'C';
+
+create trusted procedural language 'plpgsql'
+ handler plpgsql_call_handler
+ lancompiler 'PL/pgSQL';
+
--- /dev/null
+#!/bin/sh
+
+DB=plpgsql_test
+export DB
+
+FRONTEND="psql -n -e -q"
+export FRONTEND
+
+echo "*** destroy old $DB database ***"
+destroydb $DB
+
+echo "*** create new $DB database ***"
+createdb $DB
+
+echo "*** install PL/pgSQL ***"
+$FRONTEND -f mklang.sql -d $DB >/dev/null 2>&1
+
+echo "*** create tables ***"
+$FRONTEND -f tables.sql -d $DB >output/tables.out 2>&1
+if cmp -s output/tables.out expected/tables.out ; then
+ echo "OK"
+else
+ echo "FAILED"
+fi
+
+echo "*** create triggers ***"
+$FRONTEND -f triggers.sql -d $DB >output/triggers.out 2>&1
+if cmp -s output/triggers.out expected/triggers.out ; then
+ echo "OK"
+else
+ echo "FAILED"
+fi
+
+echo "*** create views and support functions ***"
+$FRONTEND -f views.sql -d $DB >output/views.out 2>&1
+if cmp -s output/views.out expected/views.out ; then
+ echo "OK"
+else
+ echo "FAILED"
+fi
+
+echo "*** running tests ***"
+$FRONTEND -f test.sql -d $DB >output/test.out 2>&1
+if cmp -s output/test.out expected/test.out ; then
+ echo "OK"
+else
+ echo "FAILED"
+fi
+
--- /dev/null
+-- ************************************************************
+-- *
+-- * Tables for the patchfield test of PL/pgSQL
+-- *
+-- * $Header: /cvsroot/pgsql/contrib/plpgsql/test/Attic/tables.sql,v 1.1 1998/08/22 12:38:36 momjian Exp $
+-- *
+-- ************************************************************
+
+create table Room (
+ roomno char(8),
+ comment text
+);
+
+create unique index Room_rno on Room using btree (roomno bpchar_ops);
+
+
+create table WSlot (
+ slotname char(20),
+ roomno char(8),
+ slotlink char(20),
+ backlink char(20)
+);
+
+create unique index WSlot_name on WSlot using btree (slotname bpchar_ops);
+
+
+create table PField (
+ name text,
+ comment text
+);
+
+create unique index PField_name on PField using btree (name text_ops);
+
+
+create table PSlot (
+ slotname char(20),
+ pfname text,
+ slotlink char(20),
+ backlink char(20)
+);
+
+create unique index PSlot_name on PSlot using btree (slotname bpchar_ops);
+
+
+create table PLine (
+ slotname char(20),
+ phonenumber char(20),
+ comment text,
+ backlink char(20)
+);
+
+create unique index PLine_name on PLine using btree (slotname bpchar_ops);
+
+
+create table Hub (
+ name char(14),
+ comment text,
+ nslots integer
+);
+
+create unique index Hub_name on Hub using btree (name bpchar_ops);
+
+
+create table HSlot (
+ slotname char(20),
+ hubname char(14),
+ slotno integer,
+ slotlink char(20)
+);
+
+create unique index HSlot_name on HSlot using btree (slotname bpchar_ops);
+create index HSlot_hubname on HSlot using btree (hubname bpchar_ops);
+
+
+create table System (
+ name text,
+ comment text
+);
+
+create unique index System_name on System using btree (name text_ops);
+
+
+create table IFace (
+ slotname char(20),
+ sysname text,
+ ifname text,
+ slotlink char(20)
+);
+
+create unique index IFace_name on IFace using btree (slotname bpchar_ops);
+
+
+create table PHone (
+ slotname char(20),
+ comment text,
+ slotlink char(20)
+);
+
+create unique index PHone_name on PHone using btree (slotname bpchar_ops);
+
+
--- /dev/null
+--
+-- First we build the house - so we create the rooms
+--
+insert into Room values ('001', 'Entrance');
+insert into Room values ('002', 'Office');
+insert into Room values ('003', 'Office');
+insert into Room values ('004', 'Technical');
+insert into Room values ('101', 'Office');
+insert into Room values ('102', 'Conference');
+insert into Room values ('103', 'Restroom');
+insert into Room values ('104', 'Technical');
+insert into Room values ('105', 'Office');
+insert into Room values ('106', 'Office');
+
+--
+-- Second we install the wall connectors
+--
+insert into WSlot values ('WS.001.1a', '001', '', '');
+insert into WSlot values ('WS.001.1b', '001', '', '');
+insert into WSlot values ('WS.001.2a', '001', '', '');
+insert into WSlot values ('WS.001.2b', '001', '', '');
+insert into WSlot values ('WS.001.3a', '001', '', '');
+insert into WSlot values ('WS.001.3b', '001', '', '');
+
+insert into WSlot values ('WS.002.1a', '002', '', '');
+insert into WSlot values ('WS.002.1b', '002', '', '');
+insert into WSlot values ('WS.002.2a', '002', '', '');
+insert into WSlot values ('WS.002.2b', '002', '', '');
+insert into WSlot values ('WS.002.3a', '002', '', '');
+insert into WSlot values ('WS.002.3b', '002', '', '');
+
+insert into WSlot values ('WS.003.1a', '003', '', '');
+insert into WSlot values ('WS.003.1b', '003', '', '');
+insert into WSlot values ('WS.003.2a', '003', '', '');
+insert into WSlot values ('WS.003.2b', '003', '', '');
+insert into WSlot values ('WS.003.3a', '003', '', '');
+insert into WSlot values ('WS.003.3b', '003', '', '');
+
+insert into WSlot values ('WS.101.1a', '101', '', '');
+insert into WSlot values ('WS.101.1b', '101', '', '');
+insert into WSlot values ('WS.101.2a', '101', '', '');
+insert into WSlot values ('WS.101.2b', '101', '', '');
+insert into WSlot values ('WS.101.3a', '101', '', '');
+insert into WSlot values ('WS.101.3b', '101', '', '');
+
+insert into WSlot values ('WS.102.1a', '102', '', '');
+insert into WSlot values ('WS.102.1b', '102', '', '');
+insert into WSlot values ('WS.102.2a', '102', '', '');
+insert into WSlot values ('WS.102.2b', '102', '', '');
+insert into WSlot values ('WS.102.3a', '102', '', '');
+insert into WSlot values ('WS.102.3b', '102', '', '');
+
+insert into WSlot values ('WS.105.1a', '105', '', '');
+insert into WSlot values ('WS.105.1b', '105', '', '');
+insert into WSlot values ('WS.105.2a', '105', '', '');
+insert into WSlot values ('WS.105.2b', '105', '', '');
+insert into WSlot values ('WS.105.3a', '105', '', '');
+insert into WSlot values ('WS.105.3b', '105', '', '');
+
+insert into WSlot values ('WS.106.1a', '106', '', '');
+insert into WSlot values ('WS.106.1b', '106', '', '');
+insert into WSlot values ('WS.106.2a', '106', '', '');
+insert into WSlot values ('WS.106.2b', '106', '', '');
+insert into WSlot values ('WS.106.3a', '106', '', '');
+insert into WSlot values ('WS.106.3b', '106', '', '');
+
+--
+-- Now create the patch fields and their slots
+--
+insert into PField values ('PF0_1', 'Wallslots basement');
+
+--
+-- The cables for these will be made later, so they are unconnected for now
+--
+insert into PSlot values ('PS.base.a1', 'PF0_1', '', '');
+insert into PSlot values ('PS.base.a2', 'PF0_1', '', '');
+insert into PSlot values ('PS.base.a3', 'PF0_1', '', '');
+insert into PSlot values ('PS.base.a4', 'PF0_1', '', '');
+insert into PSlot values ('PS.base.a5', 'PF0_1', '', '');
+insert into PSlot values ('PS.base.a6', 'PF0_1', '', '');
+
+--
+-- These are already wired to the wall connectors
+--
+insert into PSlot values ('PS.base.b1', 'PF0_1', '', 'WS.002.1a');
+insert into PSlot values ('PS.base.b2', 'PF0_1', '', 'WS.002.1b');
+insert into PSlot values ('PS.base.b3', 'PF0_1', '', 'WS.002.2a');
+insert into PSlot values ('PS.base.b4', 'PF0_1', '', 'WS.002.2b');
+insert into PSlot values ('PS.base.b5', 'PF0_1', '', 'WS.002.3a');
+insert into PSlot values ('PS.base.b6', 'PF0_1', '', 'WS.002.3b');
+
+insert into PSlot values ('PS.base.c1', 'PF0_1', '', 'WS.003.1a');
+insert into PSlot values ('PS.base.c2', 'PF0_1', '', 'WS.003.1b');
+insert into PSlot values ('PS.base.c3', 'PF0_1', '', 'WS.003.2a');
+insert into PSlot values ('PS.base.c4', 'PF0_1', '', 'WS.003.2b');
+insert into PSlot values ('PS.base.c5', 'PF0_1', '', 'WS.003.3a');
+insert into PSlot values ('PS.base.c6', 'PF0_1', '', 'WS.003.3b');
+
+--
+-- This patchfield will be renamed later into PF0_2 - so its
+-- slots references in pfname should follow
+--
+insert into PField values ('PF0_X', 'Phonelines basement');
+
+insert into PSlot values ('PS.base.ta1', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.ta2', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.ta3', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.ta4', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.ta5', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.ta6', 'PF0_X', '', '');
+
+insert into PSlot values ('PS.base.tb1', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.tb2', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.tb3', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.tb4', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.tb5', 'PF0_X', '', '');
+insert into PSlot values ('PS.base.tb6', 'PF0_X', '', '');
+
+insert into PField values ('PF1_1', 'Wallslots 1st floor');
+
+insert into PSlot values ('PS.1st.a1', 'PF1_1', '', 'WS.101.1a');
+insert into PSlot values ('PS.1st.a2', 'PF1_1', '', 'WS.101.1b');
+insert into PSlot values ('PS.1st.a3', 'PF1_1', '', 'WS.101.2a');
+insert into PSlot values ('PS.1st.a4', 'PF1_1', '', 'WS.101.2b');
+insert into PSlot values ('PS.1st.a5', 'PF1_1', '', 'WS.101.3a');
+insert into PSlot values ('PS.1st.a6', 'PF1_1', '', 'WS.101.3b');
+
+insert into PSlot values ('PS.1st.b1', 'PF1_1', '', 'WS.102.1a');
+insert into PSlot values ('PS.1st.b2', 'PF1_1', '', 'WS.102.1b');
+insert into PSlot values ('PS.1st.b3', 'PF1_1', '', 'WS.102.2a');
+insert into PSlot values ('PS.1st.b4', 'PF1_1', '', 'WS.102.2b');
+insert into PSlot values ('PS.1st.b5', 'PF1_1', '', 'WS.102.3a');
+insert into PSlot values ('PS.1st.b6', 'PF1_1', '', 'WS.102.3b');
+
+insert into PSlot values ('PS.1st.c1', 'PF1_1', '', 'WS.105.1a');
+insert into PSlot values ('PS.1st.c2', 'PF1_1', '', 'WS.105.1b');
+insert into PSlot values ('PS.1st.c3', 'PF1_1', '', 'WS.105.2a');
+insert into PSlot values ('PS.1st.c4', 'PF1_1', '', 'WS.105.2b');
+insert into PSlot values ('PS.1st.c5', 'PF1_1', '', 'WS.105.3a');
+insert into PSlot values ('PS.1st.c6', 'PF1_1', '', 'WS.105.3b');
+
+insert into PSlot values ('PS.1st.d1', 'PF1_1', '', 'WS.106.1a');
+insert into PSlot values ('PS.1st.d2', 'PF1_1', '', 'WS.106.1b');
+insert into PSlot values ('PS.1st.d3', 'PF1_1', '', 'WS.106.2a');
+insert into PSlot values ('PS.1st.d4', 'PF1_1', '', 'WS.106.2b');
+insert into PSlot values ('PS.1st.d5', 'PF1_1', '', 'WS.106.3a');
+insert into PSlot values ('PS.1st.d6', 'PF1_1', '', 'WS.106.3b');
+
+--
+-- Now we wire the wall connectors 1a-2a in room 001 to the
+-- patchfield. In the second update we make an error, and
+-- correct it after
+--
+update PSlot set backlink = 'WS.001.1a' where slotname = 'PS.base.a1';
+update PSlot set backlink = 'WS.001.1b' where slotname = 'PS.base.a3';
+select * from WSlot where roomno = '001' order by slotname;
+select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+update PSlot set backlink = 'WS.001.2a' where slotname = 'PS.base.a3';
+select * from WSlot where roomno = '001' order by slotname;
+select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+update PSlot set backlink = 'WS.001.1b' where slotname = 'PS.base.a2';
+select * from WSlot where roomno = '001' order by slotname;
+select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+
+--
+-- Same procedure for 2b-3b but this time updating the WSlot instead
+-- of the PSlot. Due to the triggers the result is the same:
+-- WSlot and corresponding PSlot point to each other.
+--
+update WSlot set backlink = 'PS.base.a4' where slotname = 'WS.001.2b';
+update WSlot set backlink = 'PS.base.a6' where slotname = 'WS.001.3a';
+select * from WSlot where roomno = '001' order by slotname;
+select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+update WSlot set backlink = 'PS.base.a6' where slotname = 'WS.001.3b';
+select * from WSlot where roomno = '001' order by slotname;
+select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+update WSlot set backlink = 'PS.base.a5' where slotname = 'WS.001.3a';
+select * from WSlot where roomno = '001' order by slotname;
+select * from PSlot where slotname ~ 'PS.base.a' order by slotname;
+
+insert into PField values ('PF1_2', 'Phonelines 1st floor');
+
+insert into PSlot values ('PS.1st.ta1', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.ta2', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.ta3', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.ta4', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.ta5', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.ta6', 'PF1_2', '', '');
+
+insert into PSlot values ('PS.1st.tb1', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.tb2', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.tb3', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.tb4', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.tb5', 'PF1_2', '', '');
+insert into PSlot values ('PS.1st.tb6', 'PF1_2', '', '');
+
+--
+-- Fix the wrong name for patchfield PF0_2
+--
+update PField set name = 'PF0_2' where name = 'PF0_X';
+
+select * from PSlot order by slotname;
+select * from WSlot order by slotname;
+
+--
+-- Install the central phone system and create the phone numbers.
+-- They are weired on insert to the patchfields. Again the
+-- triggers automatically tell the PSlots to update their
+-- backlink field.
+--
+insert into PLine values ('PL.001', '-0', 'Central call', 'PS.base.ta1');
+insert into PLine values ('PL.002', '-101', '', 'PS.base.ta2');
+insert into PLine values ('PL.003', '-102', '', 'PS.base.ta3');
+insert into PLine values ('PL.004', '-103', '', 'PS.base.ta5');
+insert into PLine values ('PL.005', '-104', '', 'PS.base.ta6');
+insert into PLine values ('PL.006', '-106', '', 'PS.base.tb2');
+insert into PLine values ('PL.007', '-108', '', 'PS.base.tb3');
+insert into PLine values ('PL.008', '-109', '', 'PS.base.tb4');
+insert into PLine values ('PL.009', '-121', '', 'PS.base.tb5');
+insert into PLine values ('PL.010', '-122', '', 'PS.base.tb6');
+insert into PLine values ('PL.015', '-134', '', 'PS.1st.ta1');
+insert into PLine values ('PL.016', '-137', '', 'PS.1st.ta3');
+insert into PLine values ('PL.017', '-139', '', 'PS.1st.ta4');
+insert into PLine values ('PL.018', '-362', '', 'PS.1st.tb1');
+insert into PLine values ('PL.019', '-363', '', 'PS.1st.tb2');
+insert into PLine values ('PL.020', '-364', '', 'PS.1st.tb3');
+insert into PLine values ('PL.021', '-365', '', 'PS.1st.tb5');
+insert into PLine values ('PL.022', '-367', '', 'PS.1st.tb6');
+insert into PLine values ('PL.028', '-501', 'Fax entrance', 'PS.base.ta2');
+insert into PLine values ('PL.029', '-502', 'Fax 1st floor', 'PS.1st.ta1');
+
+--
+-- Buy some phones, plug them into the wall and patch the
+-- phone lines to the corresponding patchfield slots.
+--
+insert into PHone values ('PH.hc001', 'Hicom standard', 'WS.001.1a');
+update PSlot set slotlink = 'PS.base.ta1' where slotname = 'PS.base.a1';
+insert into PHone values ('PH.hc002', 'Hicom standard', 'WS.002.1a');
+update PSlot set slotlink = 'PS.base.ta5' where slotname = 'PS.base.b1';
+insert into PHone values ('PH.hc003', 'Hicom standard', 'WS.002.2a');
+update PSlot set slotlink = 'PS.base.tb2' where slotname = 'PS.base.b3';
+insert into PHone values ('PH.fax001', 'Canon fax', 'WS.001.2a');
+update PSlot set slotlink = 'PS.base.ta2' where slotname = 'PS.base.a3';
+
+--
+-- Install a hub at one of the patchfields, plug a computers
+-- ethernet interface into the wall and patch it to the hub.
+--
+insert into Hub values ('base.hub1', 'Patchfield PF0_1 hub', 16);
+insert into System values ('orion', 'PC');
+insert into IFace values ('IF', 'orion', 'eth0', 'WS.002.1b');
+update PSlot set slotlink = 'HS.base.hub1.1' where slotname = 'PS.base.b2';
+
+--
+-- Now we take a look at the patchfield
+--
+select * from PField_v1 where pfname = 'PF0_1' order by slotname;
+select * from PField_v1 where pfname = 'PF0_2' order by slotname;
+
+--
+-- Finally we want errors
+--
+insert into PField values ('PF1_1', 'should fail due to unique index');
+update PSlot set backlink = 'WS.not.there' where slotname = 'PS.base.a1';
+update PSlot set backlink = 'XX.illegal' where slotname = 'PS.base.a1';
+update PSlot set slotlink = 'PS.not.there' where slotname = 'PS.base.a1';
+update PSlot set slotlink = 'XX.illegal' where slotname = 'PS.base.a1';
+insert into HSlot values ('HS', 'base.hub1', 1, '');
+insert into HSlot values ('HS', 'base.hub1', 20, '');
+delete from HSlot;
+insert into IFace values ('IF', 'notthere', 'eth0', '');
+insert into IFace values ('IF', 'orion', 'ethernet_interface_name_too_long', '');
--- /dev/null
+-- ************************************************************
+-- *
+-- * Trigger procedures and functions for the patchfield
+-- * test of PL/pgSQL
+-- *
+-- * $Header: /cvsroot/pgsql/contrib/plpgsql/test/Attic/triggers.sql,v 1.1 1998/08/22 12:38:37 momjian Exp $
+-- *
+-- ************************************************************
+
+
+-- ************************************************************
+-- * AFTER UPDATE on Room
+-- * - If room no changes let wall slots follow
+-- ************************************************************
+create function tg_room_au() returns opaque as '
+begin
+ if new.roomno != old.roomno then
+ update WSlot set roomno = new.roomno where roomno = old.roomno;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_room_au after update
+ on Room for each row execute procedure tg_room_au();
+
+
+-- ************************************************************
+-- * AFTER DELETE on Room
+-- * - delete wall slots in this room
+-- ************************************************************
+create function tg_room_ad() returns opaque as '
+begin
+ delete from WSlot where roomno = old.roomno;
+ return old;
+end;
+' language 'plpgsql';
+
+create trigger tg_room_ad after delete
+ on Room for each row execute procedure tg_room_ad();
+
+
+-- ************************************************************
+-- * BEFORE INSERT or UPDATE on WSlot
+-- * - Check that room exists
+-- ************************************************************
+create function tg_wslot_biu() returns opaque as '
+begin
+ if count(*) = 0 from Room where roomno = new.roomno then
+ raise exception ''Room % does not exist'', new.roomno;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_wslot_biu before insert or update
+ on WSlot for each row execute procedure tg_wslot_biu();
+
+
+-- ************************************************************
+-- * AFTER UPDATE on PField
+-- * - Let PSlots of this field follow
+-- ************************************************************
+create function tg_pfield_au() returns opaque as '
+begin
+ if new.name != old.name then
+ update PSlot set pfname = new.name where pfname = old.name;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_pfield_au after update
+ on PField for each row execute procedure tg_pfield_au();
+
+
+-- ************************************************************
+-- * AFTER DELETE on PField
+-- * - Remove all slots of this patchfield
+-- ************************************************************
+create function tg_pfield_ad() returns opaque as '
+begin
+ delete from PSlot where pfname = old.name;
+ return old;
+end;
+' language 'plpgsql';
+
+create trigger tg_pfield_ad after delete
+ on PField for each row execute procedure tg_pfield_ad();
+
+
+-- ************************************************************
+-- * BEFORE INSERT or UPDATE on PSlot
+-- * - Ensure that our patchfield does exist
+-- ************************************************************
+create function tg_pslot_biu() returns opaque as '
+declare
+ pfrec record;
+ rename new to ps;
+begin
+ select into pfrec * from PField where name = ps.pfname;
+ if not found then
+ raise exception ''Patchfield "%" does not exist'', ps.pfname;
+ end if;
+ return ps;
+end;
+' language 'plpgsql';
+
+create trigger tg_pslot_biu before insert or update
+ on PSlot for each row execute procedure tg_pslot_biu();
+
+
+-- ************************************************************
+-- * AFTER UPDATE on System
+-- * - If system name changes let interfaces follow
+-- ************************************************************
+create function tg_system_au() returns opaque as '
+begin
+ if new.name != old.name then
+ update IFace set sysname = new.name where sysname = old.name;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_system_au after update
+ on System for each row execute procedure tg_system_au();
+
+
+-- ************************************************************
+-- * BEFORE INSERT or UPDATE on IFace
+-- * - set the slotname to IF.sysname.ifname
+-- ************************************************************
+create function tg_iface_biu() returns opaque as '
+declare
+ sname text;
+ sysrec record;
+begin
+ select into sysrec * from system where name = new.sysname;
+ if not found then
+ raise exception ''system "%" does not exist'', new.sysname;
+ end if;
+ sname := ''IF.'' || new.sysname;
+ sname := sname || ''.'';
+ sname := sname || new.ifname;
+ if length(sname) > 20 then
+ raise exception ''IFace slotname "%" too long (20 char max)'', sname;
+ end if;
+ new.slotname := sname;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_iface_biu before insert or update
+ on IFace for each row execute procedure tg_iface_biu();
+
+
+-- ************************************************************
+-- * AFTER INSERT or UPDATE or DELETE on Hub
+-- * - insert/delete/rename slots as required
+-- ************************************************************
+create function tg_hub_a() returns opaque as '
+declare
+ hname text;
+ dummy integer;
+begin
+ if tg_op = ''INSERT'' then
+ dummy := tg_hub_adjustslots(new.name, 0, new.nslots);
+ return new;
+ end if;
+ if tg_op = ''UPDATE'' then
+ if new.name != old.name then
+ update HSlot set hubname = new.name where hubname = old.name;
+ end if;
+ dummy := tg_hub_adjustslots(new.name, old.nslots, new.nslots);
+ return new;
+ end if;
+ if tg_op = ''DELETE'' then
+ dummy := tg_hub_adjustslots(old.name, old.nslots, 0);
+ return old;
+ end if;
+end;
+' language 'plpgsql';
+
+create trigger tg_hub_a after insert or update or delete
+ on Hub for each row execute procedure tg_hub_a();
+
+
+-- ************************************************************
+-- * Support function to add/remove slots of Hub
+-- ************************************************************
+create function tg_hub_adjustslots(bpchar, integer, integer)
+returns integer as '
+declare
+ hname alias for $1;
+ oldnslots alias for $2;
+ newnslots alias for $3;
+begin
+ if newnslots = oldnslots then
+ return 0;
+ end if;
+ if newnslots < oldnslots then
+ delete from HSlot where hubname = hname and slotno > newnslots;
+ return 0;
+ end if;
+ for i in oldnslots + 1 .. newnslots loop
+ insert into HSlot (slotname, hubname, slotno, slotlink)
+ values (''HS.dummy'', hname, i, '''');
+ end loop;
+ return 0;
+end;
+' language 'plpgsql';
+
+
+-- ************************************************************
+-- * BEFORE INSERT or UPDATE on HSlot
+-- * - prevent from manual manipulation
+-- * - set the slotname to HS.hubname.slotno
+-- ************************************************************
+create function tg_hslot_biu() returns opaque as '
+declare
+ sname text;
+ xname HSlot.slotname%TYPE;
+ hubrec record;
+begin
+ select into hubrec * from Hub where name = new.hubname;
+ if not found then
+ raise exception ''no manual manipulation of HSlot'';
+ end if;
+ if new.slotno < 1 or new.slotno > hubrec.nslots then
+ raise exception ''no manual manipulation of HSlot'';
+ end if;
+ if tg_op = ''UPDATE'' then
+ if new.hubname != old.hubname then
+ if count(*) > 0 from Hub where name = old.hubname then
+ raise exception ''no manual manipulation of HSlot'';
+ end if;
+ end if;
+ end if;
+ sname := ''HS.'' || trim(new.hubname);
+ sname := sname || ''.'';
+ sname := sname || new.slotno::text;
+ if length(sname) > 20 then
+ raise exception ''HSlot slotname "%" too long (20 char max)'', sname;
+ end if;
+ new.slotname := sname;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_hslot_biu before insert or update
+ on HSlot for each row execute procedure tg_hslot_biu();
+
+
+-- ************************************************************
+-- * BEFORE DELETE on HSlot
+-- * - prevent from manual manipulation
+-- ************************************************************
+create function tg_hslot_bd() returns opaque as '
+declare
+ hubrec record;
+begin
+ select into hubrec * from Hub where name = old.hubname;
+ if not found then
+ return old;
+ end if;
+ if old.slotno > hubrec.nslots then
+ return old;
+ end if;
+ raise exception ''no manual manipulation of HSlot'';
+end;
+' language 'plpgsql';
+
+create trigger tg_hslot_bd before delete
+ on HSlot for each row execute procedure tg_hslot_bd();
+
+
+-- ************************************************************
+-- * BEFORE INSERT on all slots
+-- * - Check name prefix
+-- ************************************************************
+create function tg_chkslotname() returns opaque as '
+begin
+ if substr(new.slotname, 1, 2) != tg_argv[0] then
+ raise exception ''slotname must begin with %'', tg_argv[0];
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_chkslotname before insert
+ on PSlot for each row execute procedure tg_chkslotname('PS');
+
+create trigger tg_chkslotname before insert
+ on WSlot for each row execute procedure tg_chkslotname('WS');
+
+create trigger tg_chkslotname before insert
+ on PLine for each row execute procedure tg_chkslotname('PL');
+
+create trigger tg_chkslotname before insert
+ on IFace for each row execute procedure tg_chkslotname('IF');
+
+create trigger tg_chkslotname before insert
+ on PHone for each row execute procedure tg_chkslotname('PH');
+
+
+-- ************************************************************
+-- * BEFORE INSERT or UPDATE on all slots with slotlink
+-- * - Set slotlink to empty string if NULL value given
+-- ************************************************************
+create function tg_chkslotlink() returns opaque as '
+begin
+ if new.slotlink isnull then
+ new.slotlink := '''';
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_chkslotlink before insert or update
+ on PSlot for each row execute procedure tg_chkslotlink();
+
+create trigger tg_chkslotlink before insert or update
+ on WSlot for each row execute procedure tg_chkslotlink();
+
+create trigger tg_chkslotlink before insert or update
+ on IFace for each row execute procedure tg_chkslotlink();
+
+create trigger tg_chkslotlink before insert or update
+ on HSlot for each row execute procedure tg_chkslotlink();
+
+create trigger tg_chkslotlink before insert or update
+ on PHone for each row execute procedure tg_chkslotlink();
+
+
+-- ************************************************************
+-- * BEFORE INSERT or UPDATE on all slots with backlink
+-- * - Set backlink to empty string if NULL value given
+-- ************************************************************
+create function tg_chkbacklink() returns opaque as '
+begin
+ if new.backlink isnull then
+ new.backlink := '''';
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_chkbacklink before insert or update
+ on PSlot for each row execute procedure tg_chkbacklink();
+
+create trigger tg_chkbacklink before insert or update
+ on WSlot for each row execute procedure tg_chkbacklink();
+
+create trigger tg_chkbacklink before insert or update
+ on PLine for each row execute procedure tg_chkbacklink();
+
+
+-- ************************************************************
+-- * BEFORE UPDATE on PSlot
+-- * - do delete/insert instead of update if name changes
+-- ************************************************************
+create function tg_pslot_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from PSlot where slotname = old.slotname;
+ insert into PSlot (
+ slotname,
+ pfname,
+ slotlink,
+ backlink
+ ) values (
+ new.slotname,
+ new.pfname,
+ new.slotlink,
+ new.backlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_pslot_bu before update
+ on PSlot for each row execute procedure tg_pslot_bu();
+
+
+-- ************************************************************
+-- * BEFORE UPDATE on WSlot
+-- * - do delete/insert instead of update if name changes
+-- ************************************************************
+create function tg_wslot_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from WSlot where slotname = old.slotname;
+ insert into WSlot (
+ slotname,
+ roomno,
+ slotlink,
+ backlink
+ ) values (
+ new.slotname,
+ new.roomno,
+ new.slotlink,
+ new.backlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_wslot_bu before update
+ on WSlot for each row execute procedure tg_Wslot_bu();
+
+
+-- ************************************************************
+-- * BEFORE UPDATE on PLine
+-- * - do delete/insert instead of update if name changes
+-- ************************************************************
+create function tg_pline_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from PLine where slotname = old.slotname;
+ insert into PLine (
+ slotname,
+ phonenumber,
+ comment,
+ backlink
+ ) values (
+ new.slotname,
+ new.phonenumber,
+ new.comment,
+ new.backlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_pline_bu before update
+ on PLine for each row execute procedure tg_pline_bu();
+
+
+-- ************************************************************
+-- * BEFORE UPDATE on IFace
+-- * - do delete/insert instead of update if name changes
+-- ************************************************************
+create function tg_iface_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from IFace where slotname = old.slotname;
+ insert into IFace (
+ slotname,
+ sysname,
+ ifname,
+ slotlink
+ ) values (
+ new.slotname,
+ new.sysname,
+ new.ifname,
+ new.slotlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_iface_bu before update
+ on IFace for each row execute procedure tg_iface_bu();
+
+
+-- ************************************************************
+-- * BEFORE UPDATE on HSlot
+-- * - do delete/insert instead of update if name changes
+-- ************************************************************
+create function tg_hslot_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname or new.hubname != old.hubname then
+ delete from HSlot where slotname = old.slotname;
+ insert into HSlot (
+ slotname,
+ hubname,
+ slotno,
+ slotlink
+ ) values (
+ new.slotname,
+ new.hubname,
+ new.slotno,
+ new.slotlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_hslot_bu before update
+ on HSlot for each row execute procedure tg_hslot_bu();
+
+
+-- ************************************************************
+-- * BEFORE UPDATE on PHone
+-- * - do delete/insert instead of update if name changes
+-- ************************************************************
+create function tg_phone_bu() returns opaque as '
+begin
+ if new.slotname != old.slotname then
+ delete from PHone where slotname = old.slotname;
+ insert into PHone (
+ slotname,
+ comment,
+ slotlink
+ ) values (
+ new.slotname,
+ new.comment,
+ new.slotlink
+ );
+ return null;
+ end if;
+ return new;
+end;
+' language 'plpgsql';
+
+create trigger tg_phone_bu before update
+ on PHone for each row execute procedure tg_phone_bu();
+
+
+-- ************************************************************
+-- * AFTER INSERT or UPDATE or DELETE on slot with backlink
+-- * - Ensure that the opponent correctly points back to us
+-- ************************************************************
+create function tg_backlink_a() returns opaque as '
+declare
+ dummy integer;
+begin
+ if tg_op = ''INSERT'' then
+ if new.backlink != '''' then
+ dummy := tg_backlink_set(new.backlink, new.slotname);
+ end if;
+ return new;
+ end if;
+ if tg_op = ''UPDATE'' then
+ if new.backlink != old.backlink then
+ if old.backlink != '''' then
+ dummy := tg_backlink_unset(old.backlink, old.slotname);
+ end if;
+ if new.backlink != '''' then
+ dummy := tg_backlink_set(new.backlink, new.slotname);
+ end if;
+ else
+ if new.slotname != old.slotname and new.backlink != '''' then
+ dummy := tg_slotlink_set(new.backlink, new.slotname);
+ end if;
+ end if;
+ return new;
+ end if;
+ if tg_op = ''DELETE'' then
+ if old.backlink != '''' then
+ dummy := tg_backlink_unset(old.backlink, old.slotname);
+ end if;
+ return old;
+ end if;
+end;
+' language 'plpgsql';
+
+
+create trigger tg_backlink_a after insert or update or delete
+ on PSlot for each row execute procedure tg_backlink_a('PS');
+
+create trigger tg_backlink_a after insert or update or delete
+ on WSlot for each row execute procedure tg_backlink_a('WS');
+
+create trigger tg_backlink_a after insert or update or delete
+ on PLine for each row execute procedure tg_backlink_a('PL');
+
+
+-- ************************************************************
+-- * Support function to set the opponents backlink field
+-- * if it does not already point to the requested slot
+-- ************************************************************
+create function tg_backlink_set(bpchar, bpchar)
+returns integer as '
+declare
+ myname alias for $1;
+ blname alias for $2;
+ mytype char(2);
+ link char(4);
+ rec record;
+begin
+ mytype := substr(myname, 1, 2);
+ link := mytype || substr(blname, 1, 2);
+ if link = ''PLPL'' then
+ raise exception
+ ''backlink between two phone lines does not make sense'';
+ end if;
+ if link in (''PLWS'', ''WSPL'') then
+ raise exception
+ ''direct link of phone line to wall slot not permitted'';
+ end if;
+ if mytype = ''PS'' then
+ select into rec * from PSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.backlink != blname then
+ update PSlot set backlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''WS'' then
+ select into rec * from WSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.backlink != blname then
+ update WSlot set backlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''PL'' then
+ select into rec * from PLine where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.backlink != blname then
+ update PLine set backlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ raise exception ''illegal backlink beginning with %'', mytype;
+end;
+' language 'plpgsql';
+
+
+-- ************************************************************
+-- * Support function to clear out the backlink field if
+-- * it still points to specific slot
+-- ************************************************************
+create function tg_backlink_unset(bpchar, bpchar)
+returns integer as '
+declare
+ myname alias for $1;
+ blname alias for $2;
+ mytype char(2);
+ rec record;
+begin
+ mytype := substr(myname, 1, 2);
+ if mytype = ''PS'' then
+ select into rec * from PSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.backlink = blname then
+ update PSlot set backlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''WS'' then
+ select into rec * from WSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.backlink = blname then
+ update WSlot set backlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''PL'' then
+ select into rec * from PLine where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.backlink = blname then
+ update PLine set backlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+end;
+' language 'plpgsql';
+
+
+-- ************************************************************
+-- * AFTER INSERT or UPDATE or DELETE on slot with slotlink
+-- * - Ensure that the opponent correctly points back to us
+-- ************************************************************
+create function tg_slotlink_a() returns opaque as '
+declare
+ dummy integer;
+begin
+ if tg_op = ''INSERT'' then
+ if new.slotlink != '''' then
+ dummy := tg_slotlink_set(new.slotlink, new.slotname);
+ end if;
+ return new;
+ end if;
+ if tg_op = ''UPDATE'' then
+ if new.slotlink != old.slotlink then
+ if old.slotlink != '''' then
+ dummy := tg_slotlink_unset(old.slotlink, old.slotname);
+ end if;
+ if new.slotlink != '''' then
+ dummy := tg_slotlink_set(new.slotlink, new.slotname);
+ end if;
+ else
+ if new.slotname != old.slotname and new.slotlink != '''' then
+ dummy := tg_slotlink_set(new.slotlink, new.slotname);
+ end if;
+ end if;
+ return new;
+ end if;
+ if tg_op = ''DELETE'' then
+ if old.slotlink != '''' then
+ dummy := tg_slotlink_unset(old.slotlink, old.slotname);
+ end if;
+ return old;
+ end if;
+end;
+' language 'plpgsql';
+
+
+create trigger tg_slotlink_a after insert or update or delete
+ on PSlot for each row execute procedure tg_slotlink_a('PS');
+
+create trigger tg_slotlink_a after insert or update or delete
+ on WSlot for each row execute procedure tg_slotlink_a('WS');
+
+create trigger tg_slotlink_a after insert or update or delete
+ on IFace for each row execute procedure tg_slotlink_a('IF');
+
+create trigger tg_slotlink_a after insert or update or delete
+ on HSlot for each row execute procedure tg_slotlink_a('HS');
+
+create trigger tg_slotlink_a after insert or update or delete
+ on PHone for each row execute procedure tg_slotlink_a('PH');
+
+
+-- ************************************************************
+-- * Support function to set the opponents slotlink field
+-- * if it does not already point to the requested slot
+-- ************************************************************
+create function tg_slotlink_set(bpchar, bpchar)
+returns integer as '
+declare
+ myname alias for $1;
+ blname alias for $2;
+ mytype char(2);
+ link char(4);
+ rec record;
+begin
+ mytype := substr(myname, 1, 2);
+ link := mytype || substr(blname, 1, 2);
+ if link = ''PHPH'' then
+ raise exception
+ ''slotlink between two phones does not make sense'';
+ end if;
+ if link in (''PHHS'', ''HSPH'') then
+ raise exception
+ ''link of phone to hub does not make sense'';
+ end if;
+ if link in (''PHIF'', ''IFPH'') then
+ raise exception
+ ''link of phone to hub does not make sense'';
+ end if;
+ if link in (''PSWS'', ''WSPS'') then
+ raise exception
+ ''slotlink from patchslot to wallslot not permitted'';
+ end if;
+ if mytype = ''PS'' then
+ select into rec * from PSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update PSlot set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''WS'' then
+ select into rec * from WSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update WSlot set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''IF'' then
+ select into rec * from IFace where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update IFace set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''HS'' then
+ select into rec * from HSlot where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update HSlot set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''PH'' then
+ select into rec * from PHone where slotname = myname;
+ if not found then
+ raise exception ''% does not exists'', myname;
+ end if;
+ if rec.slotlink != blname then
+ update PHone set slotlink = blname where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ raise exception ''illegal slotlink beginning with %'', mytype;
+end;
+' language 'plpgsql';
+
+
+-- ************************************************************
+-- * Support function to clear out the slotlink field if
+-- * it still points to specific slot
+-- ************************************************************
+create function tg_slotlink_unset(bpchar, bpchar)
+returns integer as '
+declare
+ myname alias for $1;
+ blname alias for $2;
+ mytype char(2);
+ rec record;
+begin
+ mytype := substr(myname, 1, 2);
+ if mytype = ''PS'' then
+ select into rec * from PSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update PSlot set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''WS'' then
+ select into rec * from WSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update WSlot set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''IF'' then
+ select into rec * from IFace where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update IFace set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''HS'' then
+ select into rec * from HSlot where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update HSlot set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+ if mytype = ''PH'' then
+ select into rec * from PHone where slotname = myname;
+ if not found then
+ return 0;
+ end if;
+ if rec.slotlink = blname then
+ update PHone set slotlink = '''' where slotname = myname;
+ end if;
+ return 0;
+ end if;
+end;
+' language 'plpgsql';
+
+
--- /dev/null
+-- ************************************************************
+-- * Describe the backside of a patchfield slot
+-- ************************************************************
+create function pslot_backlink_view(bpchar)
+returns text as '
+<<outer>>
+declare
+ rec record;
+ bltype char(2);
+ retval text;
+begin
+ select into rec * from PSlot where slotname = $1;
+ if not found then
+ return '''';
+ end if;
+ if rec.backlink = '''' then
+ return ''-'';
+ end if;
+ bltype := substr(rec.backlink, 1, 2);
+ if bltype = ''PL'' then
+ declare
+ rec record;
+ begin
+ select into rec * from PLine where slotname = outer.rec.backlink;
+ retval := ''Phone line '' || trim(rec.phonenumber);
+ if rec.comment != '''' then
+ retval := retval || '' ('';
+ retval := retval || rec.comment;
+ retval := retval || '')'';
+ end if;
+ return retval;
+ end;
+ end if;
+ if bltype = ''WS'' then
+ select into rec * from WSlot where slotname = rec.backlink;
+ retval := trim(rec.slotname) || '' in room '';
+ retval := retval || trim(rec.roomno);
+ retval := retval || '' -> '';
+ return retval || wslot_slotlink_view(rec.slotname);
+ end if;
+ return rec.backlink;
+end;
+' language 'plpgsql';
+
+
+-- ************************************************************
+-- * Describe the front of a patchfield slot
+-- ************************************************************
+create function pslot_slotlink_view(bpchar)
+returns text as '
+declare
+ psrec record;
+ sltype char(2);
+ retval text;
+begin
+ select into psrec * from PSlot where slotname = $1;
+ if not found then
+ return '''';
+ end if;
+ if psrec.slotlink = '''' then
+ return ''-'';
+ end if;
+ sltype := substr(psrec.slotlink, 1, 2);
+ if sltype = ''PS'' then
+ retval := trim(psrec.slotlink) || '' -> '';
+ return retval || pslot_backlink_view(psrec.slotlink);
+ end if;
+ if sltype = ''HS'' then
+ retval := comment from Hub H, HSlot HS
+ where HS.slotname = psrec.slotlink
+ and H.name = HS.hubname;
+ retval := retval || '' slot '';
+ retval := retval || slotno::text from HSlot
+ where slotname = psrec.slotlink;
+ return retval;
+ end if;
+ return psrec.slotlink;
+end;
+' language 'plpgsql';
+
+
+-- ************************************************************
+-- * Describe the front of a wall connector slot
+-- ************************************************************
+create function wslot_slotlink_view(bpchar)
+returns text as '
+declare
+ rec record;
+ sltype char(2);
+ retval text;
+begin
+ select into rec * from WSlot where slotname = $1;
+ if not found then
+ return '''';
+ end if;
+ if rec.slotlink = '''' then
+ return ''-'';
+ end if;
+ sltype := substr(rec.slotlink, 1, 2);
+ if sltype = ''PH'' then
+ select into rec * from PHone where slotname = rec.slotlink;
+ retval := ''Phone '' || trim(rec.slotname);
+ if rec.comment != '''' then
+ retval := retval || '' ('';
+ retval := retval || rec.comment;
+ retval := retval || '')'';
+ end if;
+ return retval;
+ end if;
+ if sltype = ''IF'' then
+ declare
+ syrow System%RowType;
+ ifrow IFace%ROWTYPE;
+ begin
+ select into ifrow * from IFace where slotname = rec.slotlink;
+ select into syrow * from System where name = ifrow.sysname;
+ retval := syrow.name || '' IF '';
+ retval := retval || ifrow.ifname;
+ if syrow.comment != '''' then
+ retval := retval || '' ('';
+ retval := retval || syrow.comment;
+ retval := retval || '')'';
+ end if;
+ return retval;
+ end;
+ end if;
+ return rec.slotlink;
+end;
+' language 'plpgsql';
+
+
+
+-- ************************************************************
+-- * View of a patchfield describing backside and patches
+-- ************************************************************
+create view Pfield_v1 as select PF.pfname, PF.slotname,
+ pslot_backlink_view(PF.slotname) as backside,
+ pslot_slotlink_view(PF.slotname) as patch
+ from PSlot PF;
+
+