Skip to content

Commit

Permalink
refactor: clarify Scalar type
Browse files Browse the repository at this point in the history
It now contains the type of the scalar. This way we can discriminate the
void type in a more obvious way.
  • Loading branch information
steve-chavez committed Apr 13, 2023
1 parent feadf59 commit ce378e6
Show file tree
Hide file tree
Showing 3 changed files with 9 additions and 12 deletions.
2 changes: 1 addition & 1 deletion src/PostgREST/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -283,7 +283,7 @@ noRelBetweenHint parent child schema allRels = ("Perhaps you meant '" <>) <$>
-- to all the overloaded functions' params using the form "param1, param2, param3, ..."
-- and shows the best match as hint.
--
-- >>> let procsDesc = [Routine {pdParams = [RoutineParam {ppName="val"}, RoutineParam {ppName="param"}, RoutineParam {ppName="name"}]}, Routine {pdParams = [RoutineParam {ppName="id"}, RoutineParam {ppName="attr"}]}]
-- >>> let procsDesc = [Function {pdParams = [RoutineParam {ppName="val"}, RoutineParam {ppName="param"}, RoutineParam {ppName="name"}]}, Function {pdParams = [RoutineParam {ppName="id"}, RoutineParam {ppName="attr"}]}]
--
-- >>> noRpcHint "api" "test" ["vall", "pqaram", "nam"] procs procsDesc
-- Just "Perhaps you meant to call the function api.test(name, param, val)"
Expand Down
9 changes: 3 additions & 6 deletions src/PostgREST/SchemaCache.hs
Original file line number Diff line number Diff line change
Expand Up @@ -247,24 +247,22 @@ decodeFuncs =
<*> column HD.text
<*> column HD.bool
<*> column HD.bool
<*> column HD.bool
<*> column HD.bool)
<*> (parseVolatility <$> column HD.char)
<*> column HD.bool

addKey :: Routine -> (QualifiedIdentifier, Routine)
addKey pd = (QualifiedIdentifier (pdSchema pd) (pdName pd), pd)

parseRetType :: Text -> Text -> Bool -> Bool -> Bool -> Bool -> RetType
parseRetType schema name isSetOf isComposite isVoid isCompositeAlias
| isVoid = Single $ Scalar True
parseRetType :: Text -> Text -> Bool -> Bool -> Bool -> RetType
parseRetType schema name isSetOf isComposite isCompositeAlias
| isSetOf = SetOf pgType
| otherwise = Single pgType
where
qi = QualifiedIdentifier schema name
pgType
| isComposite = Composite qi isCompositeAlias
| otherwise = Scalar False
| otherwise = Scalar qi

parseVolatility :: Char -> FuncVolatility
parseVolatility v | v == 'i' = Immutable
Expand Down Expand Up @@ -339,7 +337,6 @@ funcsSqlQuery pgVer = [q|
-- if any TABLE, INOUT or OUT arguments present, treat as composite
or COALESCE(proargmodes::text[] && '{t,b,o}', false)
) AS rettype_is_composite,
('void'::regtype = t.oid) AS rettype_is_void,
bt.oid <> bt.base as rettype_is_composite_alias,
p.provolatile,
p.provariadic > 0 as hasvariadic
Expand Down
10 changes: 5 additions & 5 deletions src/PostgREST/SchemaCache/Routine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import PostgREST.SchemaCache.Identifiers (QualifiedIdentifier (..),
import Protolude

data PgType
= Scalar Bool -- True if the type is void
= Scalar QualifiedIdentifier
| Composite QualifiedIdentifier Bool -- True if the composite is a domain alias(used to work around a bug in pg 11 and 12, see QueryBuilder.hs)
deriving (Eq, Ord, Generic, JSON.ToJSON)

Expand Down Expand Up @@ -72,12 +72,12 @@ type RoutineMap = HM.HashMap QualifiedIdentifier [Routine]

funcReturnsScalar :: Routine -> Bool
funcReturnsScalar proc = case proc of
Function{pdReturnType = Single (Scalar _)} -> True
Function{pdReturnType = Single (Scalar{})} -> True
_ -> False

funcReturnsSetOfScalar :: Routine -> Bool
funcReturnsSetOfScalar proc = case proc of
Function{pdReturnType = SetOf (Scalar _)} -> True
Function{pdReturnType = SetOf (Scalar{})} -> True
_ -> False

funcReturnsCompositeAlias :: Routine -> Bool
Expand All @@ -93,8 +93,8 @@ funcReturnsSingleComposite proc = case proc of

funcReturnsVoid :: Routine -> Bool
funcReturnsVoid proc = case proc of
Function{pdReturnType = Single (Scalar True)} -> True
_ -> False
Function{pdReturnType = Single (Scalar (QualifiedIdentifier "pg_catalog" "void"))} -> True
_ -> False

funcTableName :: Routine -> Maybe TableName
funcTableName proc = case pdReturnType proc of
Expand Down

0 comments on commit ce378e6

Please sign in to comment.