functions can access session info via input arg (close #2322) (#3143)

This commit is contained in:
Rakesh Emmadi 2019-11-20 12:17:06 +05:30 committed by Shahidh K Muhammed
parent 2d5cdab60f
commit 9b8e6b42d1
51 changed files with 798 additions and 214 deletions

View File

@ -37,6 +37,7 @@ query_collections: []
remote_schemas: []
tables:
- array_relationships: []
computed_fields: []
configuration:
custom_column_names: {}
custom_root_fields:
@ -88,12 +89,14 @@ tables:
select_permissions: []
table: test
update_permissions: []
version: 2
`),
"empty-metadata": []byte(`allowlist: []
functions: []
query_collections: []
remote_schemas: []
tables: []
version: 2
`),
}
@ -283,7 +286,7 @@ func mustWriteFile(t testing.TB, dir, file string, body string) {
func compareMetadata(t testing.TB, metadataFile string, actualType string, serverVersion *semver.Version) {
var actualData []byte
c, err := semver.NewConstraint("<= v1.0.0-beta.9")
c, err := semver.NewConstraint("<= v1.0.0-beta.10")
if err != nil {
t.Fatal(err)
}

View File

@ -16,13 +16,7 @@ track_function
--------------
``track_function`` is used to add a custom SQL function to the GraphQL schema.
Currently, only functions which satisfy the following constraints can be exposed over the GraphQL API
(*terminology from* `Postgres docs <https://www.postgresql.org/docs/current/sql-createfunction.html>`__):
- **Function behaviour**: ONLY ``STABLE`` or ``IMMUTABLE``
- **Return type**: MUST be ``SETOF <table-name>``
- **Argument modes**: ONLY ``IN``
Also refer a note :ref:`here <note>`.
Add an SQL function ``search_articles``:
@ -40,6 +34,85 @@ Add an SQL function ``search_articles``:
}
}
.. _track_function_v2:
track_function v2
-----------------
Version 2 of ``track_function`` is used to add a custom SQL function to the GraphQL schema with configuration.
Also refer a note :ref:`here <note>`.
Add an SQL function called ``search_articles`` with a Hasura session argument.
.. code-block:: http
POST /v1/query HTTP/1.1
Content-Type: application/json
X-Hasura-Role: admin
{
"type": "track_function",
"version": 2,
"args": {
"function": {
"schema": "public",
"name": "search_articles"
},
"configuration": {
"session_argument": "hasura_session"
}
}
}
.. _track_function_args_syntax_v2:
Args syntax
^^^^^^^^^^^
.. list-table::
:header-rows: 1
* - Key
- Required
- Schema
- Description
* - function
- true
- :ref:`FunctionName <FunctionName>`
- Name of the SQL function
* - configuration
- false
- :ref:`Function Configuration <function_configuration>`
- Configuration for the SQL function
.. _function_configuration:
Function Configuration
^^^^^^^^^^^^^^^^^^^^^^
.. list-table::
:header-rows: 1
* - Key
- Required
- Schema
- Description
* - session_argument
- false
- `String`
- Function argument which accepts session info JSON
.. _note:
.. note::
Currently, only functions which satisfy the following constraints can be exposed over the GraphQL API
(*terminology from* `Postgres docs <https://www.postgresql.org/docs/current/sql-createfunction.html>`__):
- **Function behaviour**: ONLY ``STABLE`` or ``IMMUTABLE``
- **Return type**: MUST be ``SETOF <table-name>``
- **Argument modes**: ONLY ``IN``
.. _untrack_function:
untrack_function

View File

@ -112,6 +112,11 @@ The various types of queries are listed in the following table:
- 1
- Add an SQL function
* - :ref:`track_function`
- :ref:`track_function_args <track_function_args_syntax_v2>`
- 2
- Add an SQL function with configuration
* - :ref:`untrack_function`
- :ref:`FunctionName <FunctionName>`
- 1

View File

@ -395,6 +395,51 @@ Search nearby landmarks with ``distance_kms`` default value which is 2 kms:
}
Accessing Hasura session variables in custom functions
******************************************************
Use the v2 :ref:`track_function <track_function_v2>` to add a function by defining a session argument.
The session argument will be a JSON object where keys are session variable names (in lower case) and values are strings.
Use the ``->>`` JSON operator to fetch the value of a session variable as shown in the following example.
.. code-block:: plpgsql
-- single text column table
CREATE TABLE text_result(
result text
);
-- simple function which returns the hasura role
-- where 'hasura_session' will be session argument
CREATE FUNCTION get_session_role(hasura_session json)
RETURNS SETOF text_result AS $$
SELECT q.* FROM (VALUES (hasura_session ->> 'x-hasura-role')) q
$$ LANGUAGE sql STABLE;
.. graphiql::
:view_only:
:query:
query {
get_session_role {
result
}
}
:response:
{
"data": {
"get_session_role": [
{
"result": "admin"
}
]
}
}
.. note::
The specified session argument will not be included in the ``<function-name>_args`` input object in the GraphQL schema.
Permissions for custom function queries
---------------------------------------

View File

@ -205,6 +205,7 @@ library
, Hasura.RQL.Types.SchemaCache
, Hasura.RQL.Types.SchemaCacheTypes
, Hasura.RQL.Types.BoolExp
, Hasura.RQL.Types.Function
, Hasura.RQL.Types.Catalog
, Hasura.RQL.Types.Column
, Hasura.RQL.Types.Common

View File

@ -8,6 +8,7 @@ module Hasura.Db
, runLazyTx
, runLazyTx'
, withUserInfo
, sessionInfoJsonExp
, RespTx
, LazyRespTx
@ -29,6 +30,8 @@ import Hasura.RQL.Types.Permission
import Hasura.SQL.Error
import Hasura.SQL.Types
import qualified Hasura.SQL.DML as S
data PGExecCtx
= PGExecCtx
{ _pecPool :: !Q.PGPool
@ -88,8 +91,10 @@ setHeadersTx uVars =
Q.unitQE defaultTxErrorHandler setSess () False
where
setSess = Q.fromText $
"SET LOCAL \"hasura.user\" = " <>
pgFmtLit (J.encodeToStrictText uVars)
"SET LOCAL \"hasura.user\" = " <> toSQLTxt (sessionInfoJsonExp uVars)
sessionInfoJsonExp :: UserVars -> S.SQLExp
sessionInfoJsonExp = S.SELit . J.encodeToStrictText
defaultTxErrorHandler :: Q.PGTxErr -> QErr
defaultTxErrorHandler = mkTxErrorHandler (const False)

View File

@ -100,6 +100,7 @@ resolveMultiplexedValue = \case
pure $ fromResVars (PGTypeScalar $ pstType colVal) varJsonPath
GR.UVSessVar ty sessVar -> pure $ fromResVars ty ["session", T.toLower sessVar]
GR.UVSQL sqlExp -> pure sqlExp
GR.UVSession -> pure $ fromResVars (PGTypeScalar PGJSON) ["session"]
where
fromResVars ty jPath =
flip S.SETyAnn (S.mkTypeAnn ty) $ S.SEOpApp (S.SQLOp "#>>")

View File

@ -158,12 +158,15 @@ prepareWithPlan = \case
R.UVSessVar ty sessVar -> do
let sessVarVal =
S.SEOpApp (S.SQLOp "->>")
[S.SEPrep 1, S.SELit $ T.toLower sessVar]
[currentSession, S.SELit $ T.toLower sessVar]
return $ flip S.SETyAnn (S.mkTypeAnn ty) $ case ty of
PGTypeScalar colTy -> withConstructorFn colTy sessVarVal
PGTypeArray _ -> sessVarVal
R.UVSQL sqlExp -> return sqlExp
R.UVSQL sqlExp -> pure sqlExp
R.UVSession -> pure currentSession
where
currentSession = S.SEPrep 1
queryRootName :: Text
queryRootName = "query_root"

View File

@ -67,6 +67,7 @@ resolveVal userInfo = \case
PGTypeScalar colTy -> withConstructorFn colTy sessVarVal
PGTypeArray _ -> sessVarVal
RS.UVSQL sqlExp -> return sqlExp
RS.UVSession -> pure $ sessionInfoJsonExp $ userVars userInfo
getSessVarVal
:: (MonadError QErr m)

View File

@ -23,7 +23,8 @@ import qualified Language.GraphQL.Draft.Syntax as G
import Hasura.GraphQL.Resolve.Context
import Hasura.Prelude
import Hasura.RQL.DML.Internal (sessVarFromCurrentSetting)
import Hasura.RQL.DML.Internal (currentSession,
sessVarFromCurrentSetting)
import Hasura.RQL.Types
import Hasura.SQL.Types
@ -82,6 +83,7 @@ queryFldToSQL fn fld = do
UVPG annPGVal -> fn annPGVal
UVSQL sqlExp -> return sqlExp
UVSessVar colTy sessVar -> sessVarFromCurrentSetting colTy sessVar
UVSession -> pure currentSession
return $ RS.toPGQuery resolvedAST
mutFldToTx

View File

@ -1,5 +1,5 @@
module Hasura.GraphQL.Resolve.Context
( FuncArgItem(..)
( FunctionArgItem(..)
, OrdByItem(..)
, UpdPermForIns(..)
, InsCtx(..)
@ -43,7 +43,8 @@ import Hasura.GraphQL.Resolve.Types
import Hasura.GraphQL.Utils
import Hasura.GraphQL.Validate.Field
import Hasura.GraphQL.Validate.Types
import Hasura.RQL.DML.Internal (sessVarFromCurrentSetting)
import Hasura.RQL.DML.Internal (currentSession,
sessVarFromCurrentSetting)
import Hasura.RQL.Types
import Hasura.SQL.Types
import Hasura.SQL.Value
@ -125,13 +126,15 @@ resolveValPrep
resolveValPrep = \case
UVPG annPGVal -> prepare annPGVal
UVSessVar colTy sessVar -> sessVarFromCurrentSetting colTy sessVar
UVSQL sqlExp -> return sqlExp
UVSQL sqlExp -> pure sqlExp
UVSession -> pure currentSession
resolveValTxt :: (Applicative f) => UnresolvedVal -> f S.SQLExp
resolveValTxt = \case
UVPG annPGVal -> txtConverter annPGVal
UVSessVar colTy sessVar -> sessVarFromCurrentSetting colTy sessVar
UVSQL sqlExp -> pure sqlExp
UVSession -> pure currentSession
withPrepArgs :: StateT PrepArgs m a -> m (a, PrepArgs)
withPrepArgs m = runStateT m Seq.empty

View File

@ -43,14 +43,15 @@ convertMutResp ty selSet =
"returning" -> do
annFlds <- fromSelSet (_fType fld) $ _fSelSet fld
annFldsResolved <- traverse
(traverse (RS.traverseAnnFld convertUnresolvedVal)) annFlds
(traverse (RS.traverseAnnFld convertPGValueToTextValue)) annFlds
return $ RR.MRet annFldsResolved
G.Name t -> throw500 $ "unexpected field in mutation resp : " <> t
where
convertUnresolvedVal = \case
convertPGValueToTextValue = \case
UVPG annPGVal -> UVSQL <$> txtConverter annPGVal
UVSessVar colTy sessVar -> pure $ UVSessVar colTy sessVar
UVSQL sqlExp -> pure $ UVSQL sqlExp
UVSession -> pure UVSession
convertRowObj
:: (MonadReusability m, MonadError QErr m)

View File

@ -20,6 +20,7 @@ import Hasura.Prelude
import qualified Data.HashMap.Strict as Map
import qualified Data.HashMap.Strict.InsOrd as OMap
import qualified Data.List.NonEmpty as NE
import qualified Data.Sequence as Seq
import qualified Data.Text as T
import qualified Language.GraphQL.Draft.Syntax as G
@ -61,7 +62,7 @@ resolveComputedField
)
=> ComputedField -> Field -> m (RS.ComputedFieldSel UnresolvedVal)
resolveComputedField computedField fld = fieldAsPath fld $ do
funcArgsM <- withArgM (_fArguments fld) "args" $ parseFunctionArgs argSeq
funcArgsM <- withArgM (_fArguments fld) "args" $ parseFunctionArgs argSeq argFn
let funcArgs = fromMaybe RS.emptyFunctionArgsExp funcArgsM
argsWithTableArgument = withTableArgument funcArgs
case fieldType of
@ -75,6 +76,7 @@ resolveComputedField computedField fld = fieldAsPath fld $ do
where
ComputedField _ function argSeq fieldType = computedField
ComputedFieldFunction qf _ tableArg _ = function
argFn = IFAUnknown
withTableArgument resolvedArgs =
let argsExp@(RS.FunctionArgsExp positional named) = RS.AEInput <$> resolvedArgs
in case tableArg of
@ -452,39 +454,49 @@ convertAggSelect opCtx fld =
parseFunctionArgs
:: (MonadReusability m, MonadError QErr m)
=> FuncArgSeq
=> Seq.Seq a
-> (a -> InputFunctionArgument)
-> AnnInpVal
-> m (RS.FunctionArgsExpG UnresolvedVal)
parseFunctionArgs argSeq val = flip withObject val $ \_ obj -> do
parseFunctionArgs argSeq argFn val = flip withObject val $ \_ obj -> do
(positionalArgs, argsLeft) <- spanMaybeM (parsePositionalArg obj) argSeq
namedArgs <- Map.fromList . catMaybes <$> traverse (parseNamedArg obj) argsLeft
pure $ RS.FunctionArgsExp positionalArgs namedArgs
where
parsePositionalArg obj (FuncArgItem gqlName _ _) =
maybe (pure Nothing) (fmap Just . parseArg) $ OMap.lookup gqlName obj
parsePositionalArg obj inputArg = case argFn inputArg of
IFAKnown _ resolvedVal -> pure $ Just resolvedVal
IFAUnknown (FunctionArgItem gqlName _ _) ->
maybe (pure Nothing) (fmap Just . parseArg) $ OMap.lookup gqlName obj
parseArg = fmap (maybe (UVSQL S.SENull) mkParameterizablePGValue) . asPGColumnValueM
parseNamedArg obj (FuncArgItem gqlName maybeSqlName hasDefault) =
case OMap.lookup gqlName obj of
Just argInpVal -> case maybeSqlName of
Just sqlName -> Just . (getFuncArgNameTxt sqlName,) <$> parseArg argInpVal
Nothing -> throw400 NotSupported
"Only last set of positional arguments can be omitted"
Nothing -> if not hasDefault then
throw400 NotSupported "Non default arguments cannot be omitted"
else pure Nothing
parseNamedArg obj inputArg = case argFn inputArg of
IFAKnown argName resolvedVal ->
pure $ Just (getFuncArgNameTxt argName, resolvedVal)
IFAUnknown (FunctionArgItem gqlName maybeSqlName hasDefault) ->
case OMap.lookup gqlName obj of
Just argInpVal -> case maybeSqlName of
Just sqlName -> Just . (getFuncArgNameTxt sqlName,) <$> parseArg argInpVal
Nothing -> throw400 NotSupported
"Only last set of positional arguments can be omitted"
Nothing -> if not (unHasDefault hasDefault) then
throw400 NotSupported "Non default arguments cannot be omitted"
else pure Nothing
fromFuncQueryField
:: (MonadReusability m, MonadError QErr m)
=> (Field -> m s)
-> QualifiedFunction -> FuncArgSeq
-> QualifiedFunction
-> FunctionArgSeq
-> Field
-> m (RS.AnnFnSelG s UnresolvedVal)
fromFuncQueryField fn qf argSeq fld = fieldAsPath fld $ do
funcArgsM <- withArgM (_fArguments fld) "args" $ parseFunctionArgs argSeq
funcArgsM <- withArgM (_fArguments fld) "args" $ parseFunctionArgs argSeq argFn
let funcArgs = fromMaybe RS.emptyFunctionArgsExp funcArgsM
RS.AnnFnSel qf funcArgs <$> fn fld
where
argFn (IAUserProvided val) = IFAUnknown val
argFn (IASessionVariables argName) = IFAKnown argName UVSession
convertFuncQuerySimple
:: ( MonadReusability m
@ -496,8 +508,8 @@ convertFuncQuerySimple
)
=> FuncQOpCtx -> Field -> m QueryRootFldUnresolved
convertFuncQuerySimple funcOpCtx fld =
withPathK "selectionSet" $ QRFFnSimple <$>
fromFuncQueryField (fromField (RS.FromTable qt) colGNameMap permFilter permLimit) qf argSeq fld
withPathK "selectionSet" $ QRFFnSimple <$> fromFuncQueryField
(fromField (RS.FromTable qt) colGNameMap permFilter permLimit) qf argSeq fld
where
FuncQOpCtx qt _ colGNameMap permFilter permLimit qf argSeq = funcOpCtx
@ -511,8 +523,8 @@ convertFuncQueryAgg
)
=> FuncQOpCtx -> Field -> m QueryRootFldUnresolved
convertFuncQueryAgg funcOpCtx fld =
withPathK "selectionSet" $ QRFFnAgg <$>
fromFuncQueryField (fromAggField qt colGNameMap permFilter permLimit) qf argSeq fld
withPathK "selectionSet" $ QRFFnAgg <$> fromFuncQueryField
(fromAggField qt colGNameMap permFilter permLimit) qf argSeq fld
where
FuncQOpCtx qt _ colGNameMap permFilter permLimit qf argSeq = funcOpCtx

View File

@ -17,6 +17,7 @@ import Hasura.RQL.Types.BoolExp
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Function
import Hasura.RQL.Types.Permission
import Hasura.SQL.Types
import Hasura.SQL.Value
@ -64,6 +65,8 @@ data SelPkOpCtx
, _spocArgMap :: !PGColArgMap
} deriving (Show, Eq)
type FunctionArgSeq = Seq.Seq (InputArgument FunctionArgItem)
data FuncQOpCtx
= FuncQOpCtx
{ _fqocTable :: !QualifiedTable
@ -72,7 +75,7 @@ data FuncQOpCtx
, _fqocFilter :: !AnnBoolExpPartialSQL
, _fqocLimit :: !(Maybe Int)
, _fqocFunction :: !QualifiedFunction
, _fqocArgs :: !FuncArgSeq
, _fqocArgs :: !FunctionArgSeq
} deriving (Show, Eq)
data UpdOpCtx
@ -129,11 +132,13 @@ data ComputedFieldType
| CFTTable !ComputedFieldTable
deriving (Show, Eq)
type ComputedFieldFunctionArgSeq = Seq.Seq FunctionArgItem
data ComputedField
= ComputedField
{ _cfName :: !ComputedFieldName
, _cfFunction :: !ComputedFieldFunction
, _cfArgSeq :: !FuncArgSeq
, _cfArgSeq :: !ComputedFieldFunctionArgSeq
, _cfType :: !ComputedFieldType
} deriving (Show, Eq)
@ -156,15 +161,13 @@ type OrdByItemMap = Map.HashMap G.Name OrdByItem
type OrdByCtx = Map.HashMap G.NamedType OrdByItemMap
data FuncArgItem
= FuncArgItem
data FunctionArgItem
= FunctionArgItem
{ _faiInputArgName :: !G.Name
, _faiSqlArgName :: !(Maybe FunctionArgName)
, _faiHasDefault :: !Bool
, _faiHasDefault :: !HasDefault
} deriving (Show, Eq)
type FuncArgSeq = Seq.Seq FuncArgItem
-- insert context
type RelationInfoMap = Map.HashMap RelName RelInfo
@ -205,7 +208,9 @@ partialSQLExpToUnresolvedVal = \case
-- | A value that will be converted to an sql expression eventually
data UnresolvedVal
= UVSessVar !(PGType PGScalarType) !SessVar
-- | an entire session variables JSON object
= UVSession
| UVSessVar !(PGType PGScalarType) !SessVar
-- | a SQL value literal that can be parameterized over
| UVPG !AnnPGVal
-- | an arbitrary SQL expression, which /cannot/ be parameterized over
@ -216,3 +221,8 @@ type AnnBoolExpUnresolved = AnnBoolExp UnresolvedVal
-- template haskell related
$(makePrisms ''ResolveField)
data InputFunctionArgument
= IFAKnown !FunctionArgName !UnresolvedVal -- ^ Known value
| IFAUnknown !FunctionArgItem -- ^ Unknown value, need to be parsed
deriving (Show, Eq)

View File

@ -110,10 +110,10 @@ compAggOps = ["max", "min"]
isAggFld :: G.Name -> Bool
isAggFld = flip elem (numAggOps <> compAggOps)
mkFuncArgSeq :: Seq.Seq FunctionArg -> Seq.Seq FuncArgItem
mkFuncArgSeq inputArgs =
Seq.fromList $ procFuncArgs inputArgs $
\fa t -> FuncArgItem (G.Name t) (faName fa) (faHasDefault fa)
mkComputedFieldFunctionArgSeq :: Seq.Seq FunctionArg -> ComputedFieldFunctionArgSeq
mkComputedFieldFunctionArgSeq inputArgs =
Seq.fromList $ procFuncArgs inputArgs faName $
\fa t -> FunctionArgItem (G.Name t) (faName fa) (faHasDefault fa)
mkGCtxRole'
:: QualifiedTable
@ -213,9 +213,9 @@ mkGCtxRole' tn descM insPermM selPermM updColsM delPermM pkeyCols constraints vi
-- funcargs input type
funcArgInpObjs = flip mapMaybe funcs $ \func ->
mkFuncArgsInp (fiName func) (fiInputArgs func)
mkFuncArgsInp (fiName func) (getInputArgs func)
-- funcArgCtx = Map.unions funcArgCtxs
funcArgScalarSet = funcs ^.. folded.to fiInputArgs.folded.to (_qptName.faType)
funcArgScalarSet = funcs ^.. folded.to getInputArgs.folded.to (_qptName.faType)
-- helper
mkFldMap ty = Map.fromList . concatMap (mkFld ty)
@ -414,11 +414,20 @@ getRootFldsRole' tn primCols constraints fields funcs insM
funcFldHelper f g pFltr pLimit hdrs =
flip map funcs $ \fi ->
( f . FuncQOpCtx tn hdrs colGNameMap pFltr pLimit (fiName fi) $ mkFuncArgItemSeq fi
( f $ FuncQOpCtx tn hdrs colGNameMap pFltr pLimit
(fiName fi) (mkFuncArgItemSeq fi)
, g fi $ fiDescription fi
)
mkFuncArgItemSeq = mkFuncArgSeq . fiInputArgs
mkFuncArgItemSeq functionInfo =
let inputArgs = fiInputArgs functionInfo
in Seq.fromList $ procFuncArgs inputArgs nameFn resultFn
where
nameFn = \case
IAUserProvided fa -> faName fa
IASessionVariables name -> Just name
resultFn arg gName = flip fmap arg $
\fa -> FunctionArgItem (G.Name gName) (faName fa) (faHasDefault fa)
getSelPermission :: TableInfo PGColumnInfo -> RoleName -> Maybe SelPermInfo
@ -453,7 +462,7 @@ getSelPerm tableCache fields role selPermInfo = do
computedSelFields <- fmap catMaybes $ forM computedFields $ \info -> do
let ComputedFieldInfo name function returnTy _ = info
inputArgSeq = mkFuncArgSeq $ _cffInputArgs function
inputArgSeq = mkComputedFieldFunctionArgSeq $ _cffInputArgs function
fmap (SFComputedField . ComputedField name function inputArgSeq) <$>
case returnTy of
CFRScalar scalarTy -> pure $ Just $ CFTScalar scalarTy
@ -566,7 +575,7 @@ mkAdminSelFlds fields tableCache = do
computedSelFields <- forM computedFields $ \info -> do
let ComputedFieldInfo name function returnTy _ = info
inputArgSeq = mkFuncArgSeq $ _cffInputArgs function
inputArgSeq = mkComputedFieldFunctionArgSeq $ _cffInputArgs function
(SFComputedField . ComputedField name function inputArgSeq) <$>
case returnTy of
CFRScalar scalarTy -> pure $ CFTScalar scalarTy

View File

@ -26,20 +26,18 @@ input function_args {
}
-}
procFuncArgs
:: Seq.Seq FunctionArg
-> (FunctionArg -> Text -> a) -> [a]
procFuncArgs argSeq f =
procFuncArgs :: Seq.Seq a -> (a -> Maybe FunctionArgName) -> (a -> Text -> b) -> [b]
procFuncArgs argSeq nameFn resultFn =
fst $ foldl mkItem ([], 1::Int) argSeq
where
mkItem (items, argNo) fa =
case faName fa of
case nameFn fa of
Just argName ->
let argT = getFuncArgNameTxt argName
in (items <> pure (f fa argT), argNo)
in (items <> pure (resultFn fa argT), argNo)
Nothing ->
let argT = "arg_" <> T.pack (show argNo)
in (items <> pure (f fa argT), argNo + 1)
in (items <> pure (resultFn fa argT), argNo + 1)
mkFuncArgsInp :: QualifiedFunction -> Seq.Seq FunctionArg -> Maybe InpObjTyInfo
mkFuncArgsInp funcName funcArgs =
@ -50,7 +48,7 @@ mkFuncArgsInp funcName funcArgs =
inpObj = mkHsraInpTyInfo Nothing funcArgsTy $
fromInpValL argInps
argInps = procFuncArgs funcArgs mkInpVal
argInps = procFuncArgs funcArgs faName mkInpVal
mkInpVal fa t =
InpValInfo Nothing (G.Name t) Nothing $
@ -72,7 +70,7 @@ mkFuncArgs funInfo =
fromInpValL $ funcInpArgs <> mkSelArgs retTable
where
funcName = fiName funInfo
funcArgs = fiInputArgs funInfo
funcArgs = getInputArgs funInfo
retTable = fiReturnType funInfo
funcArgDesc = G.Description $ "input parameters for function " <>> funcName

View File

@ -21,6 +21,7 @@ import Hasura.RQL.DDL.Schema.Function (RawFunctionInfo (..),
fetchRawFunctioInfo,
mkFunctionArgs)
import Hasura.RQL.Types
import Hasura.Server.Utils (makeReasonMessage)
import Hasura.SQL.Types
import Data.Aeson
@ -30,7 +31,6 @@ import Language.Haskell.TH.Syntax (Lift)
import qualified Control.Monad.Validate as MV
import qualified Data.Sequence as Seq
import qualified Data.Text as T
import qualified Database.PG.Query as Q
import qualified Language.GraphQL.Draft.Syntax as G
@ -208,12 +208,9 @@ addComputedFieldP2Setup table computedField definition rawFunctionInfo comment =
showErrors :: [ComputedFieldValidateError] -> Text
showErrors allErrors =
"the computed field " <> computedField <<> " cannot be added to table "
<> table <<> reasonMessage
<> table <<> " " <> reasonMessage
where
reasonMessage = case allErrors of
[singleError] -> " because " <> showError function singleError
_ -> " for the following reasons: \n" <> T.unlines
(map (("" <>) . showError function) allErrors)
reasonMessage = makeReasonMessage allErrors (showError function)
dropTableArgument :: FunctionTableArgument -> [FunctionArg] -> [FunctionArg]
dropTableArgument tableArg inputArgs =

View File

@ -1,3 +1,4 @@
{-# LANGUAGE TypeApplications #-}
module Hasura.RQL.DDL.Metadata
( TableMeta
@ -55,6 +56,23 @@ import qualified Hasura.RQL.DDL.QueryCollection as Collection
import qualified Hasura.RQL.DDL.Relationship as Relationship
import qualified Hasura.RQL.DDL.Schema as Schema
data MetadataVersion
= MVVersion1
| MVVersion2
deriving (Show, Eq, Lift)
instance ToJSON MetadataVersion where
toJSON MVVersion1 = toJSON @Int 1
toJSON MVVersion2 = toJSON @Int 2
instance FromJSON MetadataVersion where
parseJSON v = do
version :: Int <- parseJSON v
case version of
1 -> pure MVVersion1
2 -> pure MVVersion2
i -> fail $ "expected 1 or 2, encountered " ++ show i
data ComputedFieldMeta
= ComputedFieldMeta
{ _cfmName :: !ComputedFieldName
@ -129,6 +147,15 @@ instance FromJSON TableMeta where
$(deriveToJSON (aesonDrop 3 snakeCase){omitNothingFields=True} ''TableMeta)
data FunctionsMetadata
= FMVersion1 ![QualifiedFunction]
| FMVersion2 ![Schema.TrackFunctionV2]
deriving (Show, Eq, Lift)
instance ToJSON FunctionsMetadata where
toJSON (FMVersion1 qualifiedFunctions) = toJSON qualifiedFunctions
toJSON (FMVersion2 functionsV2) = toJSON functionsV2
data ClearMetadata
= ClearMetadata
deriving (Show, Eq, Lift)
@ -160,19 +187,34 @@ runClearMetadata _ = do
data ReplaceMetadata
= ReplaceMetadata
{ aqTables :: ![TableMeta]
, aqFunctions :: !(Maybe [QualifiedFunction])
{ aqVersion :: !MetadataVersion
, aqTables :: ![TableMeta]
, aqFunctions :: !(Maybe FunctionsMetadata)
, aqRemoteSchemas :: !(Maybe [AddRemoteSchemaQuery])
, aqQueryCollections :: !(Maybe [Collection.CreateCollection])
, aqAllowlist :: !(Maybe [Collection.CollectionReq])
} deriving (Show, Eq, Lift)
$(deriveJSON (aesonDrop 2 snakeCase){omitNothingFields=True} ''ReplaceMetadata)
$(deriveToJSON (aesonDrop 2 snakeCase){omitNothingFields=True} ''ReplaceMetadata)
instance FromJSON ReplaceMetadata where
parseJSON = withObject "Object" $ \o -> do
version <- o .:? "version" .!= MVVersion1
ReplaceMetadata version
<$> o .: "tables"
<*> (o .:? "functions" >>= mapM (parseFunctions version))
<*> o .:? "remote_schemas"
<*> o .:? "query_collections"
<*> o .:? "allow_list"
where
parseFunctions = \case
MVVersion1 -> fmap FMVersion1 . parseJSON
MVVersion2 -> fmap FMVersion2 . parseJSON
applyQP1
:: (QErrM m, UserInfoM m)
=> ReplaceMetadata -> m ()
applyQP1 (ReplaceMetadata tables mFunctions mSchemas mCollections mAllowlist) = do
applyQP1 (ReplaceMetadata _ tables mFunctionsMeta mSchemas mCollections mAllowlist) = do
adminOnly
@ -201,7 +243,12 @@ applyQP1 (ReplaceMetadata tables mFunctions mSchemas mCollections mAllowlist) =
checkMultipleDecls "computed fields" computedFields
withPathK "functions" $
checkMultipleDecls "functions" functions
case mFunctionsMeta of
Nothing -> pure ()
Just (FMVersion1 qualifiedFunctions) ->
checkMultipleDecls "functions" qualifiedFunctions
Just (FMVersion2 functionsV2) ->
checkMultipleDecls "functions" $ map Schema._tfv2Function functionsV2
onJust mSchemas $ \schemas ->
withPathK "remote_schemas" $
@ -217,7 +264,6 @@ applyQP1 (ReplaceMetadata tables mFunctions mSchemas mCollections mAllowlist) =
where
withTableName qt = withPathK (qualObjectToText qt)
functions = fromMaybe [] mFunctions
checkMultipleDecls t l = do
let dups = getDups l
@ -239,7 +285,7 @@ applyQP2
)
=> ReplaceMetadata
-> m EncJSON
applyQP2 (ReplaceMetadata tables mFunctions mSchemas mCollections mAllowlist) = do
applyQP2 (ReplaceMetadata _ tables mFunctionsMeta mSchemas mCollections mAllowlist) = do
liftTx clearMetadata
Schema.buildSchemaCacheStrict
@ -287,18 +333,20 @@ applyQP2 (ReplaceMetadata tables mFunctions mSchemas mCollections mAllowlist) =
subTableP2 (table ^. tmTable) False etc
-- sql functions
withPathK "functions" $
indexedMapM_ (void . Schema.trackFunctionP2) functions
withPathK "functions" $ forM_ mFunctionsMeta $ \case
FMVersion1 qualifiedFunctions -> indexedForM_ qualifiedFunctions $
\qf -> void $ Schema.trackFunctionP2 qf Schema.emptyFunctionConfig
FMVersion2 functionsV2 -> indexedForM_ functionsV2 $
\(Schema.TrackFunctionV2 function config) -> void $ Schema.trackFunctionP2 function config
-- query collections
withPathK "query_collections" $
indexedForM_ collections $ \c ->
liftTx $ Collection.addCollectionToCatalog c systemDefined
indexedForM_ collections $ \c -> liftTx $ Collection.addCollectionToCatalog c systemDefined
-- allow list
withPathK "allowlist" $ do
indexedForM_ allowlist $ \(Collection.CollectionReq name) ->
liftTx $ Collection.addCollectionToAllowlistCatalog name
indexedForM_ allowlist $
\(Collection.CollectionReq name) -> liftTx $ Collection.addCollectionToAllowlistCatalog name
-- add to cache
Collection.refreshAllowlist
@ -313,7 +361,6 @@ applyQP2 (ReplaceMetadata tables mFunctions mSchemas mCollections mAllowlist) =
return successMsg
where
functions = fromMaybe [] mFunctions
collections = fromMaybe [] mCollections
allowlist = fromMaybe [] mAllowlist
processPerms tabInfo perms =
@ -382,8 +429,7 @@ fetchMetadata = do
modMetaMap tmComputedFields computedFields
-- fetch all functions
functions <- map (uncurry QualifiedObject) <$>
Q.catchE defaultTxErrorHandler fetchFunctions
functions <- FMVersion2 <$> Q.catchE defaultTxErrorHandler fetchFunctions
-- fetch all custom resolvers
remoteSchemas <- fetchRemoteSchemas
@ -394,7 +440,7 @@ fetchMetadata = do
-- fetch allow list
allowlist <- map Collection.CollectionReq <$> fetchAllowlists
return $ ReplaceMetadata (HMIns.elems postRelMap) (Just functions)
return $ ReplaceMetadata MVVersion2 (HMIns.elems postRelMap) (Just functions)
(Just remoteSchemas) (Just collections) (Just allowlist)
where
@ -452,13 +498,15 @@ fetchMetadata = do
ORDER BY e.schema_name ASC, e.table_name ASC, e.name ASC
|] () False
fetchFunctions =
Q.listQ [Q.sql|
SELECT function_schema, function_name
fetchFunctions = do
l <- Q.listQ [Q.sql|
SELECT function_schema, function_name, configuration::json
FROM hdb_catalog.hdb_function
WHERE is_system_defined = 'false'
ORDER BY function_schema ASC, function_name ASC
|] () False
pure $ flip map l $ \(sn, fn, Q.AltJ config) ->
Schema.TrackFunctionV2 (QualifiedObject sn fn) config
fetchCollections =
map fromRow <$> Q.listQE defaultTxErrorHandler [Q.sql|

View File

@ -135,14 +135,14 @@ buildSchemaCacheWithOptions withSetup = do
mkAllTriggersQ trn qt allCols (stringifyNum sqlGenCtx) (etcDefinition etc)
-- sql functions
forM_ functions $ \(CatalogFunction qf systemDefined funcDefs) -> do
forM_ functions $ \(CatalogFunction qf systemDefined config funcDefs) -> do
let def = toJSON $ TrackFunction qf
mkInconsObj =
InconsistentMetadataObj (MOFunction qf) MOTFunction def
modifyErr (\e -> "function " <> qf <<> "; " <> e) $
withSchemaObject_ mkInconsObj $ do
rawfi <- handleMultipleFunctions qf funcDefs
trackFunctionP2Setup qf systemDefined rawfi
trackFunctionP2Setup qf systemDefined config rawfi
-- allow list
replaceAllowlist $ concatMap _cdQueries allowlistDefs

View File

@ -27,6 +27,7 @@ import qualified Language.GraphQL.Draft.Syntax as G
import Hasura.Db
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Error
import Hasura.Server.Utils (makeReasonMessage)
import Hasura.SQL.Types
import qualified Hasura.SQL.DML as S
@ -101,10 +102,7 @@ fetchAndValidateEnumValues tableName primaryKeyColumns columnInfos =
showErrors allErrors =
"the table " <> tableName <<> " cannot be used as an enum " <> reasonsMessage
where
reasonsMessage = case allErrors of
[singleError] -> "because " <> showOne singleError
_ -> "for the following reasons:\n" <> T.unlines
(map (("" <>) . showOne) allErrors)
reasonsMessage = makeReasonMessage allErrors showOne
showOne :: EnumTableIntegrityError -> T.Text
showOne = \case

View File

@ -8,6 +8,7 @@ import Hasura.EncJSON
import Hasura.GraphQL.Utils (showNames)
import Hasura.Prelude
import Hasura.RQL.Types
import Hasura.Server.Utils (makeReasonMessage)
import Hasura.SQL.Types
import Data.Aeson
@ -18,8 +19,10 @@ import Language.Haskell.TH.Syntax (Lift)
import qualified Hasura.GraphQL.Schema as GS
import qualified Language.GraphQL.Draft.Syntax as G
import qualified Control.Monad.Validate as MV
import qualified Data.HashMap.Strict as M
import qualified Data.Sequence as Seq
import qualified Data.Text as T
import qualified Database.PG.Query as Q
data RawFunctionInfo
@ -42,14 +45,13 @@ mkFunctionArgs :: Int -> [QualifiedPGType] -> [FunctionArgName] -> [FunctionArg]
mkFunctionArgs defArgsNo tys argNames =
bool withNames withNoNames $ null argNames
where
hasDefaultBoolSeq = replicate (length tys - defArgsNo) False
hasDefaultBoolSeq = replicate (length tys - defArgsNo) (HasDefault False)
-- only last arguments can have default expression
<> replicate defArgsNo True
<> replicate defArgsNo (HasDefault True)
tysWithHasDefault = zip tys hasDefaultBoolSeq
withNoNames = flip map tysWithHasDefault $
\(ty, hasDef) -> FunctionArg Nothing ty hasDef
withNoNames = flip map tysWithHasDefault $ uncurry $ FunctionArg Nothing
withNames = zipWith mkArg argNames tysWithHasDefault
mkArg "" (ty, hasDef) = FunctionArg Nothing ty hasDef
@ -64,38 +66,103 @@ validateFuncArgs args =
funcArgsText = mapMaybe (fmap getFuncArgNameTxt . faName) args
invalidArgs = filter (not . G.isValidName) $ map G.Name funcArgsText
data FunctionIntegrityError
= FunctionVariadic
| FunctionReturnNotCompositeType
| FunctionReturnNotSetof
| FunctionReturnNotSetofTable
| FunctionVolatile
| FunctionSessionArgumentNotJSON !FunctionArgName
| FunctionInvalidSessionArgument !FunctionArgName
| FunctionInvalidArgumentNames [FunctionArgName]
deriving (Show, Eq)
mkFunctionInfo
:: (QErrM m) => QualifiedFunction -> SystemDefined -> RawFunctionInfo -> m FunctionInfo
mkFunctionInfo qf systemDefined rawFuncInfo = do
-- throw error if function has variadic arguments
when hasVariadic $ throw400 NotSupported "function with \"VARIADIC\" parameters are not supported"
-- throw error if return type is not composite type
when (retTyType /= PGKindComposite) $ throw400 NotSupported "function does not return a \"COMPOSITE\" type"
-- throw error if function do not returns SETOF
unless retSet $ throw400 NotSupported "function does not return a SETOF"
-- throw error if return type is not a valid table
unless returnsTab $ throw400 NotSupported "function does not return a SETOF table"
-- throw error if function type is VOLATILE
when (funTy == FTVOLATILE) $ throw400 NotSupported "function of type \"VOLATILE\" is not supported now"
let funcArgs = mkFunctionArgs defArgsNo inpArgTyps inpArgNames
validateFuncArgs funcArgs
let funcArgsSeq = Seq.fromList funcArgs
dep = SchemaDependency (SOTable retTable) DRTable
retTable = typeToTable returnType
return $ FunctionInfo qf systemDefined funTy funcArgsSeq retTable [dep] descM
:: (QErrM m)
=> QualifiedFunction
-> SystemDefined
-> FunctionConfig
-> RawFunctionInfo
-> m (FunctionInfo, SchemaDependency)
mkFunctionInfo qf systemDefined config rawFuncInfo =
either (throw400 NotSupported . showErrors) pure
=<< MV.runValidateT validateFunction
where
RawFunctionInfo hasVariadic funTy rtSN retN retTyType retSet
functionArgs = mkFunctionArgs defArgsNo inpArgTyps inpArgNames
RawFunctionInfo hasVariadic funTy retSn retN retTyTyp retSet
inpArgTyps inpArgNames defArgsNo returnsTab descM
= rawFuncInfo
returnType = QualifiedPGType rtSN retN retTyType
returnType = QualifiedPGType retSn retN retTyTyp
saveFunctionToCatalog :: QualifiedFunction -> SystemDefined -> Q.TxE QErr ()
saveFunctionToCatalog (QualifiedObject sn fn) systemDefined =
throwValidateError = MV.dispute . pure
validateFunction = do
-- throw error if function has variadic arguments
when hasVariadic $ throwValidateError FunctionVariadic
-- throw error if return type is not composite type
when (retTyTyp /= PGKindComposite) $ throwValidateError FunctionReturnNotCompositeType
-- throw error if function do not returns SETOF
unless retSet $ throwValidateError FunctionReturnNotSetof
-- throw error if return type is not a valid table
unless returnsTab $ throwValidateError FunctionReturnNotSetofTable
-- throw error if function type is VOLATILE
when (funTy == FTVOLATILE) $ throwValidateError FunctionVolatile
-- validate function argument names
validateFunctionArgNames
inputArguments <- makeInputArguments
let retTable = typeToTable returnType
pure ( FunctionInfo qf systemDefined funTy inputArguments retTable descM
, SchemaDependency (SOTable retTable) DRTable
)
validateFunctionArgNames = do
let argNames = mapMaybe faName functionArgs
invalidArgs = filter (not . G.isValidName . G.Name . getFuncArgNameTxt) argNames
when (not $ null invalidArgs) $
throwValidateError $ FunctionInvalidArgumentNames invalidArgs
makeInputArguments =
case _fcSessionArgument config of
Nothing -> pure $ Seq.fromList $ map IAUserProvided functionArgs
Just sessionArgName -> do
when (not $ any (\arg -> (Just sessionArgName) == faName arg) functionArgs) $
throwValidateError $ FunctionInvalidSessionArgument sessionArgName
fmap Seq.fromList $ forM functionArgs $ \arg ->
if (Just sessionArgName) == faName arg then do
let argTy = _qptName $ faType arg
if argTy == PGJSON then pure $ IASessionVariables sessionArgName
else MV.refute $ pure $ FunctionSessionArgumentNotJSON sessionArgName
else pure $ IAUserProvided arg
showErrors allErrors =
"the function " <> qf <<> " cannot be tracked "
<> makeReasonMessage allErrors showOneError
showOneError = \case
FunctionVariadic -> "function with \"VARIADIC\" parameters are not supported"
FunctionReturnNotCompositeType -> "the function does not return a \"COMPOSITE\" type"
FunctionReturnNotSetof -> "the function does not return a SETOF"
FunctionReturnNotSetofTable -> "the function does not return a SETOF table"
FunctionVolatile -> "function of type \"VOLATILE\" is not supported now"
FunctionSessionArgumentNotJSON argName ->
"given session argument " <> argName <<> " is not of type json"
FunctionInvalidSessionArgument argName ->
"given session argument " <> argName <<> " not the input argument of the function"
FunctionInvalidArgumentNames args ->
let argsText = T.intercalate "," $ map getFuncArgNameTxt args
in "the function arguments " <> argsText <> " are not in compliance with GraphQL spec"
saveFunctionToCatalog :: QualifiedFunction -> FunctionConfig -> SystemDefined -> Q.TxE QErr ()
saveFunctionToCatalog (QualifiedObject sn fn) config systemDefined =
Q.unitQE defaultTxErrorHandler [Q.sql|
INSERT INTO "hdb_catalog"."hdb_function" VALUES ($1, $2, $3)
|] (sn, fn, systemDefined) False
INSERT INTO "hdb_catalog"."hdb_function"
(function_schema, function_name, configuration, is_system_defined)
VALUES ($1, $2, $3, $4)
|] (sn, fn, Q.AltJ config, systemDefined) False
delFunctionFromCatalog :: QualifiedFunction -> Q.TxE QErr ()
delFunctionFromCatalog (QualifiedObject sn fn) =
@ -110,12 +177,21 @@ newtype TrackFunction
{ tfName :: QualifiedFunction}
deriving (Show, Eq, FromJSON, ToJSON, Lift)
data FunctionConfig
= FunctionConfig
{ _fcSessionArgument :: !(Maybe FunctionArgName)
} deriving (Show, Eq, Lift)
$(deriveJSON (aesonDrop 3 snakeCase){omitNothingFields = True} ''FunctionConfig)
emptyFunctionConfig :: FunctionConfig
emptyFunctionConfig = FunctionConfig Nothing
-- | Track function, Phase 1:
-- Validate function tracking operation. Fails if function is already being
-- tracked, or if a table with the same name is being tracked.
trackFunctionP1
:: (CacheRM m, UserInfoM m, QErrM m) => TrackFunction -> m ()
trackFunctionP1 (TrackFunction qf) = do
:: (CacheRM m, UserInfoM m, QErrM m) => QualifiedFunction -> m ()
trackFunctionP1 qf = do
adminOnly
rawSchemaCache <- askSchemaCache
when (M.member qf $ scFunctions rawSchemaCache) $
@ -124,19 +200,20 @@ trackFunctionP1 (TrackFunction qf) = do
when (M.member qt $ scTables rawSchemaCache) $
throw400 NotSupported $ "table with name " <> qf <<> " already exists"
trackFunctionP2Setup :: (QErrM m, CacheRWM m, MonadTx m)
=> QualifiedFunction -> SystemDefined -> RawFunctionInfo -> m ()
trackFunctionP2Setup qf systemDefined rawfi = do
fi <- mkFunctionInfo qf systemDefined rawfi
trackFunctionP2Setup
:: (QErrM m, CacheRWM m, MonadTx m)
=> QualifiedFunction -> SystemDefined -> FunctionConfig -> RawFunctionInfo -> m ()
trackFunctionP2Setup qf systemDefined config rawfi = do
(fi, dep) <- mkFunctionInfo qf systemDefined config rawfi
let retTable = fiReturnType fi
err = err400 NotExists $ "table " <> retTable <<> " is not tracked"
sc <- askSchemaCache
void $ liftMaybe err $ M.lookup retTable $ scTables sc
addFunctionToCache fi
addFunctionToCache fi [dep]
trackFunctionP2 :: (QErrM m, CacheRWM m, HasSystemDefined m, MonadTx m)
=> QualifiedFunction -> m EncJSON
trackFunctionP2 qf = do
=> QualifiedFunction -> FunctionConfig -> m EncJSON
trackFunctionP2 qf config = do
sc <- askSchemaCache
let defGCtx = scDefaultRemoteGCtx sc
funcNameGQL = GS.qualObjectToName qf
@ -149,8 +226,8 @@ trackFunctionP2 qf = do
-- fetch function info
rawfi <- fetchRawFunctioInfo qf
systemDefined <- askSystemDefined
trackFunctionP2Setup qf systemDefined rawfi
liftTx $ saveFunctionToCatalog qf systemDefined
trackFunctionP2Setup qf systemDefined config rawfi
liftTx $ saveFunctionToCatalog qf config systemDefined
return successMsg
handleMultipleFunctions :: (QErrM m) => QualifiedFunction -> [a] -> m a
@ -163,7 +240,7 @@ handleMultipleFunctions qf = \case
"function " <> qf <<> " is overloaded. Overloaded functions are not supported"
fetchRawFunctioInfo :: MonadTx m => QualifiedFunction -> m RawFunctionInfo
fetchRawFunctioInfo qf@(QualifiedObject sn fn) = do
fetchRawFunctioInfo qf@(QualifiedObject sn fn) =
handleMultipleFunctions qf =<< map (Q.getAltJ . runIdentity) <$> fetchFromDatabase
where
fetchFromDatabase = liftTx $
@ -179,9 +256,31 @@ runTrackFunc
, MonadTx m, UserInfoM m
)
=> TrackFunction -> m EncJSON
runTrackFunc q = do
trackFunctionP1 q
trackFunctionP2 $ tfName q
runTrackFunc (TrackFunction qf)= do
trackFunctionP1 qf
trackFunctionP2 qf emptyFunctionConfig
data TrackFunctionV2
= TrackFunctionV2
{ _tfv2Function :: !QualifiedFunction
, _tfv2Configuration :: !FunctionConfig
} deriving (Show, Eq, Lift)
$(deriveToJSON (aesonDrop 5 snakeCase) ''TrackFunctionV2)
instance FromJSON TrackFunctionV2 where
parseJSON = withObject "Object" $ \o ->
TrackFunctionV2
<$> o .: "function"
<*> o .:? "configuration" .!= emptyFunctionConfig
runTrackFunctionV2
:: ( QErrM m, CacheRWM m, HasSystemDefined m
, MonadTx m, UserInfoM m
)
=> TrackFunctionV2 -> m EncJSON
runTrackFunctionV2 (TrackFunctionV2 qf config) = do
trackFunctionP1 qf
trackFunctionP2 qf config
newtype UnTrackFunction
= UnTrackFunction

View File

@ -230,9 +230,11 @@ sessVarFromCurrentSetting' ty sessVar =
PGTypeScalar baseTy -> withConstructorFn baseTy sessVarVal
PGTypeArray _ -> sessVarVal
where
curSess = S.SEUnsafe "current_setting('hasura.user')::json"
sessVarVal = S.SEOpApp (S.SQLOp "->>")
[curSess, S.SELit $ T.toLower sessVar]
[currentSession, S.SELit $ T.toLower sessVar]
currentSession :: S.SQLExp
currentSession = S.SEUnsafe "current_setting('hasura.user')::json"
checkSelPerm
:: (UserInfoM m, QErrM m, CacheRM m)

View File

@ -335,6 +335,8 @@ data FunctionArgsExpG a
emptyFunctionArgsExp :: FunctionArgsExpG a
emptyFunctionArgsExp = FunctionArgsExp [] HM.empty
type FunctionArgExp = FunctionArgsExpG S.SQLExp
-- | If argument positional index is less than or equal to length of 'positional' arguments then
-- insert the value in 'positional' arguments else insert the value with argument name in 'named' arguments
insertFunctionArg
@ -351,8 +353,6 @@ insertFunctionArg argName index value (FunctionArgsExp positional named) =
where
insertAt i a = toList . Seq.insertAt i a . Seq.fromList
type FunctionArgExp = FunctionArgsExpG S.SQLExp
data AnnFnSelG s v
= AnnFnSel
{ _afFn :: !QualifiedFunction

View File

@ -55,6 +55,7 @@ import Hasura.RQL.Types.ComputedField as R
import Hasura.RQL.Types.DML as R
import Hasura.RQL.Types.Error as R
import Hasura.RQL.Types.EventTrigger as R
import Hasura.RQL.Types.Function as R
import Hasura.RQL.Types.Metadata as R
import Hasura.RQL.Types.Permission as R
import Hasura.RQL.Types.RemoteSchema as R

View File

@ -73,7 +73,7 @@ $(deriveJSON (aesonDrop 3 snakeCase) ''CatalogPermission)
data CatalogComputedField
= CatalogComputedField
{ _cccComputedField :: !AddComputedField
, _cccFunctionInfo :: ![RawFunctionInfo] -- multiple functions with same name
, _cccFunctionInfo :: ![RawFunctionInfo] -- ^ multiple functions with same name
} deriving (Show, Eq)
$(deriveJSON (aesonDrop 4 snakeCase) ''CatalogComputedField)
@ -89,6 +89,7 @@ data CatalogFunction
= CatalogFunction
{ _cfFunction :: !QualifiedFunction
, _cfIsSystemDefined :: !SystemDefined
, _cfConfiguration :: !FunctionConfig
, _cfInfo :: ![RawFunctionInfo] -- ^ multiple functions with same name
} deriving (Show, Eq)
$(deriveJSON (aesonDrop 3 snakeCase) ''CatalogFunction)

View File

@ -23,9 +23,6 @@ module Hasura.RQL.Types.Common
, adminText
, rootText
, FunctionArgName(..)
, FunctionArg(..)
, SystemDefined(..)
, isSystemDefined
) where
@ -184,20 +181,8 @@ $(deriveJSON (aesonDrop 3 snakeCase) ''ForeignKey)
instance Hashable ForeignKey
newtype FunctionArgName =
FunctionArgName { getFuncArgNameTxt :: T.Text}
deriving (Show, Eq, ToJSON, FromJSON, Lift, DQuote, IsString)
type CustomColumnNames = HM.HashMap PGCol G.Name
data FunctionArg
= FunctionArg
{ faName :: !(Maybe FunctionArgName)
, faType :: !QualifiedPGType
, faHasDefault :: !Bool
} deriving (Show, Eq)
$(deriveToJSON (aesonDrop 2 snakeCase) ''FunctionArg)
newtype SystemDefined = SystemDefined { unSystemDefined :: Bool }
deriving (Show, Eq, FromJSON, ToJSON, Q.ToPrepArg)

View File

@ -6,6 +6,7 @@ module Hasura.RQL.Types.ComputedField where
import Hasura.Prelude
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Function
import Hasura.SQL.Types
import Control.Lens hiding ((.=))

View File

@ -0,0 +1,74 @@
module Hasura.RQL.Types.Function where
import Hasura.Prelude
import Hasura.RQL.Types.Common
import Hasura.SQL.Types
import Control.Lens
import Data.Aeson
import Data.Aeson.Casing
import Data.Aeson.TH
import Language.Haskell.TH.Syntax (Lift)
import qualified Data.Sequence as Seq
import qualified Data.Text as T
data FunctionType
= FTVOLATILE
| FTIMMUTABLE
| FTSTABLE
deriving (Eq)
$(deriveJSON defaultOptions{constructorTagModifier = drop 2} ''FunctionType)
funcTypToTxt :: FunctionType -> T.Text
funcTypToTxt FTVOLATILE = "VOLATILE"
funcTypToTxt FTIMMUTABLE = "IMMUTABLE"
funcTypToTxt FTSTABLE = "STABLE"
instance Show FunctionType where
show = T.unpack . funcTypToTxt
newtype FunctionArgName =
FunctionArgName { getFuncArgNameTxt :: T.Text}
deriving (Show, Eq, ToJSON, FromJSON, Lift, DQuote, IsString)
newtype HasDefault = HasDefault { unHasDefault :: Bool }
deriving (Show, Eq, ToJSON)
data FunctionArg
= FunctionArg
{ faName :: !(Maybe FunctionArgName)
, faType :: !QualifiedPGType
, faHasDefault :: !HasDefault
} deriving (Show, Eq)
$(deriveToJSON (aesonDrop 2 snakeCase) ''FunctionArg)
data InputArgument a
= IAUserProvided !a
| IASessionVariables !FunctionArgName
deriving (Show, Eq, Functor)
$(deriveToJSON defaultOptions
{ constructorTagModifier = snakeCase . drop 2
, sumEncoding = TaggedObject "type" "argument"
}
''InputArgument
)
$(makePrisms ''InputArgument)
type FunctionInputArgument = InputArgument FunctionArg
data FunctionInfo
= FunctionInfo
{ fiName :: !QualifiedFunction
, fiSystemDefined :: !SystemDefined
, fiType :: !FunctionType
, fiInputArgs :: !(Seq.Seq FunctionInputArgument)
, fiReturnType :: !QualifiedTable
, fiDescription :: !(Maybe PGDescription)
} deriving (Show, Eq)
$(deriveToJSON (aesonDrop 2 snakeCase) ''FunctionInfo)
getInputArgs :: FunctionInfo -> Seq.Seq FunctionArg
getInputArgs =
Seq.fromList . mapMaybe (^? _IAUserProvided) . toList . fiInputArgs

View File

@ -127,6 +127,7 @@ import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Error
import Hasura.RQL.Types.EventTrigger
import Hasura.RQL.Types.Function
import Hasura.RQL.Types.Metadata
import Hasura.RQL.Types.Permission
import Hasura.RQL.Types.QueryCollection
@ -142,7 +143,6 @@ import Language.Haskell.TH.Syntax (Lift)
import qualified Data.HashMap.Strict as M
import qualified Data.HashSet as HS
import qualified Data.Sequence as Seq
import qualified Data.Text as T
reportSchemaObjs :: [SchemaObjId] -> T.Text
@ -378,35 +378,6 @@ checkForFieldConflict tabInfo f =
]
Nothing -> return ()
data FunctionType
= FTVOLATILE
| FTIMMUTABLE
| FTSTABLE
deriving (Eq)
$(deriveJSON defaultOptions{constructorTagModifier = drop 2} ''FunctionType)
funcTypToTxt :: FunctionType -> T.Text
funcTypToTxt FTVOLATILE = "VOLATILE"
funcTypToTxt FTIMMUTABLE = "IMMUTABLE"
funcTypToTxt FTSTABLE = "STABLE"
instance Show FunctionType where
show = T.unpack . funcTypToTxt
data FunctionInfo
= FunctionInfo
{ fiName :: !QualifiedFunction
, fiSystemDefined :: !SystemDefined
, fiType :: !FunctionType
, fiInputArgs :: !(Seq.Seq FunctionArg)
, fiReturnType :: !QualifiedTable
, fiDeps :: ![SchemaDependency]
, fiDescription :: !(Maybe PGDescription)
} deriving (Show, Eq)
$(deriveToJSON (aesonDrop 2 snakeCase) ''FunctionInfo)
type TableCache columnInfo = M.HashMap QualifiedTable (TableInfo columnInfo) -- info of all tables
type FunctionCache = M.HashMap QualifiedFunction FunctionInfo -- info of all functions
@ -677,8 +648,8 @@ delEventTriggerFromCache qt trn = do
addFunctionToCache
:: (QErrM m, CacheRWM m)
=> FunctionInfo -> m ()
addFunctionToCache fi = do
=> FunctionInfo -> [SchemaDependency] -> m ()
addFunctionToCache fi deps = do
sc <- askSchemaCache
let functionCache = scFunctions sc
case M.lookup fn functionCache of
@ -690,7 +661,6 @@ addFunctionToCache fi = do
where
fn = fiName fi
objId = SOFunction $ fiName fi
deps = fiDeps fi
askFunctionInfo
:: (CacheRM m, QErrM m)

View File

@ -12,7 +12,7 @@ import Hasura.Prelude
import qualified Data.Text as T
latestCatalogVersion :: Integer
latestCatalogVersion = 27
latestCatalogVersion = 28
latestCatalogVersionString :: T.Text
latestCatalogVersionString = T.pack $ show latestCatalogVersion

View File

@ -107,6 +107,7 @@ data RQLQueryV1
data RQLQueryV2
= RQV2TrackTable !TrackTableV2
| RQV2SetTableCustomFields !SetTableCustomFields
| RQV2TrackFunction !TrackFunctionV2
deriving (Show, Eq, Lift)
data RQLQuery
@ -297,6 +298,7 @@ queryNeedsReload (RQV1 qi) = case qi of
queryNeedsReload (RQV2 qi) = case qi of
RQV2TrackTable _ -> True
RQV2SetTableCustomFields _ -> True
RQV2TrackFunction _ -> True
-- TODO: RQSelect query should also be run in READ ONLY mode.
-- But this could be part of console's bulk statement and hence should be added after console changes
@ -408,3 +410,4 @@ runQueryM rq =
runQueryV2M = \case
RQV2TrackTable q -> runTrackTableV2Q q
RQV2SetTableCustomFields q -> runSetTableCustomFieldsQV2 q
RQV2TrackFunction q -> runTrackFunctionV2 q

View File

@ -207,3 +207,10 @@ instance FromJSON APIVersion where
1 -> return VIVersion1
2 -> return VIVersion2
i -> fail $ "expected 1 or 2, encountered " ++ show i
makeReasonMessage :: [a] -> (a -> Text) -> Text
makeReasonMessage errors showError =
case errors of
[singleError] -> "because " <> showError singleError
_ -> "for the following reasons:\n" <> T.unlines
(map (("" <>) . showError) errors)

View File

@ -129,6 +129,7 @@ from
'schema', hf.function_schema,
'name', hf.function_name
),
'configuration', hf.configuration,
'is_system_defined', hf.is_system_defined,
'info', hf_agg.function_info
) as info

View File

@ -306,6 +306,7 @@ CREATE TABLE hdb_catalog.hdb_function
(
function_schema TEXT,
function_name TEXT,
configuration JSONB NOT NULL DEFAULT '{}'::jsonb,
is_system_defined boolean default false,
PRIMARY KEY (function_schema, function_name)

View File

@ -0,0 +1,2 @@
ALTER TABLE hdb_catalog.hdb_function
ADD COLUMN configuration JSONB NOT NULL DEFAULT '{}'::jsonb;

View File

@ -0,0 +1,19 @@
description: Query get_session_var custom SQL function
url: /v1/graphql
status: 200
headers:
X-Hasura-Test: test value
X-Hasura-Role: admin
response:
data:
get_session_var:
- result: test value
query:
query: |
query a {
get_session_var(
args: {session_var: "x-hasura-test"}
){
result
}
}

View File

@ -136,3 +136,30 @@ args:
args:
name: get_users
schema: public
# V2 Functions
- type: run_sql
args:
sql: |
CREATE TABLE text_result(
result text
);
CREATE FUNCTION get_session_var(hasura_session json, session_var text)
RETURNS SETOF text_result AS $$
SELECT q.* FROM (VALUES (hasura_session ->> session_var)) q
$$ LANGUAGE sql STABLE;
- type: track_table
args:
name: text_result
schema: public
- type: track_function
version: 2
args:
function:
schema: public
name: get_session_var
configuration:
session_argument: hasura_session

View File

@ -8,4 +8,5 @@ args:
DROP TABLE test cascade;
DROP TABLE integer_column cascade;
DROP TABLE "user" cascade;
DROP TABLE text_result cascade;
cascade: true

View File

@ -0,0 +1,51 @@
- description: setup a custom SQL function
url: /v1/query
status: 200
query:
type: run_sql
args:
sql: |
CREATE FUNCTION get_session_var_value(hasura_session json, session_var text)
RETURNS SETOF text_result AS $$
SELECT q.* FROM (VALUES (hasura_session ->> session_var)) q
$$ LANGUAGE sql STABLE;
- description: Track function v2 with invalid session argument
url: /v1/query
status: 400
response:
path: "$.args"
error: the function "get_session_var_value" cannot be tracked because given session argument "random" not the input argument of the function
code: not-supported
query:
version: 2
type: track_function
args:
function: get_session_var_value
configuration:
session_argument: random
- description: Track function v2 with non json session argument
url: /v1/query
status: 400
response:
path: "$.args"
error: the function "get_session_var_value" cannot be tracked because given session argument "session_var" is not of type json
code: not-supported
query:
version: 2
type: track_function
args:
function: get_session_var_value
configuration:
session_argument: session_var
- description: teardown function
url: /v1/query
status: 200
query:
type: run_sql
args:
sql: |
DROP FUNCTION get_session_var_value(json, text);
cascade: true

View File

@ -0,0 +1,12 @@
description: Track function search_articles
url: /v1/query
status: 400
response:
path: "$.version"
error: expected 1 or 2, encountered 3
code: parse-failed
query:
type: track_function
version: 3
args:
function: search_articles

View File

@ -92,3 +92,15 @@ args:
true
)
# Search article functions
- type: run_sql
args:
sql: |
CREATE FUNCTION search_articles(search text)
RETURNS SETOF article AS $$
SELECT *
FROM article
WHERE
title ilike ('%' || search || '%')
OR content ilike ('%' || search || '%')
$$ LANGUAGE sql STABLE;

View File

@ -3,8 +3,6 @@ args:
- type: run_sql
args:
sql: |
drop table article
- type: run_sql
args:
sql: |
drop table author
DROP TABLE article CASCADE;
DROP TABLE author;
cascade: true

View File

@ -74,7 +74,7 @@
response:
path: "$.args.definition"
error: "the computed field \"get_articles\" cannot be added to table \"author\" for
the following reasons: \n • the function \"fetch_articles_volatile\" is of type
the following reasons:\n • the function \"fetch_articles_volatile\" is of type
VOLATILE; cannot be added as a computed field\n • \"random\" is not an input argument
of \"fetch_articles_volatile\" function\n"
code: not-supported
@ -108,7 +108,7 @@
response:
path: "$.args.definition"
error: "the computed field \"get_articles\" cannot be added to table \"author\" for
the following reasons: \n • first argument of the function \"fetch_articles\" is
the following reasons:\n • first argument of the function \"fetch_articles\" is
not COMPOSITE type\n • first argument of the function \"fetch_articles\" of type
\"pg_catalog.text\" is not the table to which the computed field is being added\n"
code: not-supported

View File

@ -11,6 +11,7 @@
url: /v1/query
status: 200
response:
version: 2
allowlist: []
functions: []
query_collections: []

View File

@ -2,8 +2,10 @@ description: Export schema cache (metadata)
url: /v1/query
status: 200
response:
version: 2
functions:
- search_articles
- function: search_articles
configuration: {}
remote_schemas: []
query_collections: []
allowlist: []

View File

@ -0,0 +1,53 @@
description: Import a v2 metadata
url: /v1/query
status: 200
response:
message: success
query:
type: replace_metadata
args:
version: 2
functions:
- function:
schema: public
name: search_articles
- function:
schema: public
name: get_session_var
configuration:
session_argument: hasura_session
tables:
- table: author
object_relationships: []
array_relationships:
- using:
foreign_key_constraint_on:
column: author_id
table: article
name: articles
comment: List all articles of the author
insert_permissions: []
select_permissions: []
update_permissions: []
delete_permissions: []
event_triggers: []
- table: article
object_relationships:
- using:
foreign_key_constraint_on: author_id
name: author
comment: null
array_relationships: []
insert_permissions: []
select_permissions: []
update_permissions: []
delete_permissions: []
event_triggers: []
- table: text_result
object_relationships: []
array_relationships: []
insert_permissions: []
select_permissions: []
update_permissions: []
delete_permissions: []
event_triggers: []

View File

@ -121,3 +121,15 @@ args:
definition:
function: fetch_articles
table_argument: author_row
- type: run_sql
args:
sql: |
CREATE TABLE text_result(
result text
);
CREATE FUNCTION get_session_var(hasura_session json, session_var text)
RETURNS SETOF text_result AS $$
SELECT q.* FROM (VALUES (hasura_session ->> session_var)) q
$$ LANGUAGE sql STABLE;

View File

@ -5,9 +5,6 @@ args:
args:
cascade: true
sql: |
drop table article cascade
- type: run_sql
args:
cascade: true
sql: |
drop table author
drop table article cascade;
drop table author;
drop table text_result cascade;

View File

@ -181,9 +181,12 @@
type: export_metadata
args: {}
response:
version: 2
functions:
- get_test1
- get_test2
- function: get_test1
configuration: {}
- function: get_test2
configuration: {}
remote_schemas: []
query_collections:
- name: collection_1
@ -552,9 +555,12 @@
type: export_metadata
args: {}
response:
version: 2
functions:
- get_test1
- get_test2
- function: get_test1
configuration: {}
- function: get_test2
configuration: {}
remote_schemas: []
query_collections:
- name: collection_1

View File

@ -482,6 +482,13 @@ class TestGraphQLQueryFunctions(DefaultTestSelectQueries):
def test_query_my_add(self, hge_ctx):
check_query_f(hge_ctx, self.dir() + '/query_my_add.yaml')
@pytest.mark.parametrize("transport", ['http', 'websocket'])
def test_query_get_session_var(self, hge_ctx, transport):
check_query_f(hge_ctx, self.dir() + '/query_get_session_var.yaml', transport)
def test_track_function_v2_errors(self, hge_ctx):
check_query_f(hge_ctx, self.dir() + '/track_function_v2_errors.yaml')
@classmethod
def dir(cls):
return 'queries/graphql_query/functions'

View File

@ -17,6 +17,9 @@ class TestV1General(DefaultTestQueries):
def test_query_args_as_string_err(self, hge_ctx):
check_query_f(hge_ctx, self.dir() + '/query_args_as_string_err.yaml')
def test_query_v2_invalid_version(self, hge_ctx):
check_query_f(hge_ctx, self.dir() + '/query_v2_invalid_version.yaml')
@classmethod
def dir(cls):
return "queries/v1/basic"
@ -476,9 +479,30 @@ class TestMetadata(DefaultTestQueries):
def test_replace_metadata_wo_remote_schemas(self, hge_ctx):
check_query_f(hge_ctx, self.dir() + '/replace_metadata_wo_rs.yaml')
def test_replace_metadata_v2(self, hge_ctx):
check_query_f(hge_ctx, self.dir() + '/replace_metadata_v2.yaml')
def test_dump_internal_state(self, hge_ctx):
check_query_f(hge_ctx, self.dir() + '/dump_internal_state.yaml')
def test_export_replace(self, hge_ctx):
url = '/v1/query'
export_query = {
'type': 'export_metadata',
'args': {}
}
headers = {}
if hge_ctx.hge_key is not None:
headers['X-Hasura-Admin-Secret'] = hge_ctx.hge_key
export_code, export_resp = hge_ctx.anyq(url, export_query, headers)
assert export_code == 200, export_resp
replace_query = {
'type': 'replace_metadata',
'args': export_resp
}
replace_code, replace_resp = hge_ctx.anyq(url, replace_query, headers)
assert replace_code == 200, replace_resp
@classmethod
def dir(cls):
return "queries/v1/metadata"