2022-11-10 19:15:55 +03:00
|
|
|
{-# LANGUAGE OverloadedLists #-}
|
2022-12-05 13:20:47 +03:00
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
2022-03-16 03:39:21 +03:00
|
|
|
|
2023-04-03 13:18:54 +03:00
|
|
|
-- | types and helpers for user-defined-functions after they have been resolved
|
|
|
|
-- in the schema cache
|
|
|
|
module Hasura.Function.Cache
|
2021-11-04 19:08:33 +03:00
|
|
|
( DBFunctionsMetadata,
|
2022-12-05 13:20:47 +03:00
|
|
|
FunctionOverloads (..),
|
2021-11-04 19:08:33 +03:00
|
|
|
FunctionArgName (..),
|
|
|
|
FunctionCache,
|
|
|
|
FunctionConfig (..),
|
|
|
|
FunctionCustomRootFields (..),
|
|
|
|
FunctionExposedAs (..),
|
|
|
|
FunctionInfo (..),
|
|
|
|
FunctionInputArgument,
|
|
|
|
FunctionPermissionInfo (..),
|
|
|
|
FunctionPermissionsMap,
|
|
|
|
FunctionVolatility (..),
|
|
|
|
InputArgument (..),
|
2022-05-25 13:24:41 +03:00
|
|
|
FunctionArgsExpG (..),
|
|
|
|
FunctionArgsExp,
|
2023-05-19 07:47:12 +03:00
|
|
|
TrackableFunctionInfo (..),
|
|
|
|
TrackableTableInfo (..),
|
|
|
|
TrackableInfo (..),
|
2021-11-04 19:08:33 +03:00
|
|
|
emptyFunctionConfig,
|
|
|
|
emptyFunctionCustomRootFields,
|
|
|
|
funcTypToTxt,
|
2022-05-25 13:24:41 +03:00
|
|
|
emptyFunctionArgsExp,
|
2021-11-04 19:08:33 +03:00
|
|
|
)
|
|
|
|
where
|
2019-11-20 09:47:06 +03:00
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
import Autodocodec (HasCodec (codec))
|
2022-11-10 19:15:55 +03:00
|
|
|
import Autodocodec qualified as AC
|
|
|
|
import Autodocodec.Extended (graphQLFieldNameCodec)
|
2021-09-24 01:56:37 +03:00
|
|
|
import Control.Lens
|
|
|
|
import Data.Aeson
|
|
|
|
import Data.Aeson.Casing
|
|
|
|
import Data.Char (toLower)
|
2023-04-26 18:42:13 +03:00
|
|
|
import Data.HashMap.Strict qualified as HashMap
|
2021-10-07 16:02:19 +03:00
|
|
|
import Data.List.Extended as LE
|
2021-09-24 01:56:37 +03:00
|
|
|
import Data.Sequence qualified as Seq
|
|
|
|
import Data.Text qualified as T
|
|
|
|
import Data.Text.Extended
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.Types.Backend
|
2023-04-24 21:35:48 +03:00
|
|
|
import Hasura.RQL.Types.BackendType
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.RQL.Types.Common
|
2023-04-24 11:50:29 +03:00
|
|
|
import Hasura.RQL.Types.Roles (RoleName)
|
2021-10-07 16:02:19 +03:00
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
2022-05-25 13:24:41 +03:00
|
|
|
import Language.Haskell.TH.Syntax
|
2021-04-22 00:44:37 +03:00
|
|
|
|
2020-11-18 21:04:57 +03:00
|
|
|
-- | https://www.postgresql.org/docs/current/xfunc-volatility.html
|
|
|
|
data FunctionVolatility
|
2019-11-20 09:47:06 +03:00
|
|
|
= FTVOLATILE
|
|
|
|
| FTIMMUTABLE
|
|
|
|
| FTSTABLE
|
2019-11-27 01:49:42 +03:00
|
|
|
deriving (Eq, Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2020-11-18 21:04:57 +03:00
|
|
|
instance NFData FunctionVolatility
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2023-04-28 17:12:59 +03:00
|
|
|
instance FromJSON FunctionVolatility where
|
|
|
|
parseJSON = genericParseJSON defaultOptions {constructorTagModifier = drop 2}
|
|
|
|
|
|
|
|
instance ToJSON FunctionVolatility where
|
|
|
|
toJSON = genericToJSON defaultOptions {constructorTagModifier = drop 2}
|
|
|
|
toEncoding = genericToEncoding defaultOptions {constructorTagModifier = drop 2}
|
2019-11-20 09:47:06 +03:00
|
|
|
|
2020-11-18 21:04:57 +03:00
|
|
|
funcTypToTxt :: FunctionVolatility -> Text
|
2021-09-24 01:56:37 +03:00
|
|
|
funcTypToTxt FTVOLATILE = "VOLATILE"
|
2019-11-20 09:47:06 +03:00
|
|
|
funcTypToTxt FTIMMUTABLE = "IMMUTABLE"
|
2021-09-24 01:56:37 +03:00
|
|
|
funcTypToTxt FTSTABLE = "STABLE"
|
2019-11-20 09:47:06 +03:00
|
|
|
|
2020-11-18 21:04:57 +03:00
|
|
|
instance Show FunctionVolatility where
|
2019-11-20 09:47:06 +03:00
|
|
|
show = T.unpack . funcTypToTxt
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype FunctionArgName = FunctionArgName {getFuncArgNameTxt :: Text}
|
server: delete the `Cacheable` type class in favor of `Eq`
What is the `Cacheable` type class about?
```haskell
class Eq a => Cacheable a where
unchanged :: Accesses -> a -> a -> Bool
default unchanged :: (Generic a, GCacheable (Rep a)) => Accesses -> a -> a -> Bool
unchanged accesses a b = gunchanged (from a) (from b) accesses
```
Its only method is an alternative to `(==)`. The added value of `unchanged` (and the additional `Accesses` argument) arises _only_ for one type, namely `Dependency`. Indeed, the `Cacheable (Dependency a)` instance is non-trivial, whereas every other `Cacheable` instance is completely boilerplate (and indeed either generated from `Generic`, or simply `unchanged _ = (==)`). The `Cacheable (Dependency a)` instance is the only one where the `Accesses` argument is not just passed onwards.
The only callsite of the `unchanged` method is in the `ArrowCache (Rule m)` method. That is to say that the `Cacheable` type class is used to decide when we can re-use parts of the schema cache between Metadata operations.
So what is the `Cacheable (Dependency a)` instance about? Normally, the output of a `Rule m a b` is re-used when the new input (of type `a`) is equal to the old one. But sometimes, that's too coarse: it might be that a certain `Rule m a b` only depends on a small part of its input of type `a`. A `Dependency` allows us to spell out what parts of `a` are being depended on, and these parts are recorded as values of types `Access a` in the state `Accesses`.
If the input `a` changes, but not in a way that touches the recorded `Accesses`, then the output `b` of that rule can be re-used without recomputing.
So now you understand _why_ we're passing `Accesses` to the `unchanged` method: `unchanged` is an equality check in disguise that just needs some additional context.
But we don't need to pass `Accesses` as a function argument. We can use the `reflection` package to pass it as type-level context. So the core of this PR is that we change the instance declaration from
```haskell
instance (Cacheable a) => Cacheable (Dependency a) where
```
to
```haskell
instance (Given Accesses, Eq a) => Eq (Dependency a) where
```
and use `(==)` instead of `unchanged`.
If you haven't seen `reflection` before: it's like a `MonadReader`, but it doesn't require a `Monad`.
In order to pass the current `Accesses` value, instead of simply passing the `Accesses` as a function argument, we need to instantiate the `Given Accesses` context. We use the `give` method from the `reflection` package for that.
```haskell
give :: forall r. Accesses -> (Given Accesses => r) -> r
unchanged :: (Given Accesses => Eq a) => Accesses -> a -> a -> Bool
unchanged accesses a b = give accesses (a == b)
```
With these three components in place, we can delete the `Cacheable` type class entirely.
The remainder of this PR is just to remove the `Cacheable` type class and its instances.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6877
GitOrigin-RevId: 7125f5e11d856e7672ab810a23d5bf5ad176e77f
2022-11-21 19:33:56 +03:00
|
|
|
deriving (Show, Eq, Ord, NFData, ToJSON, ToJSONKey, FromJSON, FromJSONKey, ToTxt, IsString, Generic, Hashable, Lift, Data)
|
2019-11-20 09:47:06 +03:00
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
instance AC.HasCodec FunctionArgName where
|
|
|
|
codec = AC.dimapCodec FunctionArgName getFuncArgNameTxt codec
|
2022-11-10 19:15:55 +03:00
|
|
|
|
2019-11-20 09:47:06 +03:00
|
|
|
data InputArgument a
|
2022-08-01 12:32:04 +03:00
|
|
|
= IAUserProvided a
|
|
|
|
| IASessionVariables FunctionArgName
|
2023-04-28 17:12:59 +03:00
|
|
|
deriving (Show, Eq, Functor, Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2023-04-28 17:12:59 +03:00
|
|
|
instance ToJSON a => ToJSON (InputArgument a) where
|
|
|
|
toJSON = genericToJSON defaultOptions {constructorTagModifier = snakeCase . drop 2, sumEncoding = TaggedObject "type" "argument"}
|
|
|
|
toEncoding = genericToEncoding defaultOptions {constructorTagModifier = snakeCase . drop 2, sumEncoding = TaggedObject "type" "argument"}
|
2019-11-20 09:47:06 +03:00
|
|
|
|
2022-05-25 13:24:41 +03:00
|
|
|
type FunctionInputArgument b = InputArgument (FunctionArgument b)
|
2019-11-20 09:47:06 +03:00
|
|
|
|
2020-11-18 21:04:57 +03:00
|
|
|
-- | Indicates whether the user requested the corresponding function to be
|
|
|
|
-- tracked as a mutation or a query/subscription, in @track_function@.
|
|
|
|
data FunctionExposedAs = FEAQuery | FEAMutation
|
2020-11-26 16:57:03 +03:00
|
|
|
deriving (Show, Eq, Generic)
|
2020-11-18 21:04:57 +03:00
|
|
|
|
|
|
|
instance NFData FunctionExposedAs
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2022-11-10 19:15:55 +03:00
|
|
|
instance HasCodec FunctionExposedAs where
|
2023-05-19 07:47:12 +03:00
|
|
|
codec = AC.stringConstCodec [(FEAQuery, "query"), (FEAMutation, "mutation")]
|
2022-11-10 19:15:55 +03:00
|
|
|
|
2023-04-28 17:12:59 +03:00
|
|
|
instance FromJSON FunctionExposedAs where
|
|
|
|
parseJSON = genericParseJSON defaultOptions {sumEncoding = UntaggedValue, constructorTagModifier = map toLower . drop 3}
|
|
|
|
|
|
|
|
instance ToJSON FunctionExposedAs where
|
|
|
|
toJSON = genericToJSON defaultOptions {sumEncoding = UntaggedValue, constructorTagModifier = map toLower . drop 3}
|
|
|
|
toEncoding = genericToEncoding defaultOptions {sumEncoding = UntaggedValue, constructorTagModifier = map toLower . drop 3}
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
newtype FunctionPermissionInfo = FunctionPermissionInfo
|
|
|
|
{ _fpmRole :: RoleName
|
|
|
|
}
|
|
|
|
deriving (Show, Eq, Generic)
|
|
|
|
|
2022-11-10 19:15:55 +03:00
|
|
|
instance HasCodec FunctionPermissionInfo where
|
|
|
|
codec =
|
|
|
|
AC.object "FunctionPermissionInfo" $
|
2023-05-19 07:47:12 +03:00
|
|
|
FunctionPermissionInfo <$> AC.requiredField' "role" AC..= _fpmRole
|
2022-11-10 19:15:55 +03:00
|
|
|
|
2023-04-28 17:12:59 +03:00
|
|
|
instance FromJSON FunctionPermissionInfo where
|
|
|
|
parseJSON = genericParseJSON hasuraJSON
|
|
|
|
|
|
|
|
instance ToJSON FunctionPermissionInfo where
|
|
|
|
toJSON = genericToJSON hasuraJSON
|
|
|
|
toEncoding = genericToEncoding hasuraJSON
|
2021-08-09 13:20:04 +03:00
|
|
|
|
|
|
|
type FunctionPermissionsMap = HashMap RoleName FunctionPermissionInfo
|
2020-11-18 21:04:57 +03:00
|
|
|
|
2021-10-07 16:02:19 +03:00
|
|
|
-- | Custom root fields for functions. When set, will be the names exposed
|
|
|
|
-- to the user in the schema.
|
|
|
|
--
|
|
|
|
-- See rfcs/function-root-field-customisation.md for more information.
|
|
|
|
data FunctionCustomRootFields = FunctionCustomRootFields
|
|
|
|
{ _fcrfFunction :: Maybe G.Name,
|
|
|
|
_fcrfFunctionAggregate :: Maybe G.Name
|
|
|
|
}
|
|
|
|
deriving (Show, Eq, Generic)
|
|
|
|
|
|
|
|
instance NFData FunctionCustomRootFields
|
|
|
|
|
2022-11-10 19:15:55 +03:00
|
|
|
instance HasCodec FunctionCustomRootFields where
|
|
|
|
codec =
|
2023-05-19 07:47:12 +03:00
|
|
|
AC.bimapCodec checkForDup id $
|
2022-11-10 19:15:55 +03:00
|
|
|
AC.object "FunctionCustomRootFields" $
|
|
|
|
FunctionCustomRootFields
|
2023-05-19 07:47:12 +03:00
|
|
|
<$> AC.optionalFieldWith' "function" graphQLFieldNameCodec AC..= _fcrfFunction
|
|
|
|
<*> AC.optionalFieldWith' "function_aggregate" graphQLFieldNameCodec AC..= _fcrfFunctionAggregate
|
2022-11-10 19:15:55 +03:00
|
|
|
where
|
|
|
|
checkForDup (FunctionCustomRootFields (Just f) (Just fa))
|
|
|
|
| f == fa =
|
|
|
|
Left $
|
|
|
|
T.unpack $
|
|
|
|
"the following custom root field names are duplicated: " <> toTxt f <<> " and " <>> toTxt fa
|
|
|
|
checkForDup fields = Right fields
|
|
|
|
|
2023-04-28 17:12:59 +03:00
|
|
|
instance ToJSON FunctionCustomRootFields where
|
|
|
|
toJSON = genericToJSON hasuraJSON {omitNothingFields = True}
|
|
|
|
toEncoding = genericToEncoding hasuraJSON {omitNothingFields = True}
|
2021-10-07 16:02:19 +03:00
|
|
|
|
|
|
|
instance FromJSON FunctionCustomRootFields where
|
|
|
|
parseJSON = withObject "Object" $ \obj -> do
|
|
|
|
function <- obj .:? "function"
|
|
|
|
functionAggregate <- obj .:? "function_aggregate"
|
|
|
|
|
|
|
|
case (function, functionAggregate) of
|
|
|
|
(Just f, Just fa)
|
|
|
|
| f == fa ->
|
2022-11-02 23:53:23 +03:00
|
|
|
fail $
|
|
|
|
T.unpack $
|
|
|
|
"the following custom root field names are duplicated: "
|
|
|
|
<> toTxt f <<> " and " <>> toTxt fa
|
2021-10-07 16:02:19 +03:00
|
|
|
_ ->
|
|
|
|
pure ()
|
|
|
|
|
|
|
|
pure $ FunctionCustomRootFields function functionAggregate
|
|
|
|
|
|
|
|
-- | A function custom root fields without custom names set. This is the default.
|
|
|
|
emptyFunctionCustomRootFields :: FunctionCustomRootFields
|
|
|
|
emptyFunctionCustomRootFields =
|
|
|
|
FunctionCustomRootFields
|
|
|
|
{ _fcrfFunction = Nothing,
|
|
|
|
_fcrfFunctionAggregate = Nothing
|
|
|
|
}
|
|
|
|
|
2021-03-18 15:49:57 +03:00
|
|
|
-- | Tracked SQL function metadata. See 'buildFunctionInfo'.
|
2021-09-24 01:56:37 +03:00
|
|
|
data FunctionInfo (b :: BackendType) = FunctionInfo
|
2021-10-07 16:02:19 +03:00
|
|
|
{ _fiSQLName :: FunctionName b,
|
|
|
|
_fiGQLName :: G.Name,
|
|
|
|
_fiGQLArgsName :: G.Name,
|
|
|
|
_fiGQLAggregateName :: G.Name,
|
|
|
|
_fiSystemDefined :: SystemDefined,
|
|
|
|
_fiVolatility :: FunctionVolatility,
|
2021-09-24 01:56:37 +03:00
|
|
|
-- | In which part of the schema should this function be exposed?
|
|
|
|
--
|
|
|
|
-- See 'mkFunctionInfo' and '_fcExposedAs'.
|
2021-10-07 16:02:19 +03:00
|
|
|
_fiExposedAs :: FunctionExposedAs,
|
|
|
|
_fiInputArgs :: Seq.Seq (FunctionInputArgument b),
|
2021-09-24 01:56:37 +03:00
|
|
|
-- | NOTE: when a table is created, a new composite type of the same name is
|
|
|
|
-- automatically created; so strictly speaking this field means "the function
|
|
|
|
-- returns the composite type corresponding to this table".
|
2023-05-19 07:47:12 +03:00
|
|
|
_fiReturnType :: TableName b, -- NOTE: We will extend this in future, but for now always resolves to a (TableName b)
|
|
|
|
|
2021-09-24 12:18:40 +03:00
|
|
|
-- | this field represents the description of the function as present on the database
|
2021-10-07 16:02:19 +03:00
|
|
|
_fiDescription :: Maybe Text,
|
2021-09-24 01:56:37 +03:00
|
|
|
-- | Roles to which the function is accessible
|
2021-10-07 16:02:19 +03:00
|
|
|
_fiPermissions :: FunctionPermissionsMap,
|
|
|
|
_fiJsonAggSelect :: JsonAggSelect,
|
|
|
|
_fiComment :: Maybe Text
|
2021-09-24 01:56:37 +03:00
|
|
|
}
|
|
|
|
deriving (Generic)
|
|
|
|
|
2021-01-20 03:31:53 +03:00
|
|
|
deriving instance Backend b => Show (FunctionInfo b)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
deriving instance Backend b => Eq (FunctionInfo b)
|
2021-04-22 00:44:37 +03:00
|
|
|
|
2021-01-20 03:31:53 +03:00
|
|
|
instance (Backend b) => ToJSON (FunctionInfo b) where
|
|
|
|
toJSON = genericToJSON hasuraJSON
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-01-20 03:31:53 +03:00
|
|
|
type FunctionCache b = HashMap (FunctionName b) (FunctionInfo b) -- info of all functions
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
data TrackableFunctionInfo b = TrackableFunctionInfo
|
|
|
|
{ tfiFunctionName :: FunctionName b,
|
|
|
|
tfiFunctionVolitility :: FunctionVolatility
|
|
|
|
}
|
|
|
|
deriving (Generic)
|
|
|
|
|
|
|
|
deriving instance Backend b => Show (TrackableFunctionInfo b)
|
|
|
|
|
|
|
|
deriving instance Backend b => Eq (TrackableFunctionInfo b)
|
|
|
|
|
|
|
|
instance (Backend b) => ToJSON (TrackableFunctionInfo b) where
|
|
|
|
toJSON (TrackableFunctionInfo name volitility) =
|
|
|
|
object
|
|
|
|
[ "name" Data.Aeson..= name,
|
|
|
|
"volitility" Data.Aeson..= volitility
|
|
|
|
]
|
|
|
|
|
|
|
|
newtype TrackableTableInfo b = TrackableTableInfo
|
|
|
|
{tfTableiName :: TableName b}
|
|
|
|
deriving (Generic)
|
|
|
|
|
|
|
|
deriving instance Backend b => Show (TrackableTableInfo b)
|
|
|
|
|
|
|
|
deriving instance Backend b => Eq (TrackableTableInfo b)
|
|
|
|
|
|
|
|
instance (Backend b) => ToJSON (TrackableTableInfo b) where
|
|
|
|
toJSON (TrackableTableInfo ti) = object ["name" Data.Aeson..= ti]
|
|
|
|
|
|
|
|
data TrackableInfo b = TrackableInfo
|
|
|
|
{ trackableFunctions :: [TrackableFunctionInfo b],
|
|
|
|
trackableTables :: [TrackableTableInfo b]
|
|
|
|
}
|
|
|
|
deriving (Generic)
|
|
|
|
|
|
|
|
deriving instance Backend b => Show (TrackableInfo b)
|
|
|
|
|
|
|
|
deriving instance Backend b => Eq (TrackableInfo b)
|
|
|
|
|
|
|
|
instance (Backend b) => ToJSON (TrackableInfo b) where
|
|
|
|
toJSON (TrackableInfo functions tables) =
|
|
|
|
object
|
|
|
|
[ "tables" Data.Aeson..= tables,
|
|
|
|
"functions" Data.Aeson..= functions
|
|
|
|
]
|
|
|
|
|
2020-11-12 12:25:48 +03:00
|
|
|
-- Metadata requests related types
|
2020-11-18 21:04:57 +03:00
|
|
|
|
2021-10-07 16:02:19 +03:00
|
|
|
-- | Tracked function configuration, and payload of the 'pg_track_function' and
|
|
|
|
-- 'pg_set_function_customization' API calls.
|
2023-05-19 07:47:12 +03:00
|
|
|
data FunctionConfig b = FunctionConfig
|
2021-10-07 16:02:19 +03:00
|
|
|
{ _fcSessionArgument :: Maybe FunctionArgName,
|
2021-09-24 01:56:37 +03:00
|
|
|
-- | In which top-level field should we expose this function?
|
|
|
|
--
|
|
|
|
-- The user might omit this, in which case we'll infer the location from the
|
|
|
|
-- SQL functions volatility. See 'mkFunctionInfo' or the @track_function@ API
|
|
|
|
-- docs for details of validation, etc.
|
2021-10-07 16:02:19 +03:00
|
|
|
_fcExposedAs :: Maybe FunctionExposedAs,
|
|
|
|
_fcCustomRootFields :: FunctionCustomRootFields,
|
2023-05-19 07:47:12 +03:00
|
|
|
_fcCustomName :: Maybe G.Name,
|
|
|
|
_fcResponse :: Maybe (FunctionReturnType b)
|
2021-09-24 01:56:37 +03:00
|
|
|
}
|
2023-05-19 07:47:12 +03:00
|
|
|
deriving (Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
deriving stock instance Backend b => Show (FunctionConfig b)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
deriving stock instance Backend b => Eq (FunctionConfig b)
|
|
|
|
|
|
|
|
instance Backend b => NFData (FunctionConfig b)
|
|
|
|
|
|
|
|
instance Backend b => HasCodec (FunctionConfig b) where
|
2022-11-10 19:15:55 +03:00
|
|
|
codec =
|
|
|
|
AC.object "FunctionConfig" $
|
|
|
|
FunctionConfig
|
2023-05-19 07:47:12 +03:00
|
|
|
<$> AC.optionalField' "session_argument" AC..= _fcSessionArgument
|
|
|
|
<*> AC.optionalField' "exposed_as" AC..= _fcExposedAs
|
|
|
|
<*> AC.optionalFieldWithDefault' "custom_root_fields" emptyFunctionCustomRootFields AC..= _fcCustomRootFields
|
|
|
|
<*> AC.optionalFieldWith' "custom_name" graphQLFieldNameCodec AC..= _fcCustomName
|
|
|
|
<*> AC.optionalFieldWith' "response" codec AC..= _fcResponse
|
2022-11-10 19:15:55 +03:00
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
instance Backend b => FromJSON (FunctionConfig b) where
|
2021-10-07 16:02:19 +03:00
|
|
|
parseJSON = withObject "FunctionConfig" $ \obj ->
|
|
|
|
FunctionConfig
|
|
|
|
<$> obj .:? "session_argument"
|
|
|
|
<*> obj .:? "exposed_as"
|
|
|
|
<*> obj .:? "custom_root_fields" .!= emptyFunctionCustomRootFields
|
|
|
|
<*> obj .:? "custom_name"
|
2023-05-19 07:47:12 +03:00
|
|
|
<*> obj .:? "response"
|
2021-10-07 16:02:19 +03:00
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
instance Backend b => ToJSON (FunctionConfig b) where
|
2023-04-28 17:12:59 +03:00
|
|
|
toJSON = genericToJSON hasuraJSON {omitNothingFields = True}
|
|
|
|
toEncoding = genericToEncoding hasuraJSON {omitNothingFields = True}
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2020-11-18 21:04:57 +03:00
|
|
|
-- | The default function config; v1 of the API implies this.
|
2023-05-19 07:47:12 +03:00
|
|
|
emptyFunctionConfig :: FunctionConfig b
|
|
|
|
emptyFunctionConfig = FunctionConfig Nothing Nothing emptyFunctionCustomRootFields Nothing Nothing
|
2020-11-18 21:04:57 +03:00
|
|
|
|
2022-12-05 13:20:47 +03:00
|
|
|
type DBFunctionsMetadata b = HashMap (FunctionName b) (FunctionOverloads b)
|
|
|
|
|
|
|
|
newtype FunctionOverloads b = FunctionOverloads {getFunctionOverloads :: NonEmpty (RawFunctionInfo b)}
|
|
|
|
|
|
|
|
deriving newtype instance Backend b => Eq (FunctionOverloads b)
|
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
deriving newtype instance Backend b => Show (FunctionOverloads b)
|
|
|
|
|
2022-12-05 13:20:47 +03:00
|
|
|
deriving newtype instance FromJSON (RawFunctionInfo b) => FromJSON (FunctionOverloads b)
|
2021-01-29 08:48:17 +03:00
|
|
|
|
2022-05-25 13:24:41 +03:00
|
|
|
data FunctionArgsExpG a = FunctionArgsExp
|
|
|
|
{ _faePositional :: [a],
|
2023-04-26 18:42:13 +03:00
|
|
|
_faeNamed :: (HashMap.HashMap Text a)
|
2022-05-25 13:24:41 +03:00
|
|
|
}
|
|
|
|
deriving stock (Show, Eq, Functor, Foldable, Traversable, Generic)
|
|
|
|
|
|
|
|
instance (Hashable a) => Hashable (FunctionArgsExpG a)
|
|
|
|
|
|
|
|
instance (NFData a) => NFData (FunctionArgsExpG a)
|
|
|
|
|
|
|
|
type FunctionArgsExp b v = FunctionArgsExpG (FunctionArgumentExp b v)
|
|
|
|
|
|
|
|
emptyFunctionArgsExp :: FunctionArgsExpG a
|
2023-04-26 18:42:13 +03:00
|
|
|
emptyFunctionArgsExp = FunctionArgsExp [] HashMap.empty
|