diff options
| author | Tom Lane <tgl@sss.pgh.pa.us> | 2002-09-18 21:35:25 +0000 |
|---|---|---|
| committer | Tom Lane <tgl@sss.pgh.pa.us> | 2002-09-18 21:35:25 +0000 |
| commit | b26dfb95222fddd25322bdddf3a5a58d3392d8b1 (patch) | |
| tree | 757cf0bafab985d38a5c84d3afebe5edd34c4f27 /src/backend/parser | |
| parent | cc70ba2e4daa78ba99619770e19beb06de3dfd1c (diff) | |
| download | postgresql-b26dfb95222fddd25322bdddf3a5a58d3392d8b1.tar.gz | |
Extend pg_cast castimplicit column to a three-way value; this allows us
to be flexible about assignment casts without introducing ambiguity in
operator/function resolution. Introduce a well-defined promotion hierarchy
for numeric datatypes (int2->int4->int8->numeric->float4->float8).
Change make_const to initially label numeric literals as int4, int8, or
numeric (never float8 anymore).
Explicitly mark Func and RelabelType nodes to indicate whether they came
from a function call, explicit cast, or implicit cast; use this to do
reverse-listing more accurately and without so many heuristics.
Explicit casts to char, varchar, bit, varbit will truncate or pad without
raising an error (the pre-7.2 behavior), while assigning to a column without
any explicit cast will still raise an error for wrong-length data like 7.3.
This more nearly follows the SQL spec than 7.2 behavior (we should be
reporting a 'completion condition' in the explicit-cast cases, but we have
no mechanism for that, so just do silent truncation).
Fix some problems with enforcement of typmod for array elements;
it didn't work at all in 'UPDATE ... SET array[n] = foo', for example.
Provide a generalized array_length_coerce() function to replace the
specialized per-array-type functions that used to be needed (and were
missing for NUMERIC as well as all the datetime types).
Add missing conversions int8<->float4, text<->numeric, oid<->int8.
initdb forced.
Diffstat (limited to 'src/backend/parser')
| -rw-r--r-- | src/backend/parser/analyze.c | 30 | ||||
| -rw-r--r-- | src/backend/parser/gram.y | 22 | ||||
| -rw-r--r-- | src/backend/parser/keywords.c | 3 | ||||
| -rw-r--r-- | src/backend/parser/parse_clause.c | 18 | ||||
| -rw-r--r-- | src/backend/parser/parse_coerce.c | 413 | ||||
| -rw-r--r-- | src/backend/parser/parse_expr.c | 191 | ||||
| -rw-r--r-- | src/backend/parser/parse_func.c | 39 | ||||
| -rw-r--r-- | src/backend/parser/parse_node.c | 126 | ||||
| -rw-r--r-- | src/backend/parser/parse_oper.c | 10 | ||||
| -rw-r--r-- | src/backend/parser/parse_target.c | 76 |
10 files changed, 453 insertions, 475 deletions
diff --git a/src/backend/parser/analyze.c b/src/backend/parser/analyze.c index 97b242b9b6..663ae22d94 100644 --- a/src/backend/parser/analyze.c +++ b/src/backend/parser/analyze.c @@ -6,7 +6,7 @@ * Portions Copyright (c) 1996-2002, PostgreSQL Global Development Group * Portions Copyright (c) 1994, Regents of the University of California * - * $Header: /cvsroot/pgsql/src/backend/parser/analyze.c,v 1.248 2002/09/04 20:31:22 momjian Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/analyze.c,v 1.249 2002/09/18 21:35:21 tgl Exp $ * *------------------------------------------------------------------------- */ @@ -2565,24 +2565,20 @@ transformExecuteStmt(ParseState *pstate, ExecuteStmt *stmt) given_type_id = exprType(expr); expected_type_id = (Oid) lfirsti(paramtypes); - if (given_type_id != expected_type_id) - { - expr = CoerceTargetExpr(pstate, - expr, - given_type_id, - expected_type_id, - -1, - false); - - if (!expr) - elog(ERROR, "Parameter $%d of type %s cannot be coerced into the expected type %s" - "\n\tYou will need to rewrite or cast the expression", - i, - format_type_be(given_type_id), - format_type_be(expected_type_id)); - } + expr = coerce_to_target_type(expr, given_type_id, + expected_type_id, -1, + COERCION_ASSIGNMENT, + COERCE_IMPLICIT_CAST); + + if (expr == NULL) + elog(ERROR, "Parameter $%d of type %s cannot be coerced into the expected type %s" + "\n\tYou will need to rewrite or cast the expression", + i, + format_type_be(given_type_id), + format_type_be(expected_type_id)); fix_opids(expr); + lfirst(l) = expr; paramtypes = lnext(paramtypes); diff --git a/src/backend/parser/gram.y b/src/backend/parser/gram.y index d038cdd46e..43597306d4 100644 --- a/src/backend/parser/gram.y +++ b/src/backend/parser/gram.y @@ -11,7 +11,7 @@ * * * IDENTIFICATION - * $Header: /cvsroot/pgsql/src/backend/parser/gram.y,v 2.366 2002/09/05 22:52:48 tgl Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/gram.y,v 2.367 2002/09/18 21:35:21 tgl Exp $ * * HISTORY * AUTHOR DATE MAJOR EVENT @@ -161,8 +161,8 @@ static void doNegateFloat(Value *v); %type <list> createdb_opt_list, copy_opt_list %type <defelt> createdb_opt_item, copy_opt_item -%type <ival> opt_lock, lock_type -%type <boolean> opt_force, opt_or_replace, opt_assignment +%type <ival> opt_lock, lock_type, cast_context +%type <boolean> opt_force, opt_or_replace %type <list> user_list @@ -349,7 +349,7 @@ static void doNegateFloat(Value *v); HANDLER, HAVING, HOUR_P, - ILIKE, IMMEDIATE, IMMUTABLE, IN_P, INCREMENT, + ILIKE, IMMEDIATE, IMMUTABLE, IMPLICIT_P, IN_P, INCREMENT, INDEX, INHERITS, INITIALLY, INNER_P, INOUT, INPUT, INSENSITIVE, INSERT, INSTEAD, INT, INTEGER, INTERSECT, INTERVAL, INTO, INVOKER, IS, ISNULL, ISOLATION, @@ -3230,29 +3230,30 @@ any_operator: *****************************************************************************/ CreateCastStmt: CREATE CAST '(' ConstTypename AS ConstTypename ')' - WITH FUNCTION function_with_argtypes opt_assignment + WITH FUNCTION function_with_argtypes cast_context { CreateCastStmt *n = makeNode(CreateCastStmt); n->sourcetype = $4; n->targettype = $6; n->func = (FuncWithArgs *) $10; - n->implicit = $11; + n->context = (CoercionContext) $11; $$ = (Node *)n; } | CREATE CAST '(' ConstTypename AS ConstTypename ')' - WITHOUT FUNCTION opt_assignment + WITHOUT FUNCTION cast_context { CreateCastStmt *n = makeNode(CreateCastStmt); n->sourcetype = $4; n->targettype = $6; n->func = NULL; - n->implicit = $10; + n->context = (CoercionContext) $10; $$ = (Node *)n; } ; -opt_assignment: AS ASSIGNMENT { $$ = TRUE; } - | /*EMPTY*/ { $$ = FALSE; } +cast_context: AS IMPLICIT_P { $$ = COERCION_IMPLICIT; } + | AS ASSIGNMENT { $$ = COERCION_ASSIGNMENT; } + | /*EMPTY*/ { $$ = COERCION_EXPLICIT; } ; @@ -7061,6 +7062,7 @@ unreserved_keyword: | HOUR_P | IMMEDIATE | IMMUTABLE + | IMPLICIT_P | INCREMENT | INDEX | INHERITS diff --git a/src/backend/parser/keywords.c b/src/backend/parser/keywords.c index 9a3064ad66..305ed86018 100644 --- a/src/backend/parser/keywords.c +++ b/src/backend/parser/keywords.c @@ -8,7 +8,7 @@ * * * IDENTIFICATION - * $Header: /cvsroot/pgsql/src/backend/parser/keywords.c,v 1.126 2002/08/27 04:55:09 tgl Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/keywords.c,v 1.127 2002/09/18 21:35:22 tgl Exp $ * *------------------------------------------------------------------------- */ @@ -147,6 +147,7 @@ static const ScanKeyword ScanKeywords[] = { {"ilike", ILIKE}, {"immediate", IMMEDIATE}, {"immutable", IMMUTABLE}, + {"implicit", IMPLICIT_P}, {"in", IN_P}, {"increment", INCREMENT}, {"index", INDEX}, diff --git a/src/backend/parser/parse_clause.c b/src/backend/parser/parse_clause.c index a46ff5e2fc..245c0ba422 100644 --- a/src/backend/parser/parse_clause.c +++ b/src/backend/parser/parse_clause.c @@ -8,7 +8,7 @@ * * * IDENTIFICATION - * $Header: /cvsroot/pgsql/src/backend/parser/parse_clause.c,v 1.97 2002/09/04 20:31:23 momjian Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/parse_clause.c,v 1.98 2002/09/18 21:35:22 tgl Exp $ * *------------------------------------------------------------------------- */ @@ -872,20 +872,24 @@ buildMergedJoinVar(JoinType jointype, Var *l_colvar, Var *r_colvar) * typmod is not same as input. */ if (l_colvar->vartype != outcoltype) - l_node = coerce_type(NULL, (Node *) l_colvar, l_colvar->vartype, - outcoltype, outcoltypmod, false); + l_node = coerce_type((Node *) l_colvar, l_colvar->vartype, + outcoltype, + COERCION_IMPLICIT, COERCE_IMPLICIT_CAST); else if (l_colvar->vartypmod != outcoltypmod) l_node = (Node *) makeRelabelType((Node *) l_colvar, - outcoltype, outcoltypmod); + outcoltype, outcoltypmod, + COERCE_IMPLICIT_CAST); else l_node = (Node *) l_colvar; if (r_colvar->vartype != outcoltype) - r_node = coerce_type(NULL, (Node *) r_colvar, r_colvar->vartype, - outcoltype, outcoltypmod, false); + r_node = coerce_type((Node *) r_colvar, r_colvar->vartype, + outcoltype, + COERCION_IMPLICIT, COERCE_IMPLICIT_CAST); else if (r_colvar->vartypmod != outcoltypmod) r_node = (Node *) makeRelabelType((Node *) r_colvar, - outcoltype, outcoltypmod); + outcoltype, outcoltypmod, + COERCE_IMPLICIT_CAST); else r_node = (Node *) r_colvar; diff --git a/src/backend/parser/parse_coerce.c b/src/backend/parser/parse_coerce.c index d57e18f232..c0081133eb 100644 --- a/src/backend/parser/parse_coerce.c +++ b/src/backend/parser/parse_coerce.c @@ -8,7 +8,7 @@ * * * IDENTIFICATION - * $Header: /cvsroot/pgsql/src/backend/parser/parse_coerce.c,v 2.83 2002/09/04 20:31:23 momjian Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/parse_coerce.c,v 2.84 2002/09/18 21:35:22 tgl Exp $ * *------------------------------------------------------------------------- */ @@ -23,28 +23,104 @@ #include "parser/parse_func.h" #include "parser/parse_type.h" #include "utils/builtins.h" +#include "utils/fmgroids.h" #include "utils/lsyscache.h" #include "utils/syscache.h" +static Node *coerce_type_typmod(Node *node, + Oid targetTypeId, int32 targetTypMod, + CoercionForm cformat); static Oid PreferredType(CATEGORY category, Oid type); static bool find_coercion_pathway(Oid targetTypeId, Oid sourceTypeId, - bool isExplicit, - Oid *funcid); -static Oid find_typmod_coercion_function(Oid typeId); -static Node *build_func_call(Oid funcid, Oid rettype, List *args); + CoercionContext ccontext, + Oid *funcid); +static Node *build_func_call(Oid funcid, Oid rettype, List *args, + CoercionForm fformat); + + +/* + * coerce_to_target_type() + * Convert an expression to a target type and typmod. + * + * This is the general-purpose entry point for arbitrary type coercion + * operations. Direct use of the component operations can_coerce_type, + * coerce_type, and coerce_type_typmod should be restricted to special + * cases (eg, when the conversion is expected to succeed). + * + * Returns the possibly-transformed expression tree, or NULL if the type + * conversion is not possible. (We do this, rather than elog'ing directly, + * so that callers can generate custom error messages indicating context.) + * + * expr - input expression tree (already transformed by transformExpr) + * exprtype - result type of expr + * targettype - desired result type + * targettypmod - desired result typmod + * ccontext, cformat - context indicators to control coercions + */ +Node * +coerce_to_target_type(Node *expr, Oid exprtype, + Oid targettype, int32 targettypmod, + CoercionContext ccontext, + CoercionForm cformat) +{ + if (can_coerce_type(1, &exprtype, &targettype, ccontext)) + expr = coerce_type(expr, exprtype, targettype, + ccontext, cformat); + /* + * String hacks to get transparent conversions for char and varchar: + * if a coercion to text is available, use it for forced coercions to + * char(n) or varchar(n). + * + * This is pretty grotty, but seems easier to maintain than providing + * entries in pg_cast that parallel all the ones for text. + */ + else if (ccontext >= COERCION_ASSIGNMENT && + (targettype == BPCHAROID || targettype == VARCHAROID)) + { + Oid text_id = TEXTOID; + + if (can_coerce_type(1, &exprtype, &text_id, ccontext)) + { + expr = coerce_type(expr, exprtype, text_id, + ccontext, cformat); + /* Need a RelabelType if no typmod coercion is performed */ + if (targettypmod < 0) + expr = (Node *) makeRelabelType(expr, targettype, -1, + cformat); + } + else + expr = NULL; + } + else + expr = NULL; + + /* + * If the target is a fixed-length type, it may need a length coercion + * as well as a type coercion. + */ + if (expr != NULL) + expr = coerce_type_typmod(expr, targettype, targettypmod, cformat); + + return expr; +} /* * coerce_type() - * Convert a function argument to a different type. + * Convert an expression to a different type. * * The caller should already have determined that the coercion is possible; * see can_coerce_type. + * + * No coercion to a typmod (length) is performed here. The caller must + * call coerce_type_typmod as well, if a typmod constraint is wanted. + * (But if the target type is a domain, it may internally contain a + * typmod constraint, which will be applied inside coerce_type_constraints.) */ Node * -coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, - Oid targetTypeId, int32 atttypmod, bool isExplicit) +coerce_type(Node *node, Oid inputTypeId, Oid targetTypeId, + CoercionContext ccontext, CoercionForm cformat) { Node *result; Oid funcId; @@ -68,7 +144,7 @@ coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, * example, int4's typinput function will reject "1.2", whereas * float-to-int type conversion will round to integer. * - * XXX if the typinput function is not cachable, we really ought to + * XXX if the typinput function is not immutable, we really ought to * postpone evaluation of the function call until runtime. But * there is no way to represent a typinput function call as an * expression tree, because C-string values are not Datums. (XXX @@ -91,28 +167,31 @@ coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, con->constvalue)); /* - * If target is a domain, use the typmod it applies to the - * base type. Note that we call stringTypeDatum using the - * domain's pg_type row, though. This works because the - * domain row has the same typinput and typelem as the base - * type --- ugly... + * We pass typmod -1 to the input routine, primarily because + * existing input routines follow implicit-coercion semantics + * for length checks, which is not always what we want here. + * Any length constraint will be applied later by our caller. + * + * Note that we call stringTypeDatum using the domain's pg_type + * row, if it's a domain. This works because the domain row has + * the same typinput and typelem as the base type --- ugly... */ - if (targetTyptype == 'd') - atttypmod = getBaseTypeMod(targetTypeId, atttypmod); - - newcon->constvalue = stringTypeDatum(targetType, val, atttypmod); + newcon->constvalue = stringTypeDatum(targetType, val, -1); pfree(val); } result = (Node *) newcon; - /* - * If target is a domain, apply constraints (except for typmod, - * which we assume the input routine took care of). - */ + /* If target is a domain, apply constraints. */ if (targetTyptype == 'd') - result = coerce_type_constraints(pstate, result, targetTypeId, - false); + { + result = coerce_type_constraints(result, targetTypeId, + cformat); + /* We might now need a RelabelType. */ + if (exprType(result) != targetTypeId) + result = (Node *) makeRelabelType(result, targetTypeId, -1, + cformat); + } ReleaseSysCache(targetType); } @@ -120,9 +199,10 @@ coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, targetTypeId == ANYARRAYOID) { /* assume can_coerce_type verified that implicit coercion is okay */ + /* NB: we do NOT want a RelabelType here */ result = node; } - else if (find_coercion_pathway(targetTypeId, inputTypeId, isExplicit, + else if (find_coercion_pathway(targetTypeId, inputTypeId, ccontext, &funcId)) { if (OidIsValid(funcId)) @@ -135,7 +215,8 @@ coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, */ Oid baseTypeId = getBaseType(targetTypeId); - result = build_func_call(funcId, baseTypeId, makeList1(node)); + result = build_func_call(funcId, baseTypeId, makeList1(node), + cformat); /* * If domain, test against domain constraints and relabel with @@ -143,9 +224,10 @@ coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, */ if (targetTypeId != baseTypeId) { - result = coerce_type_constraints(pstate, result, - targetTypeId, true); - result = (Node *) makeRelabelType(result, targetTypeId, -1); + result = coerce_type_constraints(result, targetTypeId, + cformat); + result = (Node *) makeRelabelType(result, targetTypeId, -1, + cformat); } /* @@ -179,8 +261,8 @@ coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, * Also, domains may have value restrictions beyond the base type * that must be accounted for. */ - result = coerce_type_constraints(pstate, node, - targetTypeId, true); + result = coerce_type_constraints(node, targetTypeId, + cformat); /* * XXX could we label result with exprTypmod(node) instead of @@ -189,7 +271,8 @@ coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, * typmod, which is likely but not certain (wrong if target is * a domain, in any case). */ - result = (Node *) makeRelabelType(result, targetTypeId, -1); + result = (Node *) makeRelabelType(result, targetTypeId, -1, + cformat); } } else if (typeInheritsFrom(inputTypeId, targetTypeId)) @@ -199,7 +282,8 @@ coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, * except relabel the type. This is binary compatibility for * complex types. */ - result = (Node *) makeRelabelType(node, targetTypeId, -1); + result = (Node *) makeRelabelType(node, targetTypeId, -1, + cformat); } else { @@ -215,15 +299,14 @@ coerce_type(ParseState *pstate, Node *node, Oid inputTypeId, /* * can_coerce_type() - * Can input_typeids be coerced to func_typeids? + * Can input_typeids be coerced to target_typeids? * - * We must be told whether this is an implicit or explicit coercion - * (explicit being a CAST construct, explicit function call, etc). - * We will accept a wider set of coercion cases for an explicit coercion. + * We must be told the context (CAST construct, assignment, implicit coercion) + * as this determines the set of available casts. */ bool -can_coerce_type(int nargs, Oid *input_typeids, Oid *func_typeids, - bool isExplicit) +can_coerce_type(int nargs, Oid *input_typeids, Oid *target_typeids, + CoercionContext ccontext) { int i; @@ -231,7 +314,7 @@ can_coerce_type(int nargs, Oid *input_typeids, Oid *func_typeids, for (i = 0; i < nargs; i++) { Oid inputTypeId = input_typeids[i]; - Oid targetTypeId = func_typeids[i]; + Oid targetTypeId = target_typeids[i]; Oid funcId; /* no problem if same type */ @@ -278,7 +361,7 @@ can_coerce_type(int nargs, Oid *input_typeids, Oid *func_typeids, /* * Otherwise reject; this assumes there are no explicit - * coercions to ANYARRAY. If we don't reject then + * coercion paths to ANYARRAY. If we don't reject then * parse_coerce would have to repeat the above test. */ return false; @@ -288,7 +371,7 @@ can_coerce_type(int nargs, Oid *input_typeids, Oid *func_typeids, * If pg_cast shows that we can coerce, accept. This test now * covers both binary-compatible and coercion-function cases. */ - if (find_coercion_pathway(targetTypeId, inputTypeId, isExplicit, + if (find_coercion_pathway(targetTypeId, inputTypeId, ccontext, &funcId)) continue; @@ -312,10 +395,12 @@ can_coerce_type(int nargs, Oid *input_typeids, Oid *func_typeids, * Create an expression tree to enforce the constraints (if any) * that should be applied by the type. Currently this is only * interesting for domain types. + * + * NOTE: result tree is not guaranteed to show the correct exprType() for + * the domain; it may show the base type. Caller must relabel if needed. */ Node * -coerce_type_constraints(ParseState *pstate, Node *arg, - Oid typeId, bool applyTypmod) +coerce_type_constraints(Node *arg, Oid typeId, CoercionForm cformat) { char *notNull = NULL; int32 typmod = -1; @@ -356,8 +441,8 @@ coerce_type_constraints(ParseState *pstate, Node *arg, /* * If domain applies a typmod to its base type, do length coercion. */ - if (applyTypmod && typmod >= 0) - arg = coerce_type_typmod(pstate, arg, typeId, typmod); + if (typmod >= 0) + arg = coerce_type_typmod(arg, typeId, typmod, cformat); /* * Only need to add one NOT NULL check regardless of how many domains @@ -380,8 +465,9 @@ coerce_type_constraints(ParseState *pstate, Node *arg, } -/* coerce_type_typmod() - * Force a value to a particular typmod, if meaningful and possible. +/* + * coerce_type_typmod() + * Force a value to a particular typmod, if meaningful and possible. * * This is applied to values that are going to be stored in a relation * (where we have an atttypmod for the column) as well as values being @@ -394,33 +480,65 @@ coerce_type_constraints(ParseState *pstate, Node *arg, * coercion for a domain is considered to be part of the type coercion * needed to produce the domain value in the first place. So, no getBaseType. */ -Node * -coerce_type_typmod(ParseState *pstate, Node *node, - Oid targetTypeId, int32 atttypmod) +static Node * +coerce_type_typmod(Node *node, Oid targetTypeId, int32 targetTypMod, + CoercionForm cformat) { Oid funcId; + int nargs; /* * A negative typmod is assumed to mean that no coercion is wanted. */ - if (atttypmod < 0 || atttypmod == exprTypmod(node)) + if (targetTypMod < 0 || targetTypMod == exprTypmod(node)) return node; - funcId = find_typmod_coercion_function(targetTypeId); + funcId = find_typmod_coercion_function(targetTypeId, &nargs); if (OidIsValid(funcId)) { + List *args; Const *cons; + Node *fcall; + /* Pass given value, plus target typmod as an int4 constant */ cons = makeConst(INT4OID, sizeof(int32), - Int32GetDatum(atttypmod), + Int32GetDatum(targetTypMod), false, true, false, false); - node = build_func_call(funcId, targetTypeId, makeList2(node, cons)); + args = makeList2(node, cons); + + if (nargs == 3) + { + /* Pass it a boolean isExplicit parameter, too */ + cons = makeConst(BOOLOID, + sizeof(bool), + BoolGetDatum(cformat != COERCE_IMPLICIT_CAST), + false, + true, + false, + false); + + args = lappend(args, cons); + } + + fcall = build_func_call(funcId, targetTypeId, args, cformat); + + /* + * If the input is a constant, apply the length coercion + * function now instead of delaying to runtime. + * + * See the comments for the similar case in coerce_type. + */ + if (node && IsA(node, Const) && + !((Const *) node)->constisnull) + node = eval_const_expressions(fcall); + else + node = fcall; } return node; @@ -437,19 +555,19 @@ Node * coerce_to_boolean(Node *node, const char *constructName) { Oid inputTypeId = exprType(node); - Oid targetTypeId; if (inputTypeId != BOOLOID) { - targetTypeId = BOOLOID; - if (!can_coerce_type(1, &inputTypeId, &targetTypeId, false)) + node = coerce_to_target_type(node, inputTypeId, + BOOLOID, -1, + COERCION_ASSIGNMENT, + COERCE_IMPLICIT_CAST); + if (node == NULL) { /* translator: first %s is name of a SQL construct, eg WHERE */ elog(ERROR, "Argument of %s must be type boolean, not type %s", constructName, format_type_be(inputTypeId)); } - node = coerce_type(NULL, node, inputTypeId, targetTypeId, -1, - false); } if (expression_returns_set(node)) @@ -472,12 +590,6 @@ coerce_to_boolean(Node *node, const char *constructName) * in the list will be preferred if there is doubt. * 'context' is a phrase to use in the error message if we fail to select * a usable type. - * - * XXX this code is WRONG, since (for example) given the input (int4,int8) - * it will select int4, whereas according to SQL92 clause 9.3 the correct - * answer is clearly int8. To fix this we need a notion of a promotion - * hierarchy within type categories --- something more complete than - * just a single preferred type. */ Oid select_common_type(List *typeids, const char *context) @@ -511,12 +623,13 @@ select_common_type(List *typeids, const char *context) elog(ERROR, "%s types '%s' and '%s' not matched", context, format_type_be(ptype), format_type_be(ntype)); } - else if (IsPreferredType(pcategory, ntype) - && !IsPreferredType(pcategory, ptype) - && can_coerce_type(1, &ptype, &ntype, false)) + else if (!IsPreferredType(pcategory, ptype) && + can_coerce_type(1, &ptype, &ntype, COERCION_IMPLICIT) && + !can_coerce_type(1, &ntype, &ptype, COERCION_IMPLICIT)) { /* - * new one is preferred and can convert? then take it... + * take new type if can coerce to it implicitly but not the + * other way; but if we have a preferred type, stay on it. */ ptype = ntype; pcategory = TypeCategory(ptype); @@ -547,26 +660,20 @@ select_common_type(List *typeids, const char *context) * This is used following select_common_type() to coerce the individual * expressions to the desired type. 'context' is a phrase to use in the * error message if we fail to coerce. - * - * NOTE: pstate may be NULL. */ Node * -coerce_to_common_type(ParseState *pstate, Node *node, - Oid targetTypeId, - const char *context) +coerce_to_common_type(Node *node, Oid targetTypeId, const char *context) { Oid inputTypeId = exprType(node); if (inputTypeId == targetTypeId) return node; /* no work */ - if (can_coerce_type(1, &inputTypeId, &targetTypeId, false)) - node = coerce_type(pstate, node, inputTypeId, targetTypeId, -1, - false); + if (can_coerce_type(1, &inputTypeId, &targetTypeId, COERCION_IMPLICIT)) + node = coerce_type(node, inputTypeId, targetTypeId, + COERCION_IMPLICIT, COERCE_IMPLICIT_CAST); else - { elog(ERROR, "%s unable to convert to type %s", context, format_type_be(targetTypeId)); - } return node; } @@ -708,8 +815,6 @@ PreferredType(CATEGORY category, Oid type) type == REGCLASSOID || type == REGTYPEOID) result = OIDOID; - else if (type == NUMERICOID) - result = NUMERICOID; else result = FLOAT8OID; break; @@ -742,49 +847,52 @@ PreferredType(CATEGORY category, Oid type) } /* PreferredType() */ -/* IsBinaryCompatible() - * Check if two types are binary-compatible. +/* IsBinaryCoercible() + * Check if srctype is binary-coercible to targettype. * * This notion allows us to cheat and directly exchange values without * going through the trouble of calling a conversion function. * - * As of 7.3, binary compatibility isn't hardwired into the code anymore. - * We consider two types binary-compatible if there is an implicit, - * no-function-needed pg_cast entry. NOTE that we assume that such - * entries are symmetric, ie, it doesn't matter which type we consider - * source and which target. (cf. checks in opr_sanity regression test) + * As of 7.3, binary coercibility isn't hardwired into the code anymore. + * We consider two types binary-coercible if there is an implicitly + * invokable, no-function-needed pg_cast entry. + * + * This function replaces IsBinaryCompatible(), which was an inherently + * symmetric test. Since the pg_cast entries aren't necessarily symmetric, + * the order of the operands is now significant. */ bool -IsBinaryCompatible(Oid type1, Oid type2) +IsBinaryCoercible(Oid srctype, Oid targettype) { HeapTuple tuple; Form_pg_cast castForm; bool result; /* Fast path if same type */ - if (type1 == type2) + if (srctype == targettype) return true; /* Perhaps the types are domains; if so, look at their base types */ - if (OidIsValid(type1)) - type1 = getBaseType(type1); - if (OidIsValid(type2)) - type2 = getBaseType(type2); + if (OidIsValid(srctype)) + srctype = getBaseType(srctype); + if (OidIsValid(targettype)) + targettype = getBaseType(targettype); /* Somewhat-fast path if same base type */ - if (type1 == type2) + if (srctype == targettype) return true; /* Else look in pg_cast */ tuple = SearchSysCache(CASTSOURCETARGET, - ObjectIdGetDatum(type1), - ObjectIdGetDatum(type2), + ObjectIdGetDatum(srctype), + ObjectIdGetDatum(targettype), 0, 0); if (!HeapTupleIsValid(tuple)) return false; /* no cast */ castForm = (Form_pg_cast) GETSTRUCT(tuple); - result = (castForm->castfunc == InvalidOid) && castForm->castimplicit; + result = (castForm->castfunc == InvalidOid && + castForm->castcontext == COERCION_CODE_IMPLICIT); ReleaseSysCache(tuple); @@ -796,12 +904,15 @@ IsBinaryCompatible(Oid type1, Oid type2) * find_coercion_pathway * Look for a coercion pathway between two types. * - * If we find a matching entry in pg_cast, return TRUE, and set *funcid + * ccontext determines the set of available casts. + * + * If we find a suitable entry in pg_cast, return TRUE, and set *funcid * to the castfunc value (which may be InvalidOid for a binary-compatible * coercion). */ static bool -find_coercion_pathway(Oid targetTypeId, Oid sourceTypeId, bool isExplicit, +find_coercion_pathway(Oid targetTypeId, Oid sourceTypeId, + CoercionContext ccontext, Oid *funcid) { bool result = false; @@ -828,8 +939,29 @@ find_coercion_pathway(Oid targetTypeId, Oid sourceTypeId, bool isExplicit, if (HeapTupleIsValid(tuple)) { Form_pg_cast castForm = (Form_pg_cast) GETSTRUCT(tuple); + CoercionContext castcontext; + + /* convert char value for castcontext to CoercionContext enum */ + switch (castForm->castcontext) + { + case COERCION_CODE_IMPLICIT: + castcontext = COERCION_IMPLICIT; + break; + case COERCION_CODE_ASSIGNMENT: + castcontext = COERCION_ASSIGNMENT; + break; + case COERCION_CODE_EXPLICIT: + castcontext = COERCION_EXPLICIT; + break; + default: + elog(ERROR, "find_coercion_pathway: bogus castcontext %c", + castForm->castcontext); + castcontext = 0; /* keep compiler quiet */ + break; + } - if (isExplicit || castForm->castimplicit) + /* Rely on ordering of enum for correct behavior here */ + if (ccontext >= castcontext) { *funcid = castForm->castfunc; result = true; @@ -850,30 +982,59 @@ find_coercion_pathway(Oid targetTypeId, Oid sourceTypeId, bool isExplicit, * the type requires coercion to its own length and that the said * function should be invoked to do that. * + * Alternatively, the length-coercing function may have the signature + * (targettype, int4, bool). On success, *nargs is set to report which + * signature we found. + * * "bpchar" (ie, char(N)) and "numeric" are examples of such types. * + * If the given type is a varlena array type, we do not look for a coercion + * function associated directly with the array type, but instead look for + * one associated with the element type. If one exists, we report + * array_length_coerce() as the coercion function to use. + * * This mechanism may seem pretty grotty and in need of replacement by * something in pg_cast, but since typmod is only interesting for datatypes * that have special handling in the grammar, there's not really much * percentage in making it any easier to apply such coercions ... */ -static Oid -find_typmod_coercion_function(Oid typeId) +Oid +find_typmod_coercion_function(Oid typeId, int *nargs) { Oid funcid = InvalidOid; + bool isArray = false; Type targetType; + Form_pg_type typeForm; char *typname; Oid typnamespace; Oid oid_array[FUNC_MAX_ARGS]; HeapTuple ftup; targetType = typeidType(typeId); - typname = NameStr(((Form_pg_type) GETSTRUCT(targetType))->typname); - typnamespace = ((Form_pg_type) GETSTRUCT(targetType))->typnamespace; + typeForm = (Form_pg_type) GETSTRUCT(targetType); + /* Check for a varlena array type (and not a domain) */ + if (typeForm->typelem != InvalidOid && + typeForm->typlen == -1 && + typeForm->typtype != 'd') + { + /* Yes, switch our attention to the element type */ + typeId = typeForm->typelem; + ReleaseSysCache(targetType); + targetType = typeidType(typeId); + typeForm = (Form_pg_type) GETSTRUCT(targetType); + isArray = true; + } + + /* Function name is same as type internal name, and in same namespace */ + typname = NameStr(typeForm->typname); + typnamespace = typeForm->typnamespace; + + /* First look for parameters (type, int4) */ MemSet(oid_array, 0, FUNC_MAX_ARGS * sizeof(Oid)); oid_array[0] = typeId; oid_array[1] = INT4OID; + *nargs = 2; ftup = SearchSysCache(PROCNAMENSP, CStringGetDatum(typname), @@ -894,8 +1055,45 @@ find_typmod_coercion_function(Oid typeId) ReleaseSysCache(ftup); } + if (!OidIsValid(funcid)) + { + /* Didn't find a function, so now try (type, int4, bool) */ + oid_array[2] = BOOLOID; + *nargs = 3; + + ftup = SearchSysCache(PROCNAMENSP, + CStringGetDatum(typname), + Int16GetDatum(3), + PointerGetDatum(oid_array), + ObjectIdGetDatum(typnamespace)); + if (HeapTupleIsValid(ftup)) + { + Form_pg_proc pform = (Form_pg_proc) GETSTRUCT(ftup); + + /* Make sure the function's result type is as expected */ + if (pform->prorettype == typeId && !pform->proretset && + !pform->proisagg) + { + /* Okay to use it */ + funcid = HeapTupleGetOid(ftup); + } + ReleaseSysCache(ftup); + } + } + ReleaseSysCache(targetType); + /* + * Now, if we did find a coercion function for an array element type, + * report array_length_coerce() as the function to use. We know it + * takes three arguments always. + */ + if (isArray && OidIsValid(funcid)) + { + funcid = F_ARRAY_LENGTH_COERCE; + *nargs = 3; + } + return funcid; } @@ -905,7 +1103,7 @@ find_typmod_coercion_function(Oid typeId) * The argument expressions must have been transformed already. */ static Node * -build_func_call(Oid funcid, Oid rettype, List *args) +build_func_call(Oid funcid, Oid rettype, List *args, CoercionForm fformat) { Func *funcnode; Expr *expr; @@ -914,6 +1112,7 @@ build_func_call(Oid funcid, Oid rettype, List *args) funcnode->funcid = funcid; funcnode->funcresulttype = rettype; funcnode->funcretset = false; /* only possible case here */ + funcnode->funcformat = fformat; funcnode->func_fcache = NULL; expr = makeNode(Expr); diff --git a/src/backend/parser/parse_expr.c b/src/backend/parser/parse_expr.c index 7be413f6b5..3873fd37f0 100644 --- a/src/backend/parser/parse_expr.c +++ b/src/backend/parser/parse_expr.c @@ -8,7 +8,7 @@ * * * IDENTIFICATION - * $Header: /cvsroot/pgsql/src/backend/parser/parse_expr.c,v 1.128 2002/09/04 20:31:23 momjian Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/parse_expr.c,v 1.129 2002/09/18 21:35:22 tgl Exp $ * *------------------------------------------------------------------------- */ @@ -28,7 +28,6 @@ #include "parser/parse_func.h" #include "parser/parse_oper.h" #include "parser/parse_relation.h" -#include "parser/parse_target.h" #include "parser/parse_type.h" #include "utils/builtins.h" #include "utils/lsyscache.h" @@ -40,9 +39,7 @@ static int expr_depth_counter = 0; bool Transform_null_equals = false; -static Node *parser_typecast_constant(Value *expr, TypeName *typename); -static Node *parser_typecast_expression(ParseState *pstate, - Node *expr, TypeName *typename); +static Node *typecast_expression(Node *expr, TypeName *typename); static Node *transformColumnRef(ParseState *pstate, ColumnRef *cref); static Node *transformIndirection(ParseState *pstate, Node *basenode, List *indirection); @@ -145,10 +142,9 @@ transformExpr(ParseState *pstate, Node *expr) A_Const *con = (A_Const *) expr; Value *val = &con->val; + result = (Node *) make_const(val); if (con->typename != NULL) - result = parser_typecast_constant(val, con->typename); - else - result = (Node *) make_const(val); + result = typecast_expression(result, con->typename); break; } case T_ExprFieldSelect: @@ -175,7 +171,7 @@ transformExpr(ParseState *pstate, Node *expr) TypeCast *tc = (TypeCast *) expr; Node *arg = transformExpr(pstate, tc->arg); - result = parser_typecast_expression(pstate, arg, tc->typename); + result = typecast_expression(arg, tc->typename); break; } case T_A_Expr: @@ -562,8 +558,7 @@ transformExpr(ParseState *pstate, Node *expr) newc->casetype = ptype; /* Convert default result clause, if necessary */ - newc->defresult = coerce_to_common_type(pstate, - newc->defresult, + newc->defresult = coerce_to_common_type(newc->defresult, ptype, "CASE/ELSE"); @@ -572,8 +567,7 @@ transformExpr(ParseState *pstate, Node *expr) { CaseWhen *w = (CaseWhen *) lfirst(args); - w->result = coerce_to_common_type(pstate, - w->result, + w->result = coerce_to_common_type(w->result, ptype, "CASE/WHEN"); } @@ -671,8 +665,12 @@ transformIndirection(ParseState *pstate, Node *basenode, List *indirection) if (indirection == NIL) return basenode; return (Node *) transformArraySubscripts(pstate, - basenode, exprType(basenode), - indirection, false, NULL); + basenode, + exprType(basenode), + exprTypmod(basenode), + indirection, + false, + NULL); } static Node * @@ -1037,23 +1035,13 @@ exprTypmod(Node *expr) * * If coercedTypmod is not NULL, the typmod is stored there if the expression * is a length-coercion function, else -1 is stored there. - * - * We assume that a two-argument function named for a datatype, whose - * output and first argument types are that datatype, and whose second - * input is an int32 constant, represents a forced length coercion. - * - * XXX It'd be better if the parsetree retained some explicit indication - * of the coercion, so we didn't need these heuristics. */ bool exprIsLengthCoercion(Node *expr, int32 *coercedTypmod) { Func *func; + int nargs; Const *second_arg; - HeapTuple procTuple; - HeapTuple typeTuple; - Form_pg_proc procStruct; - Form_pg_type typeStruct; if (coercedTypmod != NULL) *coercedTypmod = -1; /* default result on failure */ @@ -1067,62 +1055,26 @@ exprIsLengthCoercion(Node *expr, int32 *coercedTypmod) Assert(IsA(func, Func)); /* - * If it's not a two-argument function with the second argument being - * an int4 constant, it can't have been created from a length - * coercion. + * If it didn't come from a coercion context, reject. */ - if (length(((Expr *) expr)->args) != 2) - return false; - second_arg = (Const *) lsecond(((Expr *) expr)->args); - if (!IsA(second_arg, Const) || - second_arg->consttype != INT4OID || - second_arg->constisnull) + if (func->funcformat != COERCE_EXPLICIT_CAST && + func->funcformat != COERCE_IMPLICIT_CAST) return false; /* - * Lookup the function in pg_proc - */ - procTuple = SearchSysCache(PROCOID, - ObjectIdGetDatum(func->funcid), - 0, 0, 0); - if (!HeapTupleIsValid(procTuple)) - elog(ERROR, "cache lookup for proc %u failed", func->funcid); - procStruct = (Form_pg_proc) GETSTRUCT(procTuple); - - /* - * It must be a function with two arguments where the first is of the - * same type as the return value and the second is an int4. Also, just - * to be sure, check return type agrees with expr node. + * If it's not a two-argument or three-argument function with the second + * argument being an int4 constant, it can't have been created from a + * length coercion (it must be a type coercion, instead). */ - if (procStruct->pronargs != 2 || - procStruct->prorettype != procStruct->proargtypes[0] || - procStruct->proargtypes[1] != INT4OID || - procStruct->prorettype != ((Expr *) expr)->typeOid) - { - ReleaseSysCache(procTuple); + nargs = length(((Expr *) expr)->args); + if (nargs < 2 || nargs > 3) return false; - } - /* - * Furthermore, the name and namespace of the function must be the - * same as its result type's name/namespace (cf. - * find_coercion_function). - */ - typeTuple = SearchSysCache(TYPEOID, - ObjectIdGetDatum(procStruct->prorettype), - 0, 0, 0); - if (!HeapTupleIsValid(typeTuple)) - elog(ERROR, "cache lookup for type %u failed", - procStruct->prorettype); - typeStruct = (Form_pg_type) GETSTRUCT(typeTuple); - if (strcmp(NameStr(procStruct->proname), - NameStr(typeStruct->typname)) != 0 || - procStruct->pronamespace != typeStruct->typnamespace) - { - ReleaseSysCache(procTuple); - ReleaseSysCache(typeTuple); + second_arg = (Const *) lsecond(((Expr *) expr)->args); + if (!IsA(second_arg, Const) || + second_arg->consttype != INT4OID || + second_arg->constisnull) return false; - } /* * OK, it is indeed a length-coercion function. @@ -1130,79 +1082,17 @@ exprIsLengthCoercion(Node *expr, int32 *coercedTypmod) if (coercedTypmod != NULL) *coercedTypmod = DatumGetInt32(second_arg->constvalue); - ReleaseSysCache(procTuple); - ReleaseSysCache(typeTuple); return true; } /* - * Produce an appropriate Const node from a constant value produced - * by the parser and an explicit type name to cast to. - */ -static Node * -parser_typecast_constant(Value *expr, TypeName *typename) -{ - Type tp; - Datum datum; - Const *con; - char *const_string = NULL; - bool string_palloced = false; - bool isNull = false; - - tp = typenameType(typename); - - switch (nodeTag(expr)) - { - case T_Integer: - const_string = DatumGetCString(DirectFunctionCall1(int4out, - Int32GetDatum(expr->val.ival))); - string_palloced = true; - break; - case T_Float: - case T_String: - case T_BitString: - const_string = expr->val.str; - break; - case T_Null: - isNull = true; - break; - default: - elog(ERROR, "Cannot cast this expression to type '%s'", - typeTypeName(tp)); - } - - if (isNull) - datum = (Datum) NULL; - else - datum = stringTypeDatum(tp, const_string, typename->typmod); - - con = makeConst(typeTypeId(tp), - typeLen(tp), - datum, - isNull, - typeByVal(tp), - false, /* not a set */ - true /* is cast */ ); - - if (string_palloced) - pfree(const_string); - - ReleaseSysCache(tp); - - return (Node *) con; -} - -/* - * Handle an explicit CAST applied to a non-constant expression. - * (Actually, this works for constants too, but gram.y won't generate - * a TypeCast node if the argument is just a constant.) + * Handle an explicit CAST construct. * * The given expr has already been transformed, but we need to lookup * the type name and then apply any necessary coercion function(s). */ static Node * -parser_typecast_expression(ParseState *pstate, - Node *expr, TypeName *typename) +typecast_expression(Node *expr, TypeName *typename) { Oid inputType = exprType(expr); Oid targetType; @@ -1212,23 +1102,14 @@ parser_typecast_expression(ParseState *pstate, if (inputType == InvalidOid) return expr; /* do nothing if NULL input */ - if (inputType != targetType) - { - expr = CoerceTargetExpr(pstate, expr, inputType, - targetType, typename->typmod, - true); /* explicit coercion */ - if (expr == NULL) - elog(ERROR, "Cannot cast type '%s' to '%s'", - format_type_be(inputType), - format_type_be(targetType)); - } - - /* - * If the target is a fixed-length type, it may need a length coercion - * as well as a type coercion. - */ - expr = coerce_type_typmod(pstate, expr, - targetType, typename->typmod); + expr = coerce_to_target_type(expr, inputType, + targetType, typename->typmod, + COERCION_EXPLICIT, + COERCE_EXPLICIT_CAST); + if (expr == NULL) + elog(ERROR, "Cannot cast type %s to %s", + format_type_be(inputType), + format_type_be(targetType)); return expr; } diff --git a/src/backend/parser/parse_func.c b/src/backend/parser/parse_func.c index 648ddfbaf0..9a54a900ae 100644 --- a/src/backend/parser/parse_func.c +++ b/src/backend/parser/parse_func.c @@ -8,7 +8,7 @@ * * * IDENTIFICATION - * $Header: /cvsroot/pgsql/src/backend/parser/parse_func.c,v 1.136 2002/09/04 20:31:23 momjian Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/parse_func.c,v 1.137 2002/09/18 21:35:22 tgl Exp $ * *------------------------------------------------------------------------- */ @@ -32,15 +32,12 @@ #include "utils/syscache.h" -static Node *ParseComplexProjection(ParseState *pstate, - char *funcname, - Node *first_arg); +static Node *ParseComplexProjection(char *funcname, Node *first_arg); static Oid **argtype_inherit(int nargs, Oid *argtypes); static int find_inheritors(Oid relid, Oid **supervec); static Oid **gen_cross_product(InhPaths *arginh, int nargs); -static void make_arguments(ParseState *pstate, - int nargs, +static void make_arguments(int nargs, List *fargs, Oid *input_typeids, Oid *function_typeids); @@ -137,7 +134,7 @@ ParseFuncOrColumn(ParseState *pstate, List *funcname, List *fargs, * ParseComplexProjection can't handle the projection, we have * to keep going. */ - retval = ParseComplexProjection(pstate, cname, first_arg); + retval = ParseComplexProjection(cname, first_arg); if (retval) return retval; } @@ -243,8 +240,8 @@ ParseFuncOrColumn(ParseState *pstate, List *funcname, List *fargs, * We can do it as a trivial coercion. coerce_type can handle * these cases, so why duplicate code... */ - return coerce_type(pstate, lfirst(fargs), - oid_array[0], rettype, -1, true); + return coerce_type(lfirst(fargs), oid_array[0], rettype, + COERCION_EXPLICIT, COERCE_EXPLICIT_CALL); } else if (fdresult == FUNCDETAIL_NORMAL) { @@ -296,7 +293,7 @@ ParseFuncOrColumn(ParseState *pstate, List *funcname, List *fargs, } /* perform the necessary typecasting of arguments */ - make_arguments(pstate, nargs, fargs, oid_array, true_oid_array); + make_arguments(nargs, fargs, oid_array, true_oid_array); /* build the appropriate output structure */ if (fdresult == FUNCDETAIL_NORMAL) @@ -307,6 +304,7 @@ ParseFuncOrColumn(ParseState *pstate, List *funcname, List *fargs, funcnode->funcid = funcid; funcnode->funcresulttype = rettype; funcnode->funcretset = retset; + funcnode->funcformat = COERCE_EXPLICIT_CALL; funcnode->func_fcache = NULL; expr->typeOid = rettype; @@ -367,7 +365,7 @@ match_argtypes(int nargs, { next_candidate = current_candidate->next; if (can_coerce_type(nargs, input_typeids, current_candidate->args, - false)) + COERCION_IMPLICIT)) { current_candidate->next = *candidates; *candidates = current_candidate; @@ -470,7 +468,7 @@ func_select_candidate(int nargs, { if (input_typeids[i] != UNKNOWNOID) { - if (IsBinaryCompatible(current_typeids[i], input_typeids[i])) + if (IsBinaryCoercible(input_typeids[i], current_typeids[i])) nmatch++; } } @@ -776,7 +774,7 @@ func_get_detail(List *funcname, Node *arg1 = lfirst(fargs); if ((sourceType == UNKNOWNOID && IsA(arg1, Const)) || - IsBinaryCompatible(sourceType, targetType)) + IsBinaryCoercible(sourceType, targetType)) { /* Yup, it's a type coercion */ *funcid = InvalidOid; @@ -1120,8 +1118,7 @@ typeInheritsFrom(Oid subclassTypeId, Oid superclassTypeId) * actual arguments and argument types, do the necessary typecasting. */ static void -make_arguments(ParseState *pstate, - int nargs, +make_arguments(int nargs, List *fargs, Oid *input_typeids, Oid *function_typeids) @@ -1136,11 +1133,11 @@ make_arguments(ParseState *pstate, /* types don't match? then force coercion using a function call... */ if (input_typeids[i] != function_typeids[i]) { - lfirst(current_fargs) = coerce_type(pstate, - lfirst(current_fargs), + lfirst(current_fargs) = coerce_type(lfirst(current_fargs), input_typeids[i], - function_typeids[i], -1, - false); + function_typeids[i], + COERCION_IMPLICIT, + COERCE_IMPLICIT_CAST); } } } @@ -1179,9 +1176,7 @@ setup_field_select(Node *input, char *attname, Oid relid) * NB: argument is expected to be transformed already, ie, not a RangeVar. */ static Node * -ParseComplexProjection(ParseState *pstate, - char *funcname, - Node *first_arg) +ParseComplexProjection(char *funcname, Node *first_arg) { Oid argtype = exprType(first_arg); Oid argrelid; diff --git a/src/backend/parser/parse_node.c b/src/backend/parser/parse_node.c index 391694fa19..408fb4f11f 100644 --- a/src/backend/parser/parse_node.c +++ b/src/backend/parser/parse_node.c @@ -1,27 +1,22 @@ /*------------------------------------------------------------------------- * * parse_node.c - * various routines that make nodes for query plans + * various routines that make nodes for querytrees * * Portions Copyright (c) 1996-2002, PostgreSQL Global Development Group * Portions Copyright (c) 1994, Regents of the University of California * * * IDENTIFICATION - * $Header: /cvsroot/pgsql/src/backend/parser/parse_node.c,v 1.68 2002/09/04 20:31:24 momjian Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/parse_node.c,v 1.69 2002/09/18 21:35:22 tgl Exp $ * *------------------------------------------------------------------------- */ #include "postgres.h" -#include <ctype.h> -#include <errno.h> -#include <float.h> - #include "access/heapam.h" #include "catalog/pg_operator.h" #include "catalog/pg_type.h" -#include "fmgr.h" #include "nodes/makefuncs.h" #include "parser/parsetree.h" #include "parser/parse_coerce.h" @@ -29,14 +24,11 @@ #include "parser/parse_node.h" #include "parser/parse_oper.h" #include "parser/parse_relation.h" -#include "parser/parse_target.h" -#include "parser/parse_type.h" #include "utils/builtins.h" -#include "utils/varbit.h" +#include "utils/int8.h" #include "utils/lsyscache.h" #include "utils/syscache.h" - -static bool fitsInFloat(Value *value); +#include "utils/varbit.h" /* make_parsestate() @@ -70,8 +62,8 @@ make_operand(Node *tree, Oid orig_typeId, Oid target_typeId) { /* must coerce? */ if (target_typeId != orig_typeId) - result = coerce_type(NULL, tree, orig_typeId, target_typeId, -1, - false); + result = coerce_type(tree, orig_typeId, target_typeId, + COERCION_IMPLICIT, COERCE_IMPLICIT_CAST); else result = tree; } @@ -191,6 +183,7 @@ make_var(ParseState *pstate, RangeTblEntry *rte, int attrno) * arrayBase Already-transformed expression for the array as a whole * (may be NULL if we are handling an INSERT) * arrayType OID of array's datatype + * arrayTypMod typmod to be applied to array elements * indirection Untransformed list of subscripts (must not be NIL) * forceSlice If true, treat subscript as array slice in all cases * assignFrom NULL for array fetch, else transformed expression for source. @@ -199,6 +192,7 @@ ArrayRef * transformArraySubscripts(ParseState *pstate, Node *arrayBase, Oid arrayType, + int32 arrayTypMod, List *indirection, bool forceSlice, Node *assignFrom) @@ -286,8 +280,10 @@ transformArraySubscripts(ParseState *pstate, { subexpr = transformExpr(pstate, ai->lidx); /* If it's not int4 already, try to coerce */ - subexpr = CoerceTargetExpr(pstate, subexpr, exprType(subexpr), - INT4OID, -1, false); + subexpr = coerce_to_target_type(subexpr, exprType(subexpr), + INT4OID, -1, + COERCION_ASSIGNMENT, + COERCE_IMPLICIT_CAST); if (subexpr == NULL) elog(ERROR, "array index expressions must be integers"); } @@ -306,8 +302,10 @@ transformArraySubscripts(ParseState *pstate, } subexpr = transformExpr(pstate, ai->uidx); /* If it's not int4 already, try to coerce */ - subexpr = CoerceTargetExpr(pstate, subexpr, exprType(subexpr), - INT4OID, -1, false); + subexpr = coerce_to_target_type(subexpr, exprType(subexpr), + INT4OID, -1, + COERCION_ASSIGNMENT, + COERCE_IMPLICIT_CAST); if (subexpr == NULL) elog(ERROR, "array index expressions must be integers"); upperIndexpr = lappend(upperIndexpr, subexpr); @@ -323,19 +321,16 @@ transformArraySubscripts(ParseState *pstate, if (typesource != InvalidOid) { - if (typesource != typeneeded) - { - /* XXX fixme: need to get the array's atttypmod? */ - assignFrom = CoerceTargetExpr(pstate, assignFrom, - typesource, typeneeded, - -1, false); - if (assignFrom == NULL) - elog(ERROR, "Array assignment requires type '%s'" - " but expression is of type '%s'" - "\n\tYou will need to rewrite or cast the expression", - format_type_be(typeneeded), - format_type_be(typesource)); - } + assignFrom = coerce_to_target_type(assignFrom, typesource, + typeneeded, arrayTypMod, + COERCION_ASSIGNMENT, + COERCE_IMPLICIT_CAST); + if (assignFrom == NULL) + elog(ERROR, "Array assignment requires type %s" + " but expression is of type %s" + "\n\tYou will need to rewrite or cast the expression", + format_type_be(typeneeded), + format_type_be(typesource)); } } @@ -344,7 +339,7 @@ transformArraySubscripts(ParseState *pstate, */ aref = makeNode(ArrayRef); aref->refrestype = resultType; /* XXX should save element type - * too */ + * OID too */ aref->refattrlength = type_struct_array->typlen; aref->refelemlength = type_struct_element->typlen; aref->refelembyval = type_struct_element->typbyval; @@ -373,21 +368,16 @@ transformArraySubscripts(ParseState *pstate, * resolution that we're not sure that it should be considered text. * Explicit "NULL" constants are also typed as UNKNOWN. * - * For integers and floats we produce int4, float8, or numeric depending - * on the value of the number. XXX In some cases it would be nice to take - * context into account when determining the type to convert to, but in - * other cases we can't delay the type choice. One possibility is to invent - * a dummy type "UNKNOWNNUMERIC" that's treated similarly to UNKNOWN; - * that would allow us to do the right thing in examples like a simple - * INSERT INTO table (numericcolumn) VALUES (1.234), since we wouldn't - * have to resolve the unknown type until we knew the destination column - * type. On the other hand UNKNOWN has considerable problems of its own. - * We would not like "SELECT 1.2 + 3.4" to claim it can't choose a type. + * For integers and floats we produce int4, int8, or numeric depending + * on the value of the number. XXX This should include int2 as well, + * but additional cleanup is needed before we can do that; else cases + * like "WHERE int4var = 42" will fail to be indexable. */ Const * make_const(Value *value) { Datum val; + int64 val64; Oid typeid; int typelen; bool typebyval; @@ -404,12 +394,13 @@ make_const(Value *value) break; case T_Float: - if (fitsInFloat(value)) + /* could be an oversize integer as well as a float ... */ + if (scanint8(strVal(value), true, &val64)) { - val = Float8GetDatum(floatVal(value)); + val = Int64GetDatum(val64); - typeid = FLOAT8OID; - typelen = sizeof(float8); + typeid = INT8OID; + typelen = sizeof(int64); typebyval = false; /* XXX might change someday */ } else @@ -470,46 +461,3 @@ make_const(Value *value) return con; } - -/* - * Decide whether a T_Float value fits in float8, or must be treated as - * type "numeric". We check the number of digits and check for overflow/ - * underflow. (With standard compilation options, Postgres' NUMERIC type - * can handle decimal exponents up to 1000, considerably more than most - * implementations of float8, so this is a sensible test.) - */ -static bool -fitsInFloat(Value *value) -{ - const char *ptr; - int ndigits; - char *endptr; - - /* - * Count digits, ignoring leading zeroes (but not trailing zeroes). - * DBL_DIG is the maximum safe number of digits for "double". - */ - ptr = strVal(value); - while (*ptr == '+' || *ptr == '-' || *ptr == '0' || *ptr == '.') - ptr++; - ndigits = 0; - for (; *ptr; ptr++) - { - if (isdigit((unsigned char) *ptr)) - ndigits++; - else if (*ptr == 'e' || *ptr == 'E') - break; /* don't count digits in exponent */ - } - if (ndigits > DBL_DIG) - return false; - - /* - * Use strtod() to check for overflow/underflow. - */ - errno = 0; - (void) strtod(strVal(value), &endptr); - if (*endptr != '\0' || errno != 0) - return false; - - return true; -} diff --git a/src/backend/parser/parse_oper.c b/src/backend/parser/parse_oper.c index ecf1a2abec..776acc78bf 100644 --- a/src/backend/parser/parse_oper.c +++ b/src/backend/parser/parse_oper.c @@ -8,7 +8,7 @@ * * * IDENTIFICATION - * $Header: /cvsroot/pgsql/src/backend/parser/parse_oper.c,v 1.59 2002/09/04 20:31:24 momjian Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/parse_oper.c,v 1.60 2002/09/18 21:35:22 tgl Exp $ * *------------------------------------------------------------------------- */ @@ -273,7 +273,7 @@ oper_select_candidate(int nargs, current_candidate = current_candidate->next) { if (can_coerce_type(nargs, input_typeids, current_candidate->args, - false)) + COERCION_IMPLICIT)) { if (last_candidate == NULL) { @@ -362,7 +362,7 @@ oper_select_candidate(int nargs, { if (input_typeids[i] != UNKNOWNOID) { - if (IsBinaryCompatible(current_typeids[i], input_typeids[i])) + if (IsBinaryCoercible(input_typeids[i], current_typeids[i])) nmatch++; } } @@ -696,8 +696,8 @@ compatible_oper(List *op, Oid arg1, Oid arg2, bool noError) /* but is it good enough? */ opform = (Form_pg_operator) GETSTRUCT(optup); - if (IsBinaryCompatible(opform->oprleft, arg1) && - IsBinaryCompatible(opform->oprright, arg2)) + if (IsBinaryCoercible(arg1, opform->oprleft) && + IsBinaryCoercible(arg2, opform->oprright)) return optup; /* nope... */ diff --git a/src/backend/parser/parse_target.c b/src/backend/parser/parse_target.c index b9c5b6cb13..18d11cc7f5 100644 --- a/src/backend/parser/parse_target.c +++ b/src/backend/parser/parse_target.c @@ -8,7 +8,7 @@ * * * IDENTIFICATION - * $Header: /cvsroot/pgsql/src/backend/parser/parse_target.c,v 1.89 2002/09/04 20:31:24 momjian Exp $ + * $Header: /cvsroot/pgsql/src/backend/parser/parse_target.c,v 1.90 2002/09/18 21:35:22 tgl Exp $ * *------------------------------------------------------------------------- */ @@ -274,6 +274,7 @@ updateTargetListEntry(ParseState *pstate, aref = transformArraySubscripts(pstate, arrayBase, attrtype, + attrtypmod, indirection, pstate->p_is_insert, tle->expr); @@ -284,30 +285,21 @@ updateTargetListEntry(ParseState *pstate, /* * For normal non-subscripted target column, do type checking and * coercion. But accept InvalidOid, which indicates the source is - * a NULL constant. + * a NULL constant. (XXX is that still true?) */ if (type_id != InvalidOid) { - if (type_id != attrtype) - { - tle->expr = CoerceTargetExpr(pstate, tle->expr, type_id, - attrtype, attrtypmod, - false); - if (tle->expr == NULL) - elog(ERROR, "column \"%s\" is of type '%s'" - " but expression is of type '%s'" - "\n\tYou will need to rewrite or cast the expression", - colname, - format_type_be(attrtype), - format_type_be(type_id)); - } - - /* - * If the target is a fixed-length type, it may need a length - * coercion as well as a type coercion. - */ - tle->expr = coerce_type_typmod(pstate, tle->expr, - attrtype, attrtypmod); + tle->expr = coerce_to_target_type(tle->expr, type_id, + attrtype, attrtypmod, + COERCION_ASSIGNMENT, + COERCE_IMPLICIT_CAST); + if (tle->expr == NULL) + elog(ERROR, "column \"%s\" is of type %s" + " but expression is of type %s" + "\n\tYou will need to rewrite or cast the expression", + colname, + format_type_be(attrtype), + format_type_be(type_id)); } } @@ -324,46 +316,6 @@ updateTargetListEntry(ParseState *pstate, } -Node * -CoerceTargetExpr(ParseState *pstate, - Node *expr, - Oid type_id, - Oid attrtype, - int32 attrtypmod, - bool isExplicit) -{ - if (can_coerce_type(1, &type_id, &attrtype, isExplicit)) - expr = coerce_type(pstate, expr, type_id, attrtype, attrtypmod, - isExplicit); - -#ifndef DISABLE_STRING_HACKS - - /* - * string hacks to get transparent conversions w/o explicit - * conversions - */ - else if ((attrtype == BPCHAROID) || (attrtype == VARCHAROID)) - { - Oid text_id = TEXTOID; - - if (type_id == TEXTOID) - { - } - else if (can_coerce_type(1, &type_id, &text_id, isExplicit)) - expr = coerce_type(pstate, expr, type_id, text_id, attrtypmod, - isExplicit); - else - expr = NULL; - } -#endif - - else - expr = NULL; - - return expr; -} - - /* * checkInsertTargets - * generate a list of INSERT column targets if not supplied, or |
