{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
module Hasura.RQL.Types.Permission
( DelPerm (..),
DelPermDef,
InsPerm (..),
InsPermDef,
ValidateInput (..),
ValidateInputHttpDefinition (..),
PermColSpec (..),
PermDef (..),
PermType (..),
SelPerm (..),
SelPermDef,
UpdPerm (..),
UpdPermDef,
pdComment,
pdPermission,
pdRole,
permTypeToCode,
PermDefPermission (..),
unPermDefPermission,
reflectPermDefPermission,
SubscriptionRootFieldType (..),
QueryRootFieldType (..),
AllowedRootFields (..),
isRootFieldAllowed,
)
where
import Autodocodec hiding (object, (.=))
import Autodocodec qualified as AC
import Autodocodec.Extended (optionalFieldOrIncludedNull', typeableName)
import Control.Lens (makeLenses)
import Data.Aeson
import Data.Aeson.Casing (snakeCase)
import Data.HashSet qualified as Set
import Data.Hashable
import Data.Kind (Type)
import Data.List.NonEmpty qualified as NonEmpty
import Data.Text qualified as T
import Data.Typeable (Typeable)
import Database.PG.Query qualified as PG
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.BackendTag (backendPrefix)
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Headers
import Hasura.RQL.Types.Roles (RoleName)
import PostgreSQL.Binary.Decoding qualified as PD
data PermType
= PTInsert
| PTSelect
| PTUpdate
| PTDelete
deriving (PermType -> PermType -> Bool
(PermType -> PermType -> Bool)
-> (PermType -> PermType -> Bool) -> Eq PermType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PermType -> PermType -> Bool
== :: PermType -> PermType -> Bool
$c/= :: PermType -> PermType -> Bool
/= :: PermType -> PermType -> Bool
Eq, Eq PermType
Eq PermType
-> (PermType -> PermType -> Ordering)
-> (PermType -> PermType -> Bool)
-> (PermType -> PermType -> Bool)
-> (PermType -> PermType -> Bool)
-> (PermType -> PermType -> Bool)
-> (PermType -> PermType -> PermType)
-> (PermType -> PermType -> PermType)
-> Ord PermType
PermType -> PermType -> Bool
PermType -> PermType -> Ordering
PermType -> PermType -> PermType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PermType -> PermType -> Ordering
compare :: PermType -> PermType -> Ordering
$c< :: PermType -> PermType -> Bool
< :: PermType -> PermType -> Bool
$c<= :: PermType -> PermType -> Bool
<= :: PermType -> PermType -> Bool
$c> :: PermType -> PermType -> Bool
> :: PermType -> PermType -> Bool
$c>= :: PermType -> PermType -> Bool
>= :: PermType -> PermType -> Bool
$cmax :: PermType -> PermType -> PermType
max :: PermType -> PermType -> PermType
$cmin :: PermType -> PermType -> PermType
min :: PermType -> PermType -> PermType
Ord, (forall x. PermType -> Rep PermType x)
-> (forall x. Rep PermType x -> PermType) -> Generic PermType
forall x. Rep PermType x -> PermType
forall x. PermType -> Rep PermType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PermType -> Rep PermType x
from :: forall x. PermType -> Rep PermType x
$cto :: forall x. Rep PermType x -> PermType
to :: forall x. Rep PermType x -> PermType
Generic)
instance NFData PermType
instance Hashable PermType
instance PG.FromCol PermType where
fromCol :: Maybe ByteString -> Either Text PermType
fromCol Maybe ByteString
bs = (Value PermType -> Maybe ByteString -> Either Text PermType)
-> Maybe ByteString -> Value PermType -> Either Text PermType
forall a b c. (a -> b -> c) -> b -> a -> c
flip Value PermType -> Maybe ByteString -> Either Text PermType
forall a. Value a -> Maybe ByteString -> Either Text a
PG.fromColHelper Maybe ByteString
bs
(Value PermType -> Either Text PermType)
-> Value PermType -> Either Text PermType
forall a b. (a -> b) -> a -> b
$ (Text -> Maybe PermType) -> Value PermType
forall a. (Text -> Maybe a) -> Value a
PD.enum
((Text -> Maybe PermType) -> Value PermType)
-> (Text -> Maybe PermType) -> Value PermType
forall a b. (a -> b) -> a -> b
$ \case
Text
"insert" -> PermType -> Maybe PermType
forall a. a -> Maybe a
Just PermType
PTInsert
Text
"update" -> PermType -> Maybe PermType
forall a. a -> Maybe a
Just PermType
PTUpdate
Text
"select" -> PermType -> Maybe PermType
forall a. a -> Maybe a
Just PermType
PTSelect
Text
"delete" -> PermType -> Maybe PermType
forall a. a -> Maybe a
Just PermType
PTDelete
Text
_ -> Maybe PermType
forall a. Maybe a
Nothing
permTypeToCode :: PermType -> Text
permTypeToCode :: PermType -> Text
permTypeToCode = PermType -> Text
forall a. Show a => a -> Text
tshow
instance Show PermType where
show :: PermType -> String
show PermType
PTInsert = String
"insert"
show PermType
PTSelect = String
"select"
show PermType
PTUpdate = String
"update"
show PermType
PTDelete = String
"delete"
instance FromJSON PermType where
parseJSON :: Value -> Parser PermType
parseJSON (String Text
"insert") = PermType -> Parser PermType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return PermType
PTInsert
parseJSON (String Text
"select") = PermType -> Parser PermType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return PermType
PTSelect
parseJSON (String Text
"update") = PermType -> Parser PermType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return PermType
PTUpdate
parseJSON (String Text
"delete") = PermType -> Parser PermType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return PermType
PTDelete
parseJSON Value
_ =
String -> Parser PermType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"perm_type should be one of 'insert', 'select', 'update', 'delete'"
instance ToJSON PermType where
toJSON :: PermType -> Value
toJSON = Text -> Value
String (Text -> Value) -> (PermType -> Text) -> PermType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PermType -> Text
permTypeToCode
data PermColSpec b
= PCStar
| PCCols [Column b]
deriving ((forall x. PermColSpec b -> Rep (PermColSpec b) x)
-> (forall x. Rep (PermColSpec b) x -> PermColSpec b)
-> Generic (PermColSpec b)
forall x. Rep (PermColSpec b) x -> PermColSpec b
forall x. PermColSpec b -> Rep (PermColSpec b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x. Rep (PermColSpec b) x -> PermColSpec b
forall (b :: BackendType) x. PermColSpec b -> Rep (PermColSpec b) x
$cfrom :: forall (b :: BackendType) x. PermColSpec b -> Rep (PermColSpec b) x
from :: forall x. PermColSpec b -> Rep (PermColSpec b) x
$cto :: forall (b :: BackendType) x. Rep (PermColSpec b) x -> PermColSpec b
to :: forall x. Rep (PermColSpec b) x -> PermColSpec b
Generic)
deriving instance (Backend b) => Show (PermColSpec b)
deriving instance (Backend b) => Eq (PermColSpec b)
instance (Backend b) => HasCodec (PermColSpec b) where
codec :: JSONCodec (PermColSpec b)
codec =
(Either Text [Column b] -> PermColSpec b)
-> (PermColSpec b -> Either Text [Column b])
-> Codec Value (Either Text [Column b]) (Either Text [Column b])
-> JSONCodec (PermColSpec b)
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec
((Text -> PermColSpec b)
-> ([Column b] -> PermColSpec b)
-> Either Text [Column b]
-> PermColSpec b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (PermColSpec b -> Text -> PermColSpec b
forall a b. a -> b -> a
const PermColSpec b
forall (b :: BackendType). PermColSpec b
PCStar) [Column b] -> PermColSpec b
forall (b :: BackendType). [Column b] -> PermColSpec b
PCCols)
(\case PermColSpec b
PCStar -> Text -> Either Text [Column b]
forall a b. a -> Either a b
Left Text
"*"; PCCols [Column b]
cols -> [Column b] -> Either Text [Column b]
forall a b. b -> Either a b
Right [Column b]
cols)
(Codec Value (Either Text [Column b]) (Either Text [Column b])
-> JSONCodec (PermColSpec b))
-> Codec Value (Either Text [Column b]) (Either Text [Column b])
-> JSONCodec (PermColSpec b)
forall a b. (a -> b) -> a -> b
$ Codec Value Text Text
-> Codec Value [Column b] [Column b]
-> Codec Value (Either Text [Column b]) (Either Text [Column b])
forall context input1 output1 input2 output2.
Codec context input1 output1
-> Codec context input2 output2
-> Codec context (Either input1 input2) (Either output1 output2)
disjointEitherCodec (Text -> Codec Value Text Text
literalTextCodec Text
"*") (ValueCodec (Column b) (Column b)
-> Codec Value [Column b] [Column b]
forall input output.
ValueCodec input output -> ValueCodec [input] [output]
listCodec (ValueCodec (Column b) (Column b)
-> Codec Value [Column b] [Column b])
-> ValueCodec (Column b) (Column b)
-> Codec Value [Column b] [Column b]
forall a b. (a -> b) -> a -> b
$ forall value. HasCodec value => JSONCodec value
codec @(Column b))
instance (Backend b) => FromJSON (PermColSpec b) where
parseJSON :: Value -> Parser (PermColSpec b)
parseJSON (String Text
"*") = PermColSpec b -> Parser (PermColSpec b)
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return PermColSpec b
forall (b :: BackendType). PermColSpec b
PCStar
parseJSON Value
x = [Column b] -> PermColSpec b
forall (b :: BackendType). [Column b] -> PermColSpec b
PCCols ([Column b] -> PermColSpec b)
-> Parser [Column b] -> Parser (PermColSpec b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [Column b]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
x
instance (Backend b) => ToJSON (PermColSpec b) where
toJSON :: PermColSpec b -> Value
toJSON (PCCols [Column b]
cols) = [Column b] -> Value
forall a. ToJSON a => a -> Value
toJSON [Column b]
cols
toJSON PermColSpec b
PCStar = Value
"*"
data PermDef (b :: BackendType) (perm :: BackendType -> Type) = PermDef
{ forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> RoleName
_pdRole :: RoleName,
forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> PermDefPermission b perm
_pdPermission :: PermDefPermission b perm,
:: Maybe T.Text
}
deriving (Int -> PermDef b perm -> ShowS
[PermDef b perm] -> ShowS
PermDef b perm -> String
(Int -> PermDef b perm -> ShowS)
-> (PermDef b perm -> String)
-> ([PermDef b perm] -> ShowS)
-> Show (PermDef b perm)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType) (perm :: BackendType -> *).
Backend b =>
Int -> PermDef b perm -> ShowS
forall (b :: BackendType) (perm :: BackendType -> *).
Backend b =>
[PermDef b perm] -> ShowS
forall (b :: BackendType) (perm :: BackendType -> *).
Backend b =>
PermDef b perm -> String
$cshowsPrec :: forall (b :: BackendType) (perm :: BackendType -> *).
Backend b =>
Int -> PermDef b perm -> ShowS
showsPrec :: Int -> PermDef b perm -> ShowS
$cshow :: forall (b :: BackendType) (perm :: BackendType -> *).
Backend b =>
PermDef b perm -> String
show :: PermDef b perm -> String
$cshowList :: forall (b :: BackendType) (perm :: BackendType -> *).
Backend b =>
[PermDef b perm] -> ShowS
showList :: [PermDef b perm] -> ShowS
Show, PermDef b perm -> PermDef b perm -> Bool
(PermDef b perm -> PermDef b perm -> Bool)
-> (PermDef b perm -> PermDef b perm -> Bool)
-> Eq (PermDef b perm)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType) (perm :: BackendType -> *).
Backend b =>
PermDef b perm -> PermDef b perm -> Bool
$c== :: forall (b :: BackendType) (perm :: BackendType -> *).
Backend b =>
PermDef b perm -> PermDef b perm -> Bool
== :: PermDef b perm -> PermDef b perm -> Bool
$c/= :: forall (b :: BackendType) (perm :: BackendType -> *).
Backend b =>
PermDef b perm -> PermDef b perm -> Bool
/= :: PermDef b perm -> PermDef b perm -> Bool
Eq, (forall x. PermDef b perm -> Rep (PermDef b perm) x)
-> (forall x. Rep (PermDef b perm) x -> PermDef b perm)
-> Generic (PermDef b perm)
forall x. Rep (PermDef b perm) x -> PermDef b perm
forall x. PermDef b perm -> Rep (PermDef b perm) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) (perm :: BackendType -> *) x.
Rep (PermDef b perm) x -> PermDef b perm
forall (b :: BackendType) (perm :: BackendType -> *) x.
PermDef b perm -> Rep (PermDef b perm) x
$cfrom :: forall (b :: BackendType) (perm :: BackendType -> *) x.
PermDef b perm -> Rep (PermDef b perm) x
from :: forall x. PermDef b perm -> Rep (PermDef b perm) x
$cto :: forall (b :: BackendType) (perm :: BackendType -> *) x.
Rep (PermDef b perm) x -> PermDef b perm
to :: forall x. Rep (PermDef b perm) x -> PermDef b perm
Generic)
data PermDefPermission (b :: BackendType) (perm :: BackendType -> Type) where
SelPerm' :: SelPerm b -> PermDefPermission b SelPerm
InsPerm' :: InsPerm b -> PermDefPermission b InsPerm
UpdPerm' :: UpdPerm b -> PermDefPermission b UpdPerm
DelPerm' :: DelPerm b -> PermDefPermission b DelPerm
instance (Backend b) => FromJSON (PermDefPermission b SelPerm) where
parseJSON :: Value -> Parser (PermDefPermission b SelPerm)
parseJSON = (SelPerm b -> PermDefPermission b SelPerm)
-> Parser (SelPerm b) -> Parser (PermDefPermission b SelPerm)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SelPerm b -> PermDefPermission b SelPerm
forall (b :: BackendType). SelPerm b -> PermDefPermission b SelPerm
SelPerm' (Parser (SelPerm b) -> Parser (PermDefPermission b SelPerm))
-> (Value -> Parser (SelPerm b))
-> Value
-> Parser (PermDefPermission b SelPerm)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (SelPerm b)
forall a. FromJSON a => Value -> Parser a
parseJSON
instance (Backend b) => FromJSON (PermDefPermission b InsPerm) where
parseJSON :: Value -> Parser (PermDefPermission b InsPerm)
parseJSON = (InsPerm b -> PermDefPermission b InsPerm)
-> Parser (InsPerm b) -> Parser (PermDefPermission b InsPerm)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap InsPerm b -> PermDefPermission b InsPerm
forall (b :: BackendType). InsPerm b -> PermDefPermission b InsPerm
InsPerm' (Parser (InsPerm b) -> Parser (PermDefPermission b InsPerm))
-> (Value -> Parser (InsPerm b))
-> Value
-> Parser (PermDefPermission b InsPerm)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (InsPerm b)
forall a. FromJSON a => Value -> Parser a
parseJSON
instance (Backend b) => FromJSON (PermDefPermission b UpdPerm) where
parseJSON :: Value -> Parser (PermDefPermission b UpdPerm)
parseJSON = (UpdPerm b -> PermDefPermission b UpdPerm)
-> Parser (UpdPerm b) -> Parser (PermDefPermission b UpdPerm)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UpdPerm b -> PermDefPermission b UpdPerm
forall (b :: BackendType). UpdPerm b -> PermDefPermission b UpdPerm
UpdPerm' (Parser (UpdPerm b) -> Parser (PermDefPermission b UpdPerm))
-> (Value -> Parser (UpdPerm b))
-> Value
-> Parser (PermDefPermission b UpdPerm)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (UpdPerm b)
forall a. FromJSON a => Value -> Parser a
parseJSON
instance (Backend b) => FromJSON (PermDefPermission b DelPerm) where
parseJSON :: Value -> Parser (PermDefPermission b DelPerm)
parseJSON = (DelPerm b -> PermDefPermission b DelPerm)
-> Parser (DelPerm b) -> Parser (PermDefPermission b DelPerm)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DelPerm b -> PermDefPermission b DelPerm
forall (b :: BackendType). DelPerm b -> PermDefPermission b DelPerm
DelPerm' (Parser (DelPerm b) -> Parser (PermDefPermission b DelPerm))
-> (Value -> Parser (DelPerm b))
-> Value
-> Parser (PermDefPermission b DelPerm)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (DelPerm b)
forall a. FromJSON a => Value -> Parser a
parseJSON
instance (Backend b) => ToJSON (PermDefPermission b perm) where
toJSON :: PermDefPermission b perm -> Value
toJSON = \case
SelPerm' SelPerm b
p -> SelPerm b -> Value
forall a. ToJSON a => a -> Value
toJSON SelPerm b
p
InsPerm' InsPerm b
p -> InsPerm b -> Value
forall a. ToJSON a => a -> Value
toJSON InsPerm b
p
UpdPerm' UpdPerm b
p -> UpdPerm b -> Value
forall a. ToJSON a => a -> Value
toJSON UpdPerm b
p
DelPerm' DelPerm b
p -> DelPerm b -> Value
forall a. ToJSON a => a -> Value
toJSON DelPerm b
p
instance (Backend b, HasCodec (perm b), IsPerm perm) => HasCodec (PermDefPermission b perm) where
codec :: JSONCodec (PermDefPermission b perm)
codec = (perm b -> PermDefPermission b perm)
-> (PermDefPermission b perm -> perm b)
-> Codec Value (perm b) (perm b)
-> JSONCodec (PermDefPermission b perm)
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec perm b -> PermDefPermission b perm
forall (b :: BackendType). perm b -> PermDefPermission b perm
forall (perm :: BackendType -> *) (b :: BackendType).
IsPerm perm =>
perm b -> PermDefPermission b perm
mkPermDefPermission PermDefPermission b perm -> perm b
forall (b :: BackendType) (perm :: BackendType -> *).
PermDefPermission b perm -> perm b
unPermDefPermission Codec Value (perm b) (perm b)
forall value. HasCodec value => JSONCodec value
codec
deriving stock instance (Backend b) => Show (PermDefPermission b perm)
deriving stock instance (Backend b) => Eq (PermDefPermission b perm)
class IsPerm perm where
mkPermDefPermission :: perm b -> PermDefPermission b perm
permType :: PermType
instance IsPerm SelPerm where
mkPermDefPermission :: forall (b :: BackendType). SelPerm b -> PermDefPermission b SelPerm
mkPermDefPermission = SelPerm b -> PermDefPermission b SelPerm
forall (b :: BackendType). SelPerm b -> PermDefPermission b SelPerm
SelPerm'
permType :: PermType
permType = PermType
PTSelect
instance IsPerm InsPerm where
mkPermDefPermission :: forall (b :: BackendType). InsPerm b -> PermDefPermission b InsPerm
mkPermDefPermission = InsPerm b -> PermDefPermission b InsPerm
forall (b :: BackendType). InsPerm b -> PermDefPermission b InsPerm
InsPerm'
permType :: PermType
permType = PermType
PTInsert
instance IsPerm UpdPerm where
mkPermDefPermission :: forall (b :: BackendType). UpdPerm b -> PermDefPermission b UpdPerm
mkPermDefPermission = UpdPerm b -> PermDefPermission b UpdPerm
forall (b :: BackendType). UpdPerm b -> PermDefPermission b UpdPerm
UpdPerm'
permType :: PermType
permType = PermType
PTUpdate
instance IsPerm DelPerm where
mkPermDefPermission :: forall (b :: BackendType). DelPerm b -> PermDefPermission b DelPerm
mkPermDefPermission = DelPerm b -> PermDefPermission b DelPerm
forall (b :: BackendType). DelPerm b -> PermDefPermission b DelPerm
DelPerm'
permType :: PermType
permType = PermType
PTDelete
unPermDefPermission :: PermDefPermission b perm -> perm b
unPermDefPermission :: forall (b :: BackendType) (perm :: BackendType -> *).
PermDefPermission b perm -> perm b
unPermDefPermission = \case
SelPerm' SelPerm b
p -> perm b
SelPerm b
p
InsPerm' InsPerm b
p -> perm b
InsPerm b
p
UpdPerm' UpdPerm b
p -> perm b
UpdPerm b
p
DelPerm' DelPerm b
p -> perm b
DelPerm b
p
reflectPermDefPermission :: PermDefPermission b a -> PermType
reflectPermDefPermission :: forall (b :: BackendType) (a :: BackendType -> *).
PermDefPermission b a -> PermType
reflectPermDefPermission = \case
SelPerm' SelPerm b
_ -> PermType
PTSelect
InsPerm' InsPerm b
_ -> PermType
PTInsert
UpdPerm' UpdPerm b
_ -> PermType
PTUpdate
DelPerm' DelPerm b
_ -> PermType
PTDelete
instance (Backend b, ToJSON (perm b)) => ToJSON (PermDef b perm) where
toJSON :: PermDef b perm -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (PermDef b perm -> [Pair]) -> PermDef b perm -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PermDef b perm -> [Pair]
forall v. KeyValue v => PermDef b perm -> [v]
forall a v. (ToAesonPairs a, KeyValue v) => a -> [v]
toAesonPairs
instance (Backend b) => ToAesonPairs (PermDef b perm) where
toAesonPairs :: forall v. KeyValue v => PermDef b perm -> [v]
toAesonPairs (PermDef RoleName
rn PermDefPermission b perm
perm Maybe Text
comment) =
[ Key
"role" Key -> RoleName -> v
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> v
.= RoleName
rn,
Key
"permission" Key -> PermDefPermission b perm -> v
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> v
.= PermDefPermission b perm
perm,
Key
"comment" Key -> Maybe Text -> v
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> v
.= Maybe Text
comment
]
instance (Backend b, HasCodec (perm b), IsPerm perm) => HasCodec (PermDef b perm) where
codec :: JSONCodec (PermDef b perm)
codec =
Text
-> ObjectCodec (PermDef b perm) (PermDef b perm)
-> JSONCodec (PermDef b perm)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
T.toTitle (PermType -> Text
permTypeToCode (forall (perm :: BackendType -> *). IsPerm perm => PermType
permType @perm)) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"PermDef")
(ObjectCodec (PermDef b perm) (PermDef b perm)
-> JSONCodec (PermDef b perm))
-> ObjectCodec (PermDef b perm) (PermDef b perm)
-> JSONCodec (PermDef b perm)
forall a b. (a -> b) -> a -> b
$ RoleName
-> PermDefPermission b perm -> Maybe Text -> PermDef b perm
forall (b :: BackendType) (perm :: BackendType -> *).
RoleName
-> PermDefPermission b perm -> Maybe Text -> PermDef b perm
PermDef
(RoleName
-> PermDefPermission b perm -> Maybe Text -> PermDef b perm)
-> Codec Object (PermDef b perm) RoleName
-> Codec
Object
(PermDef b perm)
(PermDefPermission b perm -> Maybe Text -> PermDef b perm)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec RoleName RoleName
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"role"
ObjectCodec RoleName RoleName
-> (PermDef b perm -> RoleName)
-> Codec Object (PermDef b perm) RoleName
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.== PermDef b perm -> RoleName
forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> RoleName
_pdRole
Codec
Object
(PermDef b perm)
(PermDefPermission b perm -> Maybe Text -> PermDef b perm)
-> Codec Object (PermDef b perm) (PermDefPermission b perm)
-> Codec Object (PermDef b perm) (Maybe Text -> PermDef b perm)
forall a b.
Codec Object (PermDef b perm) (a -> b)
-> Codec Object (PermDef b perm) a
-> Codec Object (PermDef b perm) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(PermDefPermission b perm) (PermDefPermission b perm)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"permission"
ObjectCodec (PermDefPermission b perm) (PermDefPermission b perm)
-> (PermDef b perm -> PermDefPermission b perm)
-> Codec Object (PermDef b perm) (PermDefPermission b perm)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.== PermDef b perm -> PermDefPermission b perm
forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> PermDefPermission b perm
_pdPermission
Codec Object (PermDef b perm) (Maybe Text -> PermDef b perm)
-> Codec Object (PermDef b perm) (Maybe Text)
-> ObjectCodec (PermDef b perm) (PermDef b perm)
forall a b.
Codec Object (PermDef b perm) (a -> b)
-> Codec Object (PermDef b perm) a
-> Codec Object (PermDef b perm) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalFieldOrNull' Text
"comment"
ObjectCodec (Maybe Text) (Maybe Text)
-> (PermDef b perm -> Maybe Text)
-> Codec Object (PermDef b perm) (Maybe Text)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.== PermDef b perm -> Maybe Text
forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> Maybe Text
_pdComment
where
.== :: ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
(.==) = ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
(AC..=)
data QueryRootFieldType
= QRFTSelect
| QRFTSelectByPk
| QRFTSelectAggregate
deriving stock (Int -> QueryRootFieldType -> ShowS
[QueryRootFieldType] -> ShowS
QueryRootFieldType -> String
(Int -> QueryRootFieldType -> ShowS)
-> (QueryRootFieldType -> String)
-> ([QueryRootFieldType] -> ShowS)
-> Show QueryRootFieldType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QueryRootFieldType -> ShowS
showsPrec :: Int -> QueryRootFieldType -> ShowS
$cshow :: QueryRootFieldType -> String
show :: QueryRootFieldType -> String
$cshowList :: [QueryRootFieldType] -> ShowS
showList :: [QueryRootFieldType] -> ShowS
Show, QueryRootFieldType -> QueryRootFieldType -> Bool
(QueryRootFieldType -> QueryRootFieldType -> Bool)
-> (QueryRootFieldType -> QueryRootFieldType -> Bool)
-> Eq QueryRootFieldType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QueryRootFieldType -> QueryRootFieldType -> Bool
== :: QueryRootFieldType -> QueryRootFieldType -> Bool
$c/= :: QueryRootFieldType -> QueryRootFieldType -> Bool
/= :: QueryRootFieldType -> QueryRootFieldType -> Bool
Eq, (forall x. QueryRootFieldType -> Rep QueryRootFieldType x)
-> (forall x. Rep QueryRootFieldType x -> QueryRootFieldType)
-> Generic QueryRootFieldType
forall x. Rep QueryRootFieldType x -> QueryRootFieldType
forall x. QueryRootFieldType -> Rep QueryRootFieldType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. QueryRootFieldType -> Rep QueryRootFieldType x
from :: forall x. QueryRootFieldType -> Rep QueryRootFieldType x
$cto :: forall x. Rep QueryRootFieldType x -> QueryRootFieldType
to :: forall x. Rep QueryRootFieldType x -> QueryRootFieldType
Generic, Int -> QueryRootFieldType
QueryRootFieldType -> Int
QueryRootFieldType -> [QueryRootFieldType]
QueryRootFieldType -> QueryRootFieldType
QueryRootFieldType -> QueryRootFieldType -> [QueryRootFieldType]
QueryRootFieldType
-> QueryRootFieldType -> QueryRootFieldType -> [QueryRootFieldType]
(QueryRootFieldType -> QueryRootFieldType)
-> (QueryRootFieldType -> QueryRootFieldType)
-> (Int -> QueryRootFieldType)
-> (QueryRootFieldType -> Int)
-> (QueryRootFieldType -> [QueryRootFieldType])
-> (QueryRootFieldType
-> QueryRootFieldType -> [QueryRootFieldType])
-> (QueryRootFieldType
-> QueryRootFieldType -> [QueryRootFieldType])
-> (QueryRootFieldType
-> QueryRootFieldType
-> QueryRootFieldType
-> [QueryRootFieldType])
-> Enum QueryRootFieldType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: QueryRootFieldType -> QueryRootFieldType
succ :: QueryRootFieldType -> QueryRootFieldType
$cpred :: QueryRootFieldType -> QueryRootFieldType
pred :: QueryRootFieldType -> QueryRootFieldType
$ctoEnum :: Int -> QueryRootFieldType
toEnum :: Int -> QueryRootFieldType
$cfromEnum :: QueryRootFieldType -> Int
fromEnum :: QueryRootFieldType -> Int
$cenumFrom :: QueryRootFieldType -> [QueryRootFieldType]
enumFrom :: QueryRootFieldType -> [QueryRootFieldType]
$cenumFromThen :: QueryRootFieldType -> QueryRootFieldType -> [QueryRootFieldType]
enumFromThen :: QueryRootFieldType -> QueryRootFieldType -> [QueryRootFieldType]
$cenumFromTo :: QueryRootFieldType -> QueryRootFieldType -> [QueryRootFieldType]
enumFromTo :: QueryRootFieldType -> QueryRootFieldType -> [QueryRootFieldType]
$cenumFromThenTo :: QueryRootFieldType
-> QueryRootFieldType -> QueryRootFieldType -> [QueryRootFieldType]
enumFromThenTo :: QueryRootFieldType
-> QueryRootFieldType -> QueryRootFieldType -> [QueryRootFieldType]
Enum, QueryRootFieldType
QueryRootFieldType
-> QueryRootFieldType -> Bounded QueryRootFieldType
forall a. a -> a -> Bounded a
$cminBound :: QueryRootFieldType
minBound :: QueryRootFieldType
$cmaxBound :: QueryRootFieldType
maxBound :: QueryRootFieldType
Bounded)
deriving anyclass (Eq QueryRootFieldType
Eq QueryRootFieldType
-> (Int -> QueryRootFieldType -> Int)
-> (QueryRootFieldType -> Int)
-> Hashable QueryRootFieldType
Int -> QueryRootFieldType -> Int
QueryRootFieldType -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> QueryRootFieldType -> Int
hashWithSalt :: Int -> QueryRootFieldType -> Int
$chash :: QueryRootFieldType -> Int
hash :: QueryRootFieldType -> Int
Hashable, QueryRootFieldType -> ()
(QueryRootFieldType -> ()) -> NFData QueryRootFieldType
forall a. (a -> ()) -> NFData a
$crnf :: QueryRootFieldType -> ()
rnf :: QueryRootFieldType -> ()
NFData)
instance FromJSON QueryRootFieldType where
parseJSON :: Value -> Parser QueryRootFieldType
parseJSON = Options -> Value -> Parser QueryRootFieldType
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions {constructorTagModifier :: ShowS
constructorTagModifier = ShowS
snakeCase ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
4}
instance ToJSON QueryRootFieldType where
toJSON :: QueryRootFieldType -> Value
toJSON = Options -> QueryRootFieldType -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions {constructorTagModifier :: ShowS
constructorTagModifier = ShowS
snakeCase ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
4}
instance HasCodec QueryRootFieldType where
codec :: JSONCodec QueryRootFieldType
codec =
NonEmpty (QueryRootFieldType, Text) -> JSONCodec QueryRootFieldType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec
(NonEmpty (QueryRootFieldType, Text)
-> JSONCodec QueryRootFieldType)
-> NonEmpty (QueryRootFieldType, Text)
-> JSONCodec QueryRootFieldType
forall a b. (a -> b) -> a -> b
$ [(QueryRootFieldType, Text)] -> NonEmpty (QueryRootFieldType, Text)
forall a. HasCallStack => [a] -> NonEmpty a
NonEmpty.fromList
([(QueryRootFieldType, Text)]
-> NonEmpty (QueryRootFieldType, Text))
-> [(QueryRootFieldType, Text)]
-> NonEmpty (QueryRootFieldType, Text)
forall a b. (a -> b) -> a -> b
$ (\QueryRootFieldType
x -> (QueryRootFieldType
x, String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS
snakeCase ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
4 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ QueryRootFieldType -> String
forall a. Show a => a -> String
show QueryRootFieldType
x))
(QueryRootFieldType -> (QueryRootFieldType, Text))
-> [QueryRootFieldType] -> [(QueryRootFieldType, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [QueryRootFieldType
forall a. Bounded a => a
minBound ..]
data SubscriptionRootFieldType
= SRFTSelect
| SRFTSelectByPk
| SRFTSelectAggregate
| SRFTSelectStream
deriving stock (Int -> SubscriptionRootFieldType -> ShowS
[SubscriptionRootFieldType] -> ShowS
SubscriptionRootFieldType -> String
(Int -> SubscriptionRootFieldType -> ShowS)
-> (SubscriptionRootFieldType -> String)
-> ([SubscriptionRootFieldType] -> ShowS)
-> Show SubscriptionRootFieldType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionRootFieldType -> ShowS
showsPrec :: Int -> SubscriptionRootFieldType -> ShowS
$cshow :: SubscriptionRootFieldType -> String
show :: SubscriptionRootFieldType -> String
$cshowList :: [SubscriptionRootFieldType] -> ShowS
showList :: [SubscriptionRootFieldType] -> ShowS
Show, SubscriptionRootFieldType -> SubscriptionRootFieldType -> Bool
(SubscriptionRootFieldType -> SubscriptionRootFieldType -> Bool)
-> (SubscriptionRootFieldType -> SubscriptionRootFieldType -> Bool)
-> Eq SubscriptionRootFieldType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionRootFieldType -> SubscriptionRootFieldType -> Bool
== :: SubscriptionRootFieldType -> SubscriptionRootFieldType -> Bool
$c/= :: SubscriptionRootFieldType -> SubscriptionRootFieldType -> Bool
/= :: SubscriptionRootFieldType -> SubscriptionRootFieldType -> Bool
Eq, (forall x.
SubscriptionRootFieldType -> Rep SubscriptionRootFieldType x)
-> (forall x.
Rep SubscriptionRootFieldType x -> SubscriptionRootFieldType)
-> Generic SubscriptionRootFieldType
forall x.
Rep SubscriptionRootFieldType x -> SubscriptionRootFieldType
forall x.
SubscriptionRootFieldType -> Rep SubscriptionRootFieldType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SubscriptionRootFieldType -> Rep SubscriptionRootFieldType x
from :: forall x.
SubscriptionRootFieldType -> Rep SubscriptionRootFieldType x
$cto :: forall x.
Rep SubscriptionRootFieldType x -> SubscriptionRootFieldType
to :: forall x.
Rep SubscriptionRootFieldType x -> SubscriptionRootFieldType
Generic, Int -> SubscriptionRootFieldType
SubscriptionRootFieldType -> Int
SubscriptionRootFieldType -> [SubscriptionRootFieldType]
SubscriptionRootFieldType -> SubscriptionRootFieldType
SubscriptionRootFieldType
-> SubscriptionRootFieldType -> [SubscriptionRootFieldType]
SubscriptionRootFieldType
-> SubscriptionRootFieldType
-> SubscriptionRootFieldType
-> [SubscriptionRootFieldType]
(SubscriptionRootFieldType -> SubscriptionRootFieldType)
-> (SubscriptionRootFieldType -> SubscriptionRootFieldType)
-> (Int -> SubscriptionRootFieldType)
-> (SubscriptionRootFieldType -> Int)
-> (SubscriptionRootFieldType -> [SubscriptionRootFieldType])
-> (SubscriptionRootFieldType
-> SubscriptionRootFieldType -> [SubscriptionRootFieldType])
-> (SubscriptionRootFieldType
-> SubscriptionRootFieldType -> [SubscriptionRootFieldType])
-> (SubscriptionRootFieldType
-> SubscriptionRootFieldType
-> SubscriptionRootFieldType
-> [SubscriptionRootFieldType])
-> Enum SubscriptionRootFieldType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: SubscriptionRootFieldType -> SubscriptionRootFieldType
succ :: SubscriptionRootFieldType -> SubscriptionRootFieldType
$cpred :: SubscriptionRootFieldType -> SubscriptionRootFieldType
pred :: SubscriptionRootFieldType -> SubscriptionRootFieldType
$ctoEnum :: Int -> SubscriptionRootFieldType
toEnum :: Int -> SubscriptionRootFieldType
$cfromEnum :: SubscriptionRootFieldType -> Int
fromEnum :: SubscriptionRootFieldType -> Int
$cenumFrom :: SubscriptionRootFieldType -> [SubscriptionRootFieldType]
enumFrom :: SubscriptionRootFieldType -> [SubscriptionRootFieldType]
$cenumFromThen :: SubscriptionRootFieldType
-> SubscriptionRootFieldType -> [SubscriptionRootFieldType]
enumFromThen :: SubscriptionRootFieldType
-> SubscriptionRootFieldType -> [SubscriptionRootFieldType]
$cenumFromTo :: SubscriptionRootFieldType
-> SubscriptionRootFieldType -> [SubscriptionRootFieldType]
enumFromTo :: SubscriptionRootFieldType
-> SubscriptionRootFieldType -> [SubscriptionRootFieldType]
$cenumFromThenTo :: SubscriptionRootFieldType
-> SubscriptionRootFieldType
-> SubscriptionRootFieldType
-> [SubscriptionRootFieldType]
enumFromThenTo :: SubscriptionRootFieldType
-> SubscriptionRootFieldType
-> SubscriptionRootFieldType
-> [SubscriptionRootFieldType]
Enum, SubscriptionRootFieldType
SubscriptionRootFieldType
-> SubscriptionRootFieldType -> Bounded SubscriptionRootFieldType
forall a. a -> a -> Bounded a
$cminBound :: SubscriptionRootFieldType
minBound :: SubscriptionRootFieldType
$cmaxBound :: SubscriptionRootFieldType
maxBound :: SubscriptionRootFieldType
Bounded)
deriving anyclass (Eq SubscriptionRootFieldType
Eq SubscriptionRootFieldType
-> (Int -> SubscriptionRootFieldType -> Int)
-> (SubscriptionRootFieldType -> Int)
-> Hashable SubscriptionRootFieldType
Int -> SubscriptionRootFieldType -> Int
SubscriptionRootFieldType -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> SubscriptionRootFieldType -> Int
hashWithSalt :: Int -> SubscriptionRootFieldType -> Int
$chash :: SubscriptionRootFieldType -> Int
hash :: SubscriptionRootFieldType -> Int
Hashable, SubscriptionRootFieldType -> ()
(SubscriptionRootFieldType -> ())
-> NFData SubscriptionRootFieldType
forall a. (a -> ()) -> NFData a
$crnf :: SubscriptionRootFieldType -> ()
rnf :: SubscriptionRootFieldType -> ()
NFData)
instance FromJSON SubscriptionRootFieldType where
parseJSON :: Value -> Parser SubscriptionRootFieldType
parseJSON = Options -> Value -> Parser SubscriptionRootFieldType
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions {constructorTagModifier :: ShowS
constructorTagModifier = ShowS
snakeCase ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
4}
instance ToJSON SubscriptionRootFieldType where
toJSON :: SubscriptionRootFieldType -> Value
toJSON = Options -> SubscriptionRootFieldType -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions {constructorTagModifier :: ShowS
constructorTagModifier = ShowS
snakeCase ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
4}
instance HasCodec SubscriptionRootFieldType where
codec :: JSONCodec SubscriptionRootFieldType
codec =
NonEmpty (SubscriptionRootFieldType, Text)
-> JSONCodec SubscriptionRootFieldType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec
(NonEmpty (SubscriptionRootFieldType, Text)
-> JSONCodec SubscriptionRootFieldType)
-> NonEmpty (SubscriptionRootFieldType, Text)
-> JSONCodec SubscriptionRootFieldType
forall a b. (a -> b) -> a -> b
$ [(SubscriptionRootFieldType, Text)]
-> NonEmpty (SubscriptionRootFieldType, Text)
forall a. HasCallStack => [a] -> NonEmpty a
NonEmpty.fromList
([(SubscriptionRootFieldType, Text)]
-> NonEmpty (SubscriptionRootFieldType, Text))
-> [(SubscriptionRootFieldType, Text)]
-> NonEmpty (SubscriptionRootFieldType, Text)
forall a b. (a -> b) -> a -> b
$ (\SubscriptionRootFieldType
x -> (SubscriptionRootFieldType
x, String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS
snakeCase ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
4 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ SubscriptionRootFieldType -> String
forall a. Show a => a -> String
show SubscriptionRootFieldType
x))
(SubscriptionRootFieldType -> (SubscriptionRootFieldType, Text))
-> [SubscriptionRootFieldType]
-> [(SubscriptionRootFieldType, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SubscriptionRootFieldType
forall a. Bounded a => a
minBound ..]
data InsPerm (b :: BackendType) = InsPerm
{ forall (b :: BackendType). InsPerm b -> BoolExp b
ipCheck :: BoolExp b,
forall (b :: BackendType).
InsPerm b -> Maybe (ColumnValues b Value)
ipSet :: Maybe (ColumnValues b Value),
forall (b :: BackendType). InsPerm b -> Maybe (PermColSpec b)
ipColumns :: Maybe (PermColSpec b),
forall (b :: BackendType). InsPerm b -> Bool
ipBackendOnly :: Bool,
forall (b :: BackendType).
InsPerm b -> Maybe (ValidateInput InputWebhook)
ipValidateInput :: Maybe (ValidateInput InputWebhook)
}
deriving (Int -> InsPerm b -> ShowS
[InsPerm b] -> ShowS
InsPerm b -> String
(Int -> InsPerm b -> ShowS)
-> (InsPerm b -> String)
-> ([InsPerm b] -> ShowS)
-> Show (InsPerm b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType). Backend b => Int -> InsPerm b -> ShowS
forall (b :: BackendType). Backend b => [InsPerm b] -> ShowS
forall (b :: BackendType). Backend b => InsPerm b -> String
$cshowsPrec :: forall (b :: BackendType). Backend b => Int -> InsPerm b -> ShowS
showsPrec :: Int -> InsPerm b -> ShowS
$cshow :: forall (b :: BackendType). Backend b => InsPerm b -> String
show :: InsPerm b -> String
$cshowList :: forall (b :: BackendType). Backend b => [InsPerm b] -> ShowS
showList :: [InsPerm b] -> ShowS
Show, InsPerm b -> InsPerm b -> Bool
(InsPerm b -> InsPerm b -> Bool)
-> (InsPerm b -> InsPerm b -> Bool) -> Eq (InsPerm b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType).
Backend b =>
InsPerm b -> InsPerm b -> Bool
$c== :: forall (b :: BackendType).
Backend b =>
InsPerm b -> InsPerm b -> Bool
== :: InsPerm b -> InsPerm b -> Bool
$c/= :: forall (b :: BackendType).
Backend b =>
InsPerm b -> InsPerm b -> Bool
/= :: InsPerm b -> InsPerm b -> Bool
Eq, (forall x. InsPerm b -> Rep (InsPerm b) x)
-> (forall x. Rep (InsPerm b) x -> InsPerm b)
-> Generic (InsPerm b)
forall x. Rep (InsPerm b) x -> InsPerm b
forall x. InsPerm b -> Rep (InsPerm b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x. Rep (InsPerm b) x -> InsPerm b
forall (b :: BackendType) x. InsPerm b -> Rep (InsPerm b) x
$cfrom :: forall (b :: BackendType) x. InsPerm b -> Rep (InsPerm b) x
from :: forall x. InsPerm b -> Rep (InsPerm b) x
$cto :: forall (b :: BackendType) x. Rep (InsPerm b) x -> InsPerm b
to :: forall x. Rep (InsPerm b) x -> InsPerm b
Generic)
instance (Backend b) => FromJSON (InsPerm b) where
parseJSON :: Value -> Parser (InsPerm b)
parseJSON = String
-> (Object -> Parser (InsPerm b)) -> Value -> Parser (InsPerm b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"InsPerm" ((Object -> Parser (InsPerm b)) -> Value -> Parser (InsPerm b))
-> (Object -> Parser (InsPerm b)) -> Value -> Parser (InsPerm b)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
BoolExp b
-> Maybe (HashMap (Column b) Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b
forall (b :: BackendType).
BoolExp b
-> Maybe (ColumnValues b Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b
InsPerm
(BoolExp b
-> Maybe (HashMap (Column b) Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b)
-> Parser (BoolExp b)
-> Parser
(Maybe (HashMap (Column b) Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser (BoolExp b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"check"
Parser
(Maybe (HashMap (Column b) Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b)
-> Parser (Maybe (HashMap (Column b) Value))
-> Parser
(Maybe (PermColSpec b)
-> Bool -> Maybe (ValidateInput InputWebhook) -> InsPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe (HashMap (Column b) Value))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"set"
Parser
(Maybe (PermColSpec b)
-> Bool -> Maybe (ValidateInput InputWebhook) -> InsPerm b)
-> Parser (Maybe (PermColSpec b))
-> Parser (Bool -> Maybe (ValidateInput InputWebhook) -> InsPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe (PermColSpec b))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"columns"
Parser (Bool -> Maybe (ValidateInput InputWebhook) -> InsPerm b)
-> Parser Bool
-> Parser (Maybe (ValidateInput InputWebhook) -> InsPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"backend_only"
Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Parser (Maybe (ValidateInput InputWebhook) -> InsPerm b)
-> Parser (Maybe (ValidateInput InputWebhook))
-> Parser (InsPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe (ValidateInput InputWebhook))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"validate_input"
instance (Backend b) => ToJSON (InsPerm b) where
toJSON :: InsPerm b -> Value
toJSON = Options -> InsPerm b -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance (Backend b) => HasCodec (InsPerm b) where
codec :: JSONCodec (InsPerm b)
codec =
Text
-> ObjectCodec (InsPerm b) (InsPerm b) -> JSONCodec (InsPerm b)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"InsPerm")
(ObjectCodec (InsPerm b) (InsPerm b) -> JSONCodec (InsPerm b))
-> ObjectCodec (InsPerm b) (InsPerm b) -> JSONCodec (InsPerm b)
forall a b. (a -> b) -> a -> b
$ BoolExp b
-> Maybe (HashMap (Column b) Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b
forall (b :: BackendType).
BoolExp b
-> Maybe (ColumnValues b Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b
InsPerm
(BoolExp b
-> Maybe (HashMap (Column b) Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b)
-> Codec Object (InsPerm b) (BoolExp b)
-> Codec
Object
(InsPerm b)
(Maybe (HashMap (Column b) Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec (BoolExp b) (BoolExp b)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"check"
ObjectCodec (BoolExp b) (BoolExp b)
-> (InsPerm b -> BoolExp b) -> Codec Object (InsPerm b) (BoolExp b)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= InsPerm b -> BoolExp b
forall (b :: BackendType). InsPerm b -> BoolExp b
ipCheck
Codec
Object
(InsPerm b)
(Maybe (HashMap (Column b) Value)
-> Maybe (PermColSpec b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> InsPerm b)
-> Codec Object (InsPerm b) (Maybe (HashMap (Column b) Value))
-> Codec
Object
(InsPerm b)
(Maybe (PermColSpec b)
-> Bool -> Maybe (ValidateInput InputWebhook) -> InsPerm b)
forall a b.
Codec Object (InsPerm b) (a -> b)
-> Codec Object (InsPerm b) a -> Codec Object (InsPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe (HashMap (Column b) Value))
(Maybe (HashMap (Column b) Value))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"set"
ObjectCodec
(Maybe (HashMap (Column b) Value))
(Maybe (HashMap (Column b) Value))
-> (InsPerm b -> Maybe (HashMap (Column b) Value))
-> Codec Object (InsPerm b) (Maybe (HashMap (Column b) Value))
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= InsPerm b -> Maybe (HashMap (Column b) Value)
forall (b :: BackendType).
InsPerm b -> Maybe (ColumnValues b Value)
ipSet
Codec
Object
(InsPerm b)
(Maybe (PermColSpec b)
-> Bool -> Maybe (ValidateInput InputWebhook) -> InsPerm b)
-> Codec Object (InsPerm b) (Maybe (PermColSpec b))
-> Codec
Object
(InsPerm b)
(Bool -> Maybe (ValidateInput InputWebhook) -> InsPerm b)
forall a b.
Codec Object (InsPerm b) (a -> b)
-> Codec Object (InsPerm b) a -> Codec Object (InsPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe (PermColSpec b)) (Maybe (PermColSpec b))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"columns"
ObjectCodec (Maybe (PermColSpec b)) (Maybe (PermColSpec b))
-> (InsPerm b -> Maybe (PermColSpec b))
-> Codec Object (InsPerm b) (Maybe (PermColSpec b))
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= InsPerm b -> Maybe (PermColSpec b)
forall (b :: BackendType). InsPerm b -> Maybe (PermColSpec b)
ipColumns
Codec
Object
(InsPerm b)
(Bool -> Maybe (ValidateInput InputWebhook) -> InsPerm b)
-> Codec Object (InsPerm b) Bool
-> Codec
Object
(InsPerm b)
(Maybe (ValidateInput InputWebhook) -> InsPerm b)
forall a b.
Codec Object (InsPerm b) (a -> b)
-> Codec Object (InsPerm b) a -> Codec Object (InsPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Bool -> ObjectCodec Bool Bool
forall output.
HasCodec output =>
Text -> output -> ObjectCodec output output
optionalFieldWithDefault' Text
"backend_only" Bool
False
ObjectCodec Bool Bool
-> (InsPerm b -> Bool) -> Codec Object (InsPerm b) Bool
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= InsPerm b -> Bool
forall (b :: BackendType). InsPerm b -> Bool
ipBackendOnly
Codec
Object
(InsPerm b)
(Maybe (ValidateInput InputWebhook) -> InsPerm b)
-> Codec Object (InsPerm b) (Maybe (ValidateInput InputWebhook))
-> ObjectCodec (InsPerm b) (InsPerm b)
forall a b.
Codec Object (InsPerm b) (a -> b)
-> Codec Object (InsPerm b) a -> Codec Object (InsPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe (ValidateInput InputWebhook))
(Maybe (ValidateInput InputWebhook))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"validate_input"
ObjectCodec
(Maybe (ValidateInput InputWebhook))
(Maybe (ValidateInput InputWebhook))
-> (InsPerm b -> Maybe (ValidateInput InputWebhook))
-> Codec Object (InsPerm b) (Maybe (ValidateInput InputWebhook))
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= InsPerm b -> Maybe (ValidateInput InputWebhook)
forall (b :: BackendType).
InsPerm b -> Maybe (ValidateInput InputWebhook)
ipValidateInput
type InsPermDef b = PermDef b InsPerm
data AllowedRootFields rootFieldType
= ARFAllowAllRootFields
| ARFAllowConfiguredRootFields (Set.HashSet rootFieldType)
deriving (Int -> AllowedRootFields rootFieldType -> ShowS
[AllowedRootFields rootFieldType] -> ShowS
AllowedRootFields rootFieldType -> String
(Int -> AllowedRootFields rootFieldType -> ShowS)
-> (AllowedRootFields rootFieldType -> String)
-> ([AllowedRootFields rootFieldType] -> ShowS)
-> Show (AllowedRootFields rootFieldType)
forall rootFieldType.
Show rootFieldType =>
Int -> AllowedRootFields rootFieldType -> ShowS
forall rootFieldType.
Show rootFieldType =>
[AllowedRootFields rootFieldType] -> ShowS
forall rootFieldType.
Show rootFieldType =>
AllowedRootFields rootFieldType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall rootFieldType.
Show rootFieldType =>
Int -> AllowedRootFields rootFieldType -> ShowS
showsPrec :: Int -> AllowedRootFields rootFieldType -> ShowS
$cshow :: forall rootFieldType.
Show rootFieldType =>
AllowedRootFields rootFieldType -> String
show :: AllowedRootFields rootFieldType -> String
$cshowList :: forall rootFieldType.
Show rootFieldType =>
[AllowedRootFields rootFieldType] -> ShowS
showList :: [AllowedRootFields rootFieldType] -> ShowS
Show, AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType -> Bool
(AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType -> Bool)
-> (AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType -> Bool)
-> Eq (AllowedRootFields rootFieldType)
forall rootFieldType.
Eq rootFieldType =>
AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall rootFieldType.
Eq rootFieldType =>
AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType -> Bool
== :: AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType -> Bool
$c/= :: forall rootFieldType.
Eq rootFieldType =>
AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType -> Bool
/= :: AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType -> Bool
Eq, (forall x.
AllowedRootFields rootFieldType
-> Rep (AllowedRootFields rootFieldType) x)
-> (forall x.
Rep (AllowedRootFields rootFieldType) x
-> AllowedRootFields rootFieldType)
-> Generic (AllowedRootFields rootFieldType)
forall x.
Rep (AllowedRootFields rootFieldType) x
-> AllowedRootFields rootFieldType
forall x.
AllowedRootFields rootFieldType
-> Rep (AllowedRootFields rootFieldType) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall rootFieldType x.
Rep (AllowedRootFields rootFieldType) x
-> AllowedRootFields rootFieldType
forall rootFieldType x.
AllowedRootFields rootFieldType
-> Rep (AllowedRootFields rootFieldType) x
$cfrom :: forall rootFieldType x.
AllowedRootFields rootFieldType
-> Rep (AllowedRootFields rootFieldType) x
from :: forall x.
AllowedRootFields rootFieldType
-> Rep (AllowedRootFields rootFieldType) x
$cto :: forall rootFieldType x.
Rep (AllowedRootFields rootFieldType) x
-> AllowedRootFields rootFieldType
to :: forall x.
Rep (AllowedRootFields rootFieldType) x
-> AllowedRootFields rootFieldType
Generic)
instance (NFData rootFieldType) => NFData (AllowedRootFields rootFieldType)
instance (ToJSON rootFieldType) => ToJSON (AllowedRootFields rootFieldType) where
toJSON :: AllowedRootFields rootFieldType -> Value
toJSON = \case
AllowedRootFields rootFieldType
ARFAllowAllRootFields -> Text -> Value
String Text
"allow all root fields"
ARFAllowConfiguredRootFields HashSet rootFieldType
configuredRootFields -> HashSet rootFieldType -> Value
forall a. ToJSON a => a -> Value
toJSON HashSet rootFieldType
configuredRootFields
instance (Hashable rootFieldType, HasCodec rootFieldType) => HasCodec (AllowedRootFields rootFieldType) where
codec :: JSONCodec (AllowedRootFields rootFieldType)
codec = (Maybe [rootFieldType] -> AllowedRootFields rootFieldType)
-> (AllowedRootFields rootFieldType -> Maybe [rootFieldType])
-> Codec Value (Maybe [rootFieldType]) (Maybe [rootFieldType])
-> JSONCodec (AllowedRootFields rootFieldType)
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Maybe [rootFieldType] -> AllowedRootFields rootFieldType
forall {rootFieldType}.
Hashable rootFieldType =>
Maybe [rootFieldType] -> AllowedRootFields rootFieldType
dec AllowedRootFields rootFieldType -> Maybe [rootFieldType]
forall {a}. AllowedRootFields a -> Maybe [a]
enc (Codec Value (Maybe [rootFieldType]) (Maybe [rootFieldType])
-> JSONCodec (AllowedRootFields rootFieldType))
-> Codec Value (Maybe [rootFieldType]) (Maybe [rootFieldType])
-> JSONCodec (AllowedRootFields rootFieldType)
forall a b. (a -> b) -> a -> b
$ ValueCodec [rootFieldType] [rootFieldType]
-> Codec Value (Maybe [rootFieldType]) (Maybe [rootFieldType])
forall input output.
ValueCodec input output -> ValueCodec (Maybe input) (Maybe output)
maybeCodec (ValueCodec [rootFieldType] [rootFieldType]
-> Codec Value (Maybe [rootFieldType]) (Maybe [rootFieldType]))
-> ValueCodec [rootFieldType] [rootFieldType]
-> Codec Value (Maybe [rootFieldType]) (Maybe [rootFieldType])
forall a b. (a -> b) -> a -> b
$ ValueCodec rootFieldType rootFieldType
-> ValueCodec [rootFieldType] [rootFieldType]
forall input output.
ValueCodec input output -> ValueCodec [input] [output]
listCodec ValueCodec rootFieldType rootFieldType
forall value. HasCodec value => JSONCodec value
codec
where
dec :: Maybe [rootFieldType] -> AllowedRootFields rootFieldType
dec (Just [rootFieldType]
fields) = HashSet rootFieldType -> AllowedRootFields rootFieldType
forall rootFieldType.
HashSet rootFieldType -> AllowedRootFields rootFieldType
ARFAllowConfiguredRootFields (HashSet rootFieldType -> AllowedRootFields rootFieldType)
-> HashSet rootFieldType -> AllowedRootFields rootFieldType
forall a b. (a -> b) -> a -> b
$ [rootFieldType] -> HashSet rootFieldType
forall a. (Eq a, Hashable a) => [a] -> HashSet a
Set.fromList [rootFieldType]
fields
dec (Maybe [rootFieldType]
Nothing) = AllowedRootFields rootFieldType
forall rootFieldType. AllowedRootFields rootFieldType
ARFAllowAllRootFields
enc :: AllowedRootFields a -> Maybe [a]
enc AllowedRootFields a
ARFAllowAllRootFields = Maybe [a]
forall a. Maybe a
Nothing
enc (ARFAllowConfiguredRootFields HashSet a
fields) = [a] -> Maybe [a]
forall a. a -> Maybe a
Just ([a] -> Maybe [a]) -> [a] -> Maybe [a]
forall a b. (a -> b) -> a -> b
$ HashSet a -> [a]
forall a. HashSet a -> [a]
Set.toList HashSet a
fields
instance (Semigroup (HashSet rootFieldType)) => Semigroup (AllowedRootFields rootFieldType) where
AllowedRootFields rootFieldType
ARFAllowAllRootFields <> :: AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType
-> AllowedRootFields rootFieldType
<> AllowedRootFields rootFieldType
_ = AllowedRootFields rootFieldType
forall rootFieldType. AllowedRootFields rootFieldType
ARFAllowAllRootFields
AllowedRootFields rootFieldType
_ <> AllowedRootFields rootFieldType
ARFAllowAllRootFields = AllowedRootFields rootFieldType
forall rootFieldType. AllowedRootFields rootFieldType
ARFAllowAllRootFields
ARFAllowConfiguredRootFields HashSet rootFieldType
rfL <> ARFAllowConfiguredRootFields HashSet rootFieldType
rfR =
HashSet rootFieldType -> AllowedRootFields rootFieldType
forall rootFieldType.
HashSet rootFieldType -> AllowedRootFields rootFieldType
ARFAllowConfiguredRootFields (HashSet rootFieldType
rfL HashSet rootFieldType
-> HashSet rootFieldType -> HashSet rootFieldType
forall a. Semigroup a => a -> a -> a
<> HashSet rootFieldType
rfR)
isRootFieldAllowed :: (Eq rootField) => rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed :: forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed rootField
rootField = \case
AllowedRootFields rootField
ARFAllowAllRootFields -> Bool
True
ARFAllowConfiguredRootFields HashSet rootField
allowedRootFields -> rootField
rootField rootField -> HashSet rootField -> Bool
forall a. Eq a => a -> HashSet a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` HashSet rootField
allowedRootFields
data ValidateInputHttpDefinition webhook = ValidateInputHttpDefinition
{ forall webhook. ValidateInputHttpDefinition webhook -> webhook
_vihdUrl :: webhook,
:: [HeaderConf],
forall webhook. ValidateInputHttpDefinition webhook -> Timeout
_vihdTimeout :: Timeout,
:: Bool
}
deriving (Int -> ValidateInputHttpDefinition webhook -> ShowS
[ValidateInputHttpDefinition webhook] -> ShowS
ValidateInputHttpDefinition webhook -> String
(Int -> ValidateInputHttpDefinition webhook -> ShowS)
-> (ValidateInputHttpDefinition webhook -> String)
-> ([ValidateInputHttpDefinition webhook] -> ShowS)
-> Show (ValidateInputHttpDefinition webhook)
forall webhook.
Show webhook =>
Int -> ValidateInputHttpDefinition webhook -> ShowS
forall webhook.
Show webhook =>
[ValidateInputHttpDefinition webhook] -> ShowS
forall webhook.
Show webhook =>
ValidateInputHttpDefinition webhook -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall webhook.
Show webhook =>
Int -> ValidateInputHttpDefinition webhook -> ShowS
showsPrec :: Int -> ValidateInputHttpDefinition webhook -> ShowS
$cshow :: forall webhook.
Show webhook =>
ValidateInputHttpDefinition webhook -> String
show :: ValidateInputHttpDefinition webhook -> String
$cshowList :: forall webhook.
Show webhook =>
[ValidateInputHttpDefinition webhook] -> ShowS
showList :: [ValidateInputHttpDefinition webhook] -> ShowS
Show, ValidateInputHttpDefinition webhook
-> ValidateInputHttpDefinition webhook -> Bool
(ValidateInputHttpDefinition webhook
-> ValidateInputHttpDefinition webhook -> Bool)
-> (ValidateInputHttpDefinition webhook
-> ValidateInputHttpDefinition webhook -> Bool)
-> Eq (ValidateInputHttpDefinition webhook)
forall webhook.
Eq webhook =>
ValidateInputHttpDefinition webhook
-> ValidateInputHttpDefinition webhook -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall webhook.
Eq webhook =>
ValidateInputHttpDefinition webhook
-> ValidateInputHttpDefinition webhook -> Bool
== :: ValidateInputHttpDefinition webhook
-> ValidateInputHttpDefinition webhook -> Bool
$c/= :: forall webhook.
Eq webhook =>
ValidateInputHttpDefinition webhook
-> ValidateInputHttpDefinition webhook -> Bool
/= :: ValidateInputHttpDefinition webhook
-> ValidateInputHttpDefinition webhook -> Bool
Eq, (forall x.
ValidateInputHttpDefinition webhook
-> Rep (ValidateInputHttpDefinition webhook) x)
-> (forall x.
Rep (ValidateInputHttpDefinition webhook) x
-> ValidateInputHttpDefinition webhook)
-> Generic (ValidateInputHttpDefinition webhook)
forall x.
Rep (ValidateInputHttpDefinition webhook) x
-> ValidateInputHttpDefinition webhook
forall x.
ValidateInputHttpDefinition webhook
-> Rep (ValidateInputHttpDefinition webhook) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall webhook x.
Rep (ValidateInputHttpDefinition webhook) x
-> ValidateInputHttpDefinition webhook
forall webhook x.
ValidateInputHttpDefinition webhook
-> Rep (ValidateInputHttpDefinition webhook) x
$cfrom :: forall webhook x.
ValidateInputHttpDefinition webhook
-> Rep (ValidateInputHttpDefinition webhook) x
from :: forall x.
ValidateInputHttpDefinition webhook
-> Rep (ValidateInputHttpDefinition webhook) x
$cto :: forall webhook x.
Rep (ValidateInputHttpDefinition webhook) x
-> ValidateInputHttpDefinition webhook
to :: forall x.
Rep (ValidateInputHttpDefinition webhook) x
-> ValidateInputHttpDefinition webhook
Generic, (forall a b.
(a -> b)
-> ValidateInputHttpDefinition a -> ValidateInputHttpDefinition b)
-> (forall a b.
a
-> ValidateInputHttpDefinition b -> ValidateInputHttpDefinition a)
-> Functor ValidateInputHttpDefinition
forall a b.
a -> ValidateInputHttpDefinition b -> ValidateInputHttpDefinition a
forall a b.
(a -> b)
-> ValidateInputHttpDefinition a -> ValidateInputHttpDefinition b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b)
-> ValidateInputHttpDefinition a -> ValidateInputHttpDefinition b
fmap :: forall a b.
(a -> b)
-> ValidateInputHttpDefinition a -> ValidateInputHttpDefinition b
$c<$ :: forall a b.
a -> ValidateInputHttpDefinition b -> ValidateInputHttpDefinition a
<$ :: forall a b.
a -> ValidateInputHttpDefinition b -> ValidateInputHttpDefinition a
Functor, (forall m. Monoid m => ValidateInputHttpDefinition m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> ValidateInputHttpDefinition a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> ValidateInputHttpDefinition a -> m)
-> (forall a b.
(a -> b -> b) -> b -> ValidateInputHttpDefinition a -> b)
-> (forall a b.
(a -> b -> b) -> b -> ValidateInputHttpDefinition a -> b)
-> (forall b a.
(b -> a -> b) -> b -> ValidateInputHttpDefinition a -> b)
-> (forall b a.
(b -> a -> b) -> b -> ValidateInputHttpDefinition a -> b)
-> (forall a. (a -> a -> a) -> ValidateInputHttpDefinition a -> a)
-> (forall a. (a -> a -> a) -> ValidateInputHttpDefinition a -> a)
-> (forall a. ValidateInputHttpDefinition a -> [a])
-> (forall webhook. ValidateInputHttpDefinition webhook -> Bool)
-> (forall a. ValidateInputHttpDefinition a -> Int)
-> (forall a. Eq a => a -> ValidateInputHttpDefinition a -> Bool)
-> (forall a. Ord a => ValidateInputHttpDefinition a -> a)
-> (forall a. Ord a => ValidateInputHttpDefinition a -> a)
-> (forall a. Num a => ValidateInputHttpDefinition a -> a)
-> (forall a. Num a => ValidateInputHttpDefinition a -> a)
-> Foldable ValidateInputHttpDefinition
forall a. Eq a => a -> ValidateInputHttpDefinition a -> Bool
forall a. Num a => ValidateInputHttpDefinition a -> a
forall a. Ord a => ValidateInputHttpDefinition a -> a
forall m. Monoid m => ValidateInputHttpDefinition m -> m
forall webhook. ValidateInputHttpDefinition webhook -> Bool
forall a. ValidateInputHttpDefinition a -> Int
forall a. ValidateInputHttpDefinition a -> [a]
forall a. (a -> a -> a) -> ValidateInputHttpDefinition a -> a
forall m a.
Monoid m =>
(a -> m) -> ValidateInputHttpDefinition a -> m
forall b a.
(b -> a -> b) -> b -> ValidateInputHttpDefinition a -> b
forall a b.
(a -> b -> b) -> b -> ValidateInputHttpDefinition a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => ValidateInputHttpDefinition m -> m
fold :: forall m. Monoid m => ValidateInputHttpDefinition m -> m
$cfoldMap :: forall m a.
Monoid m =>
(a -> m) -> ValidateInputHttpDefinition a -> m
foldMap :: forall m a.
Monoid m =>
(a -> m) -> ValidateInputHttpDefinition a -> m
$cfoldMap' :: forall m a.
Monoid m =>
(a -> m) -> ValidateInputHttpDefinition a -> m
foldMap' :: forall m a.
Monoid m =>
(a -> m) -> ValidateInputHttpDefinition a -> m
$cfoldr :: forall a b.
(a -> b -> b) -> b -> ValidateInputHttpDefinition a -> b
foldr :: forall a b.
(a -> b -> b) -> b -> ValidateInputHttpDefinition a -> b
$cfoldr' :: forall a b.
(a -> b -> b) -> b -> ValidateInputHttpDefinition a -> b
foldr' :: forall a b.
(a -> b -> b) -> b -> ValidateInputHttpDefinition a -> b
$cfoldl :: forall b a.
(b -> a -> b) -> b -> ValidateInputHttpDefinition a -> b
foldl :: forall b a.
(b -> a -> b) -> b -> ValidateInputHttpDefinition a -> b
$cfoldl' :: forall b a.
(b -> a -> b) -> b -> ValidateInputHttpDefinition a -> b
foldl' :: forall b a.
(b -> a -> b) -> b -> ValidateInputHttpDefinition a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> ValidateInputHttpDefinition a -> a
foldr1 :: forall a. (a -> a -> a) -> ValidateInputHttpDefinition a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> ValidateInputHttpDefinition a -> a
foldl1 :: forall a. (a -> a -> a) -> ValidateInputHttpDefinition a -> a
$ctoList :: forall a. ValidateInputHttpDefinition a -> [a]
toList :: forall a. ValidateInputHttpDefinition a -> [a]
$cnull :: forall webhook. ValidateInputHttpDefinition webhook -> Bool
null :: forall webhook. ValidateInputHttpDefinition webhook -> Bool
$clength :: forall a. ValidateInputHttpDefinition a -> Int
length :: forall a. ValidateInputHttpDefinition a -> Int
$celem :: forall a. Eq a => a -> ValidateInputHttpDefinition a -> Bool
elem :: forall a. Eq a => a -> ValidateInputHttpDefinition a -> Bool
$cmaximum :: forall a. Ord a => ValidateInputHttpDefinition a -> a
maximum :: forall a. Ord a => ValidateInputHttpDefinition a -> a
$cminimum :: forall a. Ord a => ValidateInputHttpDefinition a -> a
minimum :: forall a. Ord a => ValidateInputHttpDefinition a -> a
$csum :: forall a. Num a => ValidateInputHttpDefinition a -> a
sum :: forall a. Num a => ValidateInputHttpDefinition a -> a
$cproduct :: forall a. Num a => ValidateInputHttpDefinition a -> a
product :: forall a. Num a => ValidateInputHttpDefinition a -> a
Foldable, Functor ValidateInputHttpDefinition
Foldable ValidateInputHttpDefinition
Functor ValidateInputHttpDefinition
-> Foldable ValidateInputHttpDefinition
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ValidateInputHttpDefinition a
-> f (ValidateInputHttpDefinition b))
-> (forall (f :: * -> *) a.
Applicative f =>
ValidateInputHttpDefinition (f a)
-> f (ValidateInputHttpDefinition a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ValidateInputHttpDefinition a
-> m (ValidateInputHttpDefinition b))
-> (forall (m :: * -> *) a.
Monad m =>
ValidateInputHttpDefinition (m a)
-> m (ValidateInputHttpDefinition a))
-> Traversable ValidateInputHttpDefinition
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ValidateInputHttpDefinition (m a)
-> m (ValidateInputHttpDefinition a)
forall (f :: * -> *) a.
Applicative f =>
ValidateInputHttpDefinition (f a)
-> f (ValidateInputHttpDefinition a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ValidateInputHttpDefinition a
-> m (ValidateInputHttpDefinition b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ValidateInputHttpDefinition a
-> f (ValidateInputHttpDefinition b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ValidateInputHttpDefinition a
-> f (ValidateInputHttpDefinition b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ValidateInputHttpDefinition a
-> f (ValidateInputHttpDefinition b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
ValidateInputHttpDefinition (f a)
-> f (ValidateInputHttpDefinition a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
ValidateInputHttpDefinition (f a)
-> f (ValidateInputHttpDefinition a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ValidateInputHttpDefinition a
-> m (ValidateInputHttpDefinition b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ValidateInputHttpDefinition a
-> m (ValidateInputHttpDefinition b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
ValidateInputHttpDefinition (m a)
-> m (ValidateInputHttpDefinition a)
sequence :: forall (m :: * -> *) a.
Monad m =>
ValidateInputHttpDefinition (m a)
-> m (ValidateInputHttpDefinition a)
Traversable)
instance (NFData webhook) => NFData (ValidateInputHttpDefinition webhook)
instance (FromJSON webhook) => FromJSON (ValidateInputHttpDefinition webhook) where
parseJSON :: Value -> Parser (ValidateInputHttpDefinition webhook)
parseJSON = String
-> (Object -> Parser (ValidateInputHttpDefinition webhook))
-> Value
-> Parser (ValidateInputHttpDefinition webhook)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ValidateInputHttpDefinition" ((Object -> Parser (ValidateInputHttpDefinition webhook))
-> Value -> Parser (ValidateInputHttpDefinition webhook))
-> (Object -> Parser (ValidateInputHttpDefinition webhook))
-> Value
-> Parser (ValidateInputHttpDefinition webhook)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
webhook
-> [HeaderConf]
-> Timeout
-> Bool
-> ValidateInputHttpDefinition webhook
forall webhook.
webhook
-> [HeaderConf]
-> Timeout
-> Bool
-> ValidateInputHttpDefinition webhook
ValidateInputHttpDefinition
(webhook
-> [HeaderConf]
-> Timeout
-> Bool
-> ValidateInputHttpDefinition webhook)
-> Parser webhook
-> Parser
([HeaderConf]
-> Timeout -> Bool -> ValidateInputHttpDefinition webhook)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser webhook
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
Parser
([HeaderConf]
-> Timeout -> Bool -> ValidateInputHttpDefinition webhook)
-> Parser [HeaderConf]
-> Parser (Timeout -> Bool -> ValidateInputHttpDefinition webhook)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe [HeaderConf])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"headers"
Parser (Maybe [HeaderConf]) -> [HeaderConf] -> Parser [HeaderConf]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
Parser (Timeout -> Bool -> ValidateInputHttpDefinition webhook)
-> Parser Timeout
-> Parser (Bool -> ValidateInputHttpDefinition webhook)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Timeout)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"timeout"
Parser (Maybe Timeout) -> Timeout -> Parser Timeout
forall a. Parser (Maybe a) -> a -> Parser a
.!= (Int -> Timeout
Timeout Int
10)
Parser (Bool -> ValidateInputHttpDefinition webhook)
-> Parser Bool -> Parser (ValidateInputHttpDefinition webhook)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"forward_client_headers"
Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
instance (ToJSON webhook) => ToJSON (ValidateInputHttpDefinition webhook) where
toJSON :: ValidateInputHttpDefinition webhook -> Value
toJSON = Options -> ValidateInputHttpDefinition webhook -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance (HasCodec webhook) => HasCodec (ValidateInputHttpDefinition webhook) where
codec :: JSONCodec (ValidateInputHttpDefinition webhook)
codec =
Text
-> ObjectCodec
(ValidateInputHttpDefinition webhook)
(ValidateInputHttpDefinition webhook)
-> JSONCodec (ValidateInputHttpDefinition webhook)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object Text
"ValidateInputHttpDefinition"
(ObjectCodec
(ValidateInputHttpDefinition webhook)
(ValidateInputHttpDefinition webhook)
-> JSONCodec (ValidateInputHttpDefinition webhook))
-> ObjectCodec
(ValidateInputHttpDefinition webhook)
(ValidateInputHttpDefinition webhook)
-> JSONCodec (ValidateInputHttpDefinition webhook)
forall a b. (a -> b) -> a -> b
$ webhook
-> [HeaderConf]
-> Timeout
-> Bool
-> ValidateInputHttpDefinition webhook
forall webhook.
webhook
-> [HeaderConf]
-> Timeout
-> Bool
-> ValidateInputHttpDefinition webhook
ValidateInputHttpDefinition
(webhook
-> [HeaderConf]
-> Timeout
-> Bool
-> ValidateInputHttpDefinition webhook)
-> Codec Object (ValidateInputHttpDefinition webhook) webhook
-> Codec
Object
(ValidateInputHttpDefinition webhook)
([HeaderConf]
-> Timeout -> Bool -> ValidateInputHttpDefinition webhook)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec webhook webhook
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"url"
ObjectCodec webhook webhook
-> (ValidateInputHttpDefinition webhook -> webhook)
-> Codec Object (ValidateInputHttpDefinition webhook) webhook
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ValidateInputHttpDefinition webhook -> webhook
forall webhook. ValidateInputHttpDefinition webhook -> webhook
_vihdUrl
Codec
Object
(ValidateInputHttpDefinition webhook)
([HeaderConf]
-> Timeout -> Bool -> ValidateInputHttpDefinition webhook)
-> Codec Object (ValidateInputHttpDefinition webhook) [HeaderConf]
-> Codec
Object
(ValidateInputHttpDefinition webhook)
(Timeout -> Bool -> ValidateInputHttpDefinition webhook)
forall a b.
Codec Object (ValidateInputHttpDefinition webhook) (a -> b)
-> Codec Object (ValidateInputHttpDefinition webhook) a
-> Codec Object (ValidateInputHttpDefinition webhook) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> [HeaderConf] -> ObjectCodec [HeaderConf] [HeaderConf]
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"headers" []
ObjectCodec [HeaderConf] [HeaderConf]
-> (ValidateInputHttpDefinition webhook -> [HeaderConf])
-> Codec Object (ValidateInputHttpDefinition webhook) [HeaderConf]
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ValidateInputHttpDefinition webhook -> [HeaderConf]
forall webhook. ValidateInputHttpDefinition webhook -> [HeaderConf]
_vihdHeaders
Codec
Object
(ValidateInputHttpDefinition webhook)
(Timeout -> Bool -> ValidateInputHttpDefinition webhook)
-> Codec Object (ValidateInputHttpDefinition webhook) Timeout
-> Codec
Object
(ValidateInputHttpDefinition webhook)
(Bool -> ValidateInputHttpDefinition webhook)
forall a b.
Codec Object (ValidateInputHttpDefinition webhook) (a -> b)
-> Codec Object (ValidateInputHttpDefinition webhook) a
-> Codec Object (ValidateInputHttpDefinition webhook) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Timeout -> ObjectCodec Timeout Timeout
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"timeout" (Int -> Timeout
Timeout Int
10)
ObjectCodec Timeout Timeout
-> (ValidateInputHttpDefinition webhook -> Timeout)
-> Codec Object (ValidateInputHttpDefinition webhook) Timeout
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ValidateInputHttpDefinition webhook -> Timeout
forall webhook. ValidateInputHttpDefinition webhook -> Timeout
_vihdTimeout
Codec
Object
(ValidateInputHttpDefinition webhook)
(Bool -> ValidateInputHttpDefinition webhook)
-> Codec Object (ValidateInputHttpDefinition webhook) Bool
-> ObjectCodec
(ValidateInputHttpDefinition webhook)
(ValidateInputHttpDefinition webhook)
forall a b.
Codec Object (ValidateInputHttpDefinition webhook) (a -> b)
-> Codec Object (ValidateInputHttpDefinition webhook) a
-> Codec Object (ValidateInputHttpDefinition webhook) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Bool -> ObjectCodec Bool Bool
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"forward_client_headers" Bool
False
ObjectCodec Bool Bool
-> (ValidateInputHttpDefinition webhook -> Bool)
-> Codec Object (ValidateInputHttpDefinition webhook) Bool
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ValidateInputHttpDefinition webhook -> Bool
forall webhook. ValidateInputHttpDefinition webhook -> Bool
_vihdForwardClientHeaders
data ValidateInput webhook
= VIHttp (ValidateInputHttpDefinition webhook)
deriving (Int -> ValidateInput webhook -> ShowS
[ValidateInput webhook] -> ShowS
ValidateInput webhook -> String
(Int -> ValidateInput webhook -> ShowS)
-> (ValidateInput webhook -> String)
-> ([ValidateInput webhook] -> ShowS)
-> Show (ValidateInput webhook)
forall webhook.
Show webhook =>
Int -> ValidateInput webhook -> ShowS
forall webhook. Show webhook => [ValidateInput webhook] -> ShowS
forall webhook. Show webhook => ValidateInput webhook -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall webhook.
Show webhook =>
Int -> ValidateInput webhook -> ShowS
showsPrec :: Int -> ValidateInput webhook -> ShowS
$cshow :: forall webhook. Show webhook => ValidateInput webhook -> String
show :: ValidateInput webhook -> String
$cshowList :: forall webhook. Show webhook => [ValidateInput webhook] -> ShowS
showList :: [ValidateInput webhook] -> ShowS
Show, ValidateInput webhook -> ValidateInput webhook -> Bool
(ValidateInput webhook -> ValidateInput webhook -> Bool)
-> (ValidateInput webhook -> ValidateInput webhook -> Bool)
-> Eq (ValidateInput webhook)
forall webhook.
Eq webhook =>
ValidateInput webhook -> ValidateInput webhook -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall webhook.
Eq webhook =>
ValidateInput webhook -> ValidateInput webhook -> Bool
== :: ValidateInput webhook -> ValidateInput webhook -> Bool
$c/= :: forall webhook.
Eq webhook =>
ValidateInput webhook -> ValidateInput webhook -> Bool
/= :: ValidateInput webhook -> ValidateInput webhook -> Bool
Eq, (forall x. ValidateInput webhook -> Rep (ValidateInput webhook) x)
-> (forall x.
Rep (ValidateInput webhook) x -> ValidateInput webhook)
-> Generic (ValidateInput webhook)
forall x. Rep (ValidateInput webhook) x -> ValidateInput webhook
forall x. ValidateInput webhook -> Rep (ValidateInput webhook) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall webhook x.
Rep (ValidateInput webhook) x -> ValidateInput webhook
forall webhook x.
ValidateInput webhook -> Rep (ValidateInput webhook) x
$cfrom :: forall webhook x.
ValidateInput webhook -> Rep (ValidateInput webhook) x
from :: forall x. ValidateInput webhook -> Rep (ValidateInput webhook) x
$cto :: forall webhook x.
Rep (ValidateInput webhook) x -> ValidateInput webhook
to :: forall x. Rep (ValidateInput webhook) x -> ValidateInput webhook
Generic, (forall a b. (a -> b) -> ValidateInput a -> ValidateInput b)
-> (forall a b. a -> ValidateInput b -> ValidateInput a)
-> Functor ValidateInput
forall a b. a -> ValidateInput b -> ValidateInput a
forall a b. (a -> b) -> ValidateInput a -> ValidateInput b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> ValidateInput a -> ValidateInput b
fmap :: forall a b. (a -> b) -> ValidateInput a -> ValidateInput b
$c<$ :: forall a b. a -> ValidateInput b -> ValidateInput a
<$ :: forall a b. a -> ValidateInput b -> ValidateInput a
Functor, (forall m. Monoid m => ValidateInput m -> m)
-> (forall m a. Monoid m => (a -> m) -> ValidateInput a -> m)
-> (forall m a. Monoid m => (a -> m) -> ValidateInput a -> m)
-> (forall a b. (a -> b -> b) -> b -> ValidateInput a -> b)
-> (forall a b. (a -> b -> b) -> b -> ValidateInput a -> b)
-> (forall b a. (b -> a -> b) -> b -> ValidateInput a -> b)
-> (forall b a. (b -> a -> b) -> b -> ValidateInput a -> b)
-> (forall a. (a -> a -> a) -> ValidateInput a -> a)
-> (forall a. (a -> a -> a) -> ValidateInput a -> a)
-> (forall a. ValidateInput a -> [a])
-> (forall a. ValidateInput a -> Bool)
-> (forall a. ValidateInput a -> Int)
-> (forall a. Eq a => a -> ValidateInput a -> Bool)
-> (forall a. Ord a => ValidateInput a -> a)
-> (forall a. Ord a => ValidateInput a -> a)
-> (forall a. Num a => ValidateInput a -> a)
-> (forall a. Num a => ValidateInput a -> a)
-> Foldable ValidateInput
forall a. Eq a => a -> ValidateInput a -> Bool
forall a. Num a => ValidateInput a -> a
forall a. Ord a => ValidateInput a -> a
forall m. Monoid m => ValidateInput m -> m
forall a. ValidateInput a -> Bool
forall a. ValidateInput a -> Int
forall a. ValidateInput a -> [a]
forall a. (a -> a -> a) -> ValidateInput a -> a
forall m a. Monoid m => (a -> m) -> ValidateInput a -> m
forall b a. (b -> a -> b) -> b -> ValidateInput a -> b
forall a b. (a -> b -> b) -> b -> ValidateInput a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => ValidateInput m -> m
fold :: forall m. Monoid m => ValidateInput m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> ValidateInput a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> ValidateInput a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> ValidateInput a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> ValidateInput a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> ValidateInput a -> b
foldr :: forall a b. (a -> b -> b) -> b -> ValidateInput a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> ValidateInput a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> ValidateInput a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> ValidateInput a -> b
foldl :: forall b a. (b -> a -> b) -> b -> ValidateInput a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> ValidateInput a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> ValidateInput a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> ValidateInput a -> a
foldr1 :: forall a. (a -> a -> a) -> ValidateInput a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> ValidateInput a -> a
foldl1 :: forall a. (a -> a -> a) -> ValidateInput a -> a
$ctoList :: forall a. ValidateInput a -> [a]
toList :: forall a. ValidateInput a -> [a]
$cnull :: forall a. ValidateInput a -> Bool
null :: forall a. ValidateInput a -> Bool
$clength :: forall a. ValidateInput a -> Int
length :: forall a. ValidateInput a -> Int
$celem :: forall a. Eq a => a -> ValidateInput a -> Bool
elem :: forall a. Eq a => a -> ValidateInput a -> Bool
$cmaximum :: forall a. Ord a => ValidateInput a -> a
maximum :: forall a. Ord a => ValidateInput a -> a
$cminimum :: forall a. Ord a => ValidateInput a -> a
minimum :: forall a. Ord a => ValidateInput a -> a
$csum :: forall a. Num a => ValidateInput a -> a
sum :: forall a. Num a => ValidateInput a -> a
$cproduct :: forall a. Num a => ValidateInput a -> a
product :: forall a. Num a => ValidateInput a -> a
Foldable, Functor ValidateInput
Foldable ValidateInput
Functor ValidateInput
-> Foldable ValidateInput
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ValidateInput a -> f (ValidateInput b))
-> (forall (f :: * -> *) a.
Applicative f =>
ValidateInput (f a) -> f (ValidateInput a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ValidateInput a -> m (ValidateInput b))
-> (forall (m :: * -> *) a.
Monad m =>
ValidateInput (m a) -> m (ValidateInput a))
-> Traversable ValidateInput
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ValidateInput (m a) -> m (ValidateInput a)
forall (f :: * -> *) a.
Applicative f =>
ValidateInput (f a) -> f (ValidateInput a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ValidateInput a -> m (ValidateInput b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ValidateInput a -> f (ValidateInput b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ValidateInput a -> f (ValidateInput b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ValidateInput a -> f (ValidateInput b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
ValidateInput (f a) -> f (ValidateInput a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
ValidateInput (f a) -> f (ValidateInput a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ValidateInput a -> m (ValidateInput b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ValidateInput a -> m (ValidateInput b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
ValidateInput (m a) -> m (ValidateInput a)
sequence :: forall (m :: * -> *) a.
Monad m =>
ValidateInput (m a) -> m (ValidateInput a)
Traversable)
instance (NFData webhook) => NFData (ValidateInput webhook)
instance (FromJSON webhook) => FromJSON (ValidateInput webhook) where
parseJSON :: Value -> Parser (ValidateInput webhook)
parseJSON = String
-> (Object -> Parser (ValidateInput webhook))
-> Value
-> Parser (ValidateInput webhook)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ValidateInput" ((Object -> Parser (ValidateInput webhook))
-> Value -> Parser (ValidateInput webhook))
-> (Object -> Parser (ValidateInput webhook))
-> Value
-> Parser (ValidateInput webhook)
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
String
ty <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
case String
ty of
String
"http" -> ValidateInputHttpDefinition webhook -> ValidateInput webhook
forall webhook.
ValidateInputHttpDefinition webhook -> ValidateInput webhook
VIHttp (ValidateInputHttpDefinition webhook -> ValidateInput webhook)
-> Parser (ValidateInputHttpDefinition webhook)
-> Parser (ValidateInput webhook)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (ValidateInputHttpDefinition webhook)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"definition"
String
_ -> String -> Parser (ValidateInput webhook)
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser (ValidateInput webhook))
-> String -> Parser (ValidateInput webhook)
forall a b. (a -> b) -> a -> b
$ String
"expecting only 'http' for 'type' but got " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
ty
instance (ToJSON webhook) => ToJSON (ValidateInput webhook) where
toJSON :: ValidateInput webhook -> Value
toJSON ValidateInput webhook
v =
let (Value
ty, Value
def) = case ValidateInput webhook
v of
VIHttp ValidateInputHttpDefinition webhook
def' -> (Text -> Value
String Text
"http", ValidateInputHttpDefinition webhook -> Value
forall a. ToJSON a => a -> Value
toJSON ValidateInputHttpDefinition webhook
def')
in [Pair] -> Value
object [Key
"type" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Value
ty, Key
"definition" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Value
def]
instance (HasCodec webhook, Typeable webhook) => HasCodec (ValidateInput webhook) where
codec :: JSONCodec (ValidateInput webhook)
codec =
Text
-> ObjectCodec (ValidateInput webhook) (ValidateInput webhook)
-> JSONCodec (ValidateInput webhook)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (Text
"ValidateInput" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> forall a. Typeable a => Text
forall {k} (a :: k). Typeable a => Text
typeableName @webhook)
(ObjectCodec (ValidateInput webhook) (ValidateInput webhook)
-> JSONCodec (ValidateInput webhook))
-> ObjectCodec (ValidateInput webhook) (ValidateInput webhook)
-> JSONCodec (ValidateInput webhook)
forall a b. (a -> b) -> a -> b
$ ValidateInputHttpDefinition webhook -> ValidateInput webhook
forall webhook.
ValidateInputHttpDefinition webhook -> ValidateInput webhook
VIHttp
(ValidateInputHttpDefinition webhook -> ValidateInput webhook)
-> Codec Object (ValidateInput webhook) Text
-> Codec
Object
(ValidateInput webhook)
(ValidateInputHttpDefinition webhook -> ValidateInput webhook)
forall a b.
a
-> Codec Object (ValidateInput webhook) b
-> Codec Object (ValidateInput webhook) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> Codec Value Text Text -> ObjectCodec Text Text
forall input output.
Text -> ValueCodec input output -> ObjectCodec input output
requiredFieldWith' Text
"type" (Text -> Codec Value Text Text
AC.literalTextCodec Text
"http")
ObjectCodec Text Text
-> (ValidateInput webhook -> Text)
-> Codec Object (ValidateInput webhook) Text
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= Text -> ValidateInput webhook -> Text
forall a b. a -> b -> a
const Text
"http"
Codec
Object
(ValidateInput webhook)
(ValidateInputHttpDefinition webhook -> ValidateInput webhook)
-> Codec
Object
(ValidateInput webhook)
(ValidateInputHttpDefinition webhook)
-> ObjectCodec (ValidateInput webhook) (ValidateInput webhook)
forall a b.
Codec Object (ValidateInput webhook) (a -> b)
-> Codec Object (ValidateInput webhook) a
-> Codec Object (ValidateInput webhook) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(ValidateInputHttpDefinition webhook)
(ValidateInputHttpDefinition webhook)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"definition"
ObjectCodec
(ValidateInputHttpDefinition webhook)
(ValidateInputHttpDefinition webhook)
-> (ValidateInput webhook -> ValidateInputHttpDefinition webhook)
-> Codec
Object
(ValidateInput webhook)
(ValidateInputHttpDefinition webhook)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= ((\(VIHttp ValidateInputHttpDefinition webhook
def) -> ValidateInputHttpDefinition webhook
def))
data SelPerm (b :: BackendType) = SelPerm
{
forall (b :: BackendType). SelPerm b -> PermColSpec b
spColumns :: PermColSpec b,
forall (b :: BackendType). SelPerm b -> BoolExp b
spFilter :: BoolExp b,
forall (b :: BackendType). SelPerm b -> Maybe Int
spLimit :: Maybe Int,
forall (b :: BackendType). SelPerm b -> Bool
spAllowAggregations :: Bool,
forall (b :: BackendType). SelPerm b -> [ComputedFieldName]
spComputedFields :: [ComputedFieldName],
forall (b :: BackendType).
SelPerm b -> AllowedRootFields QueryRootFieldType
spAllowedQueryRootFields :: AllowedRootFields QueryRootFieldType,
forall (b :: BackendType).
SelPerm b -> AllowedRootFields SubscriptionRootFieldType
spAllowedSubscriptionRootFields :: AllowedRootFields SubscriptionRootFieldType
}
deriving (Int -> SelPerm b -> ShowS
[SelPerm b] -> ShowS
SelPerm b -> String
(Int -> SelPerm b -> ShowS)
-> (SelPerm b -> String)
-> ([SelPerm b] -> ShowS)
-> Show (SelPerm b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType). Backend b => Int -> SelPerm b -> ShowS
forall (b :: BackendType). Backend b => [SelPerm b] -> ShowS
forall (b :: BackendType). Backend b => SelPerm b -> String
$cshowsPrec :: forall (b :: BackendType). Backend b => Int -> SelPerm b -> ShowS
showsPrec :: Int -> SelPerm b -> ShowS
$cshow :: forall (b :: BackendType). Backend b => SelPerm b -> String
show :: SelPerm b -> String
$cshowList :: forall (b :: BackendType). Backend b => [SelPerm b] -> ShowS
showList :: [SelPerm b] -> ShowS
Show, SelPerm b -> SelPerm b -> Bool
(SelPerm b -> SelPerm b -> Bool)
-> (SelPerm b -> SelPerm b -> Bool) -> Eq (SelPerm b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType).
Backend b =>
SelPerm b -> SelPerm b -> Bool
$c== :: forall (b :: BackendType).
Backend b =>
SelPerm b -> SelPerm b -> Bool
== :: SelPerm b -> SelPerm b -> Bool
$c/= :: forall (b :: BackendType).
Backend b =>
SelPerm b -> SelPerm b -> Bool
/= :: SelPerm b -> SelPerm b -> Bool
Eq, (forall x. SelPerm b -> Rep (SelPerm b) x)
-> (forall x. Rep (SelPerm b) x -> SelPerm b)
-> Generic (SelPerm b)
forall x. Rep (SelPerm b) x -> SelPerm b
forall x. SelPerm b -> Rep (SelPerm b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x. Rep (SelPerm b) x -> SelPerm b
forall (b :: BackendType) x. SelPerm b -> Rep (SelPerm b) x
$cfrom :: forall (b :: BackendType) x. SelPerm b -> Rep (SelPerm b) x
from :: forall x. SelPerm b -> Rep (SelPerm b) x
$cto :: forall (b :: BackendType) x. Rep (SelPerm b) x -> SelPerm b
to :: forall x. Rep (SelPerm b) x -> SelPerm b
Generic)
instance (Backend b) => ToJSON (SelPerm b) where
toJSON :: SelPerm b -> Value
toJSON SelPerm {Bool
[ComputedFieldName]
Maybe Int
BoolExp b
AllowedRootFields SubscriptionRootFieldType
AllowedRootFields QueryRootFieldType
PermColSpec b
spColumns :: forall (b :: BackendType). SelPerm b -> PermColSpec b
spFilter :: forall (b :: BackendType). SelPerm b -> BoolExp b
spLimit :: forall (b :: BackendType). SelPerm b -> Maybe Int
spAllowAggregations :: forall (b :: BackendType). SelPerm b -> Bool
spComputedFields :: forall (b :: BackendType). SelPerm b -> [ComputedFieldName]
spAllowedQueryRootFields :: forall (b :: BackendType).
SelPerm b -> AllowedRootFields QueryRootFieldType
spAllowedSubscriptionRootFields :: forall (b :: BackendType).
SelPerm b -> AllowedRootFields SubscriptionRootFieldType
spColumns :: PermColSpec b
spFilter :: BoolExp b
spLimit :: Maybe Int
spAllowAggregations :: Bool
spComputedFields :: [ComputedFieldName]
spAllowedQueryRootFields :: AllowedRootFields QueryRootFieldType
spAllowedSubscriptionRootFields :: AllowedRootFields SubscriptionRootFieldType
..} =
let queryRootFieldsPair :: [Pair]
queryRootFieldsPair =
case AllowedRootFields QueryRootFieldType
spAllowedQueryRootFields of
AllowedRootFields QueryRootFieldType
ARFAllowAllRootFields -> [Pair]
forall a. Monoid a => a
mempty
ARFAllowConfiguredRootFields HashSet QueryRootFieldType
configuredRootFields ->
[Key
"query_root_fields" Key -> HashSet QueryRootFieldType -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= HashSet QueryRootFieldType
configuredRootFields]
subscriptionRootFieldsPair :: [Pair]
subscriptionRootFieldsPair =
case AllowedRootFields SubscriptionRootFieldType
spAllowedSubscriptionRootFields of
AllowedRootFields SubscriptionRootFieldType
ARFAllowAllRootFields -> [Pair]
forall a. Monoid a => a
mempty
ARFAllowConfiguredRootFields HashSet SubscriptionRootFieldType
configuredRootFields ->
[Key
"subscription_root_fields" Key -> HashSet SubscriptionRootFieldType -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= HashSet SubscriptionRootFieldType
configuredRootFields]
limitPair :: [Pair]
limitPair =
case Maybe Int
spLimit of
Maybe Int
Nothing -> [Pair]
forall a. Monoid a => a
mempty
Just Int
limit -> [Key
"limit" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
limit]
in [Pair] -> Value
object
([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Key
"columns" Key -> PermColSpec b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= PermColSpec b
spColumns,
Key
"filter" Key -> BoolExp b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= BoolExp b
spFilter,
Key
"allow_aggregations" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Bool
spAllowAggregations,
Key
"computed_fields" Key -> [ComputedFieldName] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [ComputedFieldName]
spComputedFields
]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Pair]
queryRootFieldsPair
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Pair]
subscriptionRootFieldsPair
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Pair]
limitPair
instance (Backend b) => FromJSON (SelPerm b) where
parseJSON :: Value -> Parser (SelPerm b)
parseJSON = do
String
-> (Object -> Parser (SelPerm b)) -> Value -> Parser (SelPerm b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SelPerm" ((Object -> Parser (SelPerm b)) -> Value -> Parser (SelPerm b))
-> (Object -> Parser (SelPerm b)) -> Value -> Parser (SelPerm b)
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Maybe (HashSet QueryRootFieldType)
queryRootFieldsMaybe <- Object
o Object -> Key -> Parser (Maybe (HashSet QueryRootFieldType))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"query_root_fields"
Maybe (HashSet SubscriptionRootFieldType)
subscriptionRootFieldsMaybe <- Object
o Object -> Key -> Parser (Maybe (HashSet SubscriptionRootFieldType))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"subscription_root_fields"
AllowedRootFields QueryRootFieldType
allowedQueryRootFields <-
case Maybe (HashSet QueryRootFieldType)
queryRootFieldsMaybe of
Just HashSet QueryRootFieldType
configuredQueryRootFields -> do
AllowedRootFields QueryRootFieldType
-> Parser (AllowedRootFields QueryRootFieldType)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AllowedRootFields QueryRootFieldType
-> Parser (AllowedRootFields QueryRootFieldType))
-> AllowedRootFields QueryRootFieldType
-> Parser (AllowedRootFields QueryRootFieldType)
forall a b. (a -> b) -> a -> b
$ HashSet QueryRootFieldType -> AllowedRootFields QueryRootFieldType
forall rootFieldType.
HashSet rootFieldType -> AllowedRootFields rootFieldType
ARFAllowConfiguredRootFields HashSet QueryRootFieldType
configuredQueryRootFields
Maybe (HashSet QueryRootFieldType)
Nothing -> AllowedRootFields QueryRootFieldType
-> Parser (AllowedRootFields QueryRootFieldType)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllowedRootFields QueryRootFieldType
forall rootFieldType. AllowedRootFields rootFieldType
ARFAllowAllRootFields
AllowedRootFields SubscriptionRootFieldType
allowedSubscriptionRootFields <-
case Maybe (HashSet SubscriptionRootFieldType)
subscriptionRootFieldsMaybe of
Just HashSet SubscriptionRootFieldType
configuredSubscriptionRootFields -> AllowedRootFields SubscriptionRootFieldType
-> Parser (AllowedRootFields SubscriptionRootFieldType)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AllowedRootFields SubscriptionRootFieldType
-> Parser (AllowedRootFields SubscriptionRootFieldType))
-> AllowedRootFields SubscriptionRootFieldType
-> Parser (AllowedRootFields SubscriptionRootFieldType)
forall a b. (a -> b) -> a -> b
$ HashSet SubscriptionRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
forall rootFieldType.
HashSet rootFieldType -> AllowedRootFields rootFieldType
ARFAllowConfiguredRootFields HashSet SubscriptionRootFieldType
configuredSubscriptionRootFields
Maybe (HashSet SubscriptionRootFieldType)
Nothing -> AllowedRootFields SubscriptionRootFieldType
-> Parser (AllowedRootFields SubscriptionRootFieldType)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AllowedRootFields SubscriptionRootFieldType
-> Parser (AllowedRootFields SubscriptionRootFieldType))
-> AllowedRootFields SubscriptionRootFieldType
-> Parser (AllowedRootFields SubscriptionRootFieldType)
forall a b. (a -> b) -> a -> b
$ AllowedRootFields SubscriptionRootFieldType
forall rootFieldType. AllowedRootFields rootFieldType
ARFAllowAllRootFields
PermColSpec b
-> BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b
forall (b :: BackendType).
PermColSpec b
-> BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b
SelPerm
(PermColSpec b
-> BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Parser (PermColSpec b)
-> Parser
(BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser (PermColSpec b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"columns"
Parser
(BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Parser (BoolExp b)
-> Parser
(Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (BoolExp b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"filter"
Parser
(Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Parser (Maybe Int)
-> Parser
(Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"limit"
Parser
(Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Parser Bool
-> Parser
([ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"allow_aggregations"
Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Parser
([ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Parser [ComputedFieldName]
-> Parser
(AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType -> SelPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe [ComputedFieldName])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"computed_fields"
Parser (Maybe [ComputedFieldName])
-> [ComputedFieldName] -> Parser [ComputedFieldName]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
Parser
(AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType -> SelPerm b)
-> Parser (AllowedRootFields QueryRootFieldType)
-> Parser
(AllowedRootFields SubscriptionRootFieldType -> SelPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> AllowedRootFields QueryRootFieldType
-> Parser (AllowedRootFields QueryRootFieldType)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllowedRootFields QueryRootFieldType
allowedQueryRootFields
Parser (AllowedRootFields SubscriptionRootFieldType -> SelPerm b)
-> Parser (AllowedRootFields SubscriptionRootFieldType)
-> Parser (SelPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> AllowedRootFields SubscriptionRootFieldType
-> Parser (AllowedRootFields SubscriptionRootFieldType)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllowedRootFields SubscriptionRootFieldType
allowedSubscriptionRootFields
instance (Backend b) => HasCodec (SelPerm b) where
codec :: JSONCodec (SelPerm b)
codec =
Text
-> ObjectCodec (SelPerm b) (SelPerm b) -> JSONCodec (SelPerm b)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"SelPerm")
(ObjectCodec (SelPerm b) (SelPerm b) -> JSONCodec (SelPerm b))
-> ObjectCodec (SelPerm b) (SelPerm b) -> JSONCodec (SelPerm b)
forall a b. (a -> b) -> a -> b
$ PermColSpec b
-> BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b
forall (b :: BackendType).
PermColSpec b
-> BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b
SelPerm
(PermColSpec b
-> BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Codec Object (SelPerm b) (PermColSpec b)
-> Codec
Object
(SelPerm b)
(BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec (PermColSpec b) (PermColSpec b)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"columns"
ObjectCodec (PermColSpec b) (PermColSpec b)
-> (SelPerm b -> PermColSpec b)
-> Codec Object (SelPerm b) (PermColSpec b)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SelPerm b -> PermColSpec b
forall (b :: BackendType). SelPerm b -> PermColSpec b
spColumns
Codec
Object
(SelPerm b)
(BoolExp b
-> Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Codec Object (SelPerm b) (BoolExp b)
-> Codec
Object
(SelPerm b)
(Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
forall a b.
Codec Object (SelPerm b) (a -> b)
-> Codec Object (SelPerm b) a -> Codec Object (SelPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (BoolExp b) (BoolExp b)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"filter"
ObjectCodec (BoolExp b) (BoolExp b)
-> (SelPerm b -> BoolExp b) -> Codec Object (SelPerm b) (BoolExp b)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SelPerm b -> BoolExp b
forall (b :: BackendType). SelPerm b -> BoolExp b
spFilter
Codec
Object
(SelPerm b)
(Maybe Int
-> Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Codec Object (SelPerm b) (Maybe Int)
-> Codec
Object
(SelPerm b)
(Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
forall a b.
Codec Object (SelPerm b) (a -> b)
-> Codec Object (SelPerm b) a -> Codec Object (SelPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Int) (Maybe Int)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"limit"
ObjectCodec (Maybe Int) (Maybe Int)
-> (SelPerm b -> Maybe Int) -> Codec Object (SelPerm b) (Maybe Int)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SelPerm b -> Maybe Int
forall (b :: BackendType). SelPerm b -> Maybe Int
spLimit
Codec
Object
(SelPerm b)
(Bool
-> [ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Codec Object (SelPerm b) Bool
-> Codec
Object
(SelPerm b)
([ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
forall a b.
Codec Object (SelPerm b) (a -> b)
-> Codec Object (SelPerm b) a -> Codec Object (SelPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Bool -> ObjectCodec Bool Bool
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"allow_aggregations" Bool
False
ObjectCodec Bool Bool
-> (SelPerm b -> Bool) -> Codec Object (SelPerm b) Bool
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SelPerm b -> Bool
forall (b :: BackendType). SelPerm b -> Bool
spAllowAggregations
Codec
Object
(SelPerm b)
([ComputedFieldName]
-> AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType
-> SelPerm b)
-> Codec Object (SelPerm b) [ComputedFieldName]
-> Codec
Object
(SelPerm b)
(AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType -> SelPerm b)
forall a b.
Codec Object (SelPerm b) (a -> b)
-> Codec Object (SelPerm b) a -> Codec Object (SelPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> [ComputedFieldName]
-> ObjectCodec [ComputedFieldName] [ComputedFieldName]
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"computed_fields" []
ObjectCodec [ComputedFieldName] [ComputedFieldName]
-> (SelPerm b -> [ComputedFieldName])
-> Codec Object (SelPerm b) [ComputedFieldName]
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SelPerm b -> [ComputedFieldName]
forall (b :: BackendType). SelPerm b -> [ComputedFieldName]
spComputedFields
Codec
Object
(SelPerm b)
(AllowedRootFields QueryRootFieldType
-> AllowedRootFields SubscriptionRootFieldType -> SelPerm b)
-> Codec Object (SelPerm b) (AllowedRootFields QueryRootFieldType)
-> Codec
Object
(SelPerm b)
(AllowedRootFields SubscriptionRootFieldType -> SelPerm b)
forall a b.
Codec Object (SelPerm b) (a -> b)
-> Codec Object (SelPerm b) a -> Codec Object (SelPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> AllowedRootFields QueryRootFieldType
-> ObjectCodec
(AllowedRootFields QueryRootFieldType)
(AllowedRootFields QueryRootFieldType)
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"query_root_fields" AllowedRootFields QueryRootFieldType
forall rootFieldType. AllowedRootFields rootFieldType
ARFAllowAllRootFields
ObjectCodec
(AllowedRootFields QueryRootFieldType)
(AllowedRootFields QueryRootFieldType)
-> (SelPerm b -> AllowedRootFields QueryRootFieldType)
-> Codec Object (SelPerm b) (AllowedRootFields QueryRootFieldType)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SelPerm b -> AllowedRootFields QueryRootFieldType
forall (b :: BackendType).
SelPerm b -> AllowedRootFields QueryRootFieldType
spAllowedQueryRootFields
Codec
Object
(SelPerm b)
(AllowedRootFields SubscriptionRootFieldType -> SelPerm b)
-> Codec
Object (SelPerm b) (AllowedRootFields SubscriptionRootFieldType)
-> ObjectCodec (SelPerm b) (SelPerm b)
forall a b.
Codec Object (SelPerm b) (a -> b)
-> Codec Object (SelPerm b) a -> Codec Object (SelPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> AllowedRootFields SubscriptionRootFieldType
-> ObjectCodec
(AllowedRootFields SubscriptionRootFieldType)
(AllowedRootFields SubscriptionRootFieldType)
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"subscription_root_fields" AllowedRootFields SubscriptionRootFieldType
forall rootFieldType. AllowedRootFields rootFieldType
ARFAllowAllRootFields
ObjectCodec
(AllowedRootFields SubscriptionRootFieldType)
(AllowedRootFields SubscriptionRootFieldType)
-> (SelPerm b -> AllowedRootFields SubscriptionRootFieldType)
-> Codec
Object (SelPerm b) (AllowedRootFields SubscriptionRootFieldType)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= SelPerm b -> AllowedRootFields SubscriptionRootFieldType
forall (b :: BackendType).
SelPerm b -> AllowedRootFields SubscriptionRootFieldType
spAllowedSubscriptionRootFields
type SelPermDef b = PermDef b SelPerm
data DelPerm (b :: BackendType) = DelPerm
{ forall (b :: BackendType). DelPerm b -> BoolExp b
dcFilter :: BoolExp b,
forall (b :: BackendType). DelPerm b -> Bool
dcBackendOnly :: Bool,
forall (b :: BackendType).
DelPerm b -> Maybe (ValidateInput InputWebhook)
dcValidateInput :: Maybe (ValidateInput InputWebhook)
}
deriving (Int -> DelPerm b -> ShowS
[DelPerm b] -> ShowS
DelPerm b -> String
(Int -> DelPerm b -> ShowS)
-> (DelPerm b -> String)
-> ([DelPerm b] -> ShowS)
-> Show (DelPerm b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType). Backend b => Int -> DelPerm b -> ShowS
forall (b :: BackendType). Backend b => [DelPerm b] -> ShowS
forall (b :: BackendType). Backend b => DelPerm b -> String
$cshowsPrec :: forall (b :: BackendType). Backend b => Int -> DelPerm b -> ShowS
showsPrec :: Int -> DelPerm b -> ShowS
$cshow :: forall (b :: BackendType). Backend b => DelPerm b -> String
show :: DelPerm b -> String
$cshowList :: forall (b :: BackendType). Backend b => [DelPerm b] -> ShowS
showList :: [DelPerm b] -> ShowS
Show, DelPerm b -> DelPerm b -> Bool
(DelPerm b -> DelPerm b -> Bool)
-> (DelPerm b -> DelPerm b -> Bool) -> Eq (DelPerm b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType).
Backend b =>
DelPerm b -> DelPerm b -> Bool
$c== :: forall (b :: BackendType).
Backend b =>
DelPerm b -> DelPerm b -> Bool
== :: DelPerm b -> DelPerm b -> Bool
$c/= :: forall (b :: BackendType).
Backend b =>
DelPerm b -> DelPerm b -> Bool
/= :: DelPerm b -> DelPerm b -> Bool
Eq, (forall x. DelPerm b -> Rep (DelPerm b) x)
-> (forall x. Rep (DelPerm b) x -> DelPerm b)
-> Generic (DelPerm b)
forall x. Rep (DelPerm b) x -> DelPerm b
forall x. DelPerm b -> Rep (DelPerm b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x. Rep (DelPerm b) x -> DelPerm b
forall (b :: BackendType) x. DelPerm b -> Rep (DelPerm b) x
$cfrom :: forall (b :: BackendType) x. DelPerm b -> Rep (DelPerm b) x
from :: forall x. DelPerm b -> Rep (DelPerm b) x
$cto :: forall (b :: BackendType) x. Rep (DelPerm b) x -> DelPerm b
to :: forall x. Rep (DelPerm b) x -> DelPerm b
Generic)
instance (Backend b) => FromJSON (DelPerm b) where
parseJSON :: Value -> Parser (DelPerm b)
parseJSON = String
-> (Object -> Parser (DelPerm b)) -> Value -> Parser (DelPerm b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"DelPerm" ((Object -> Parser (DelPerm b)) -> Value -> Parser (DelPerm b))
-> (Object -> Parser (DelPerm b)) -> Value -> Parser (DelPerm b)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
BoolExp b
-> Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b
forall (b :: BackendType).
BoolExp b
-> Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b
DelPerm
(BoolExp b
-> Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b)
-> Parser (BoolExp b)
-> Parser (Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser (BoolExp b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"filter"
Parser (Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b)
-> Parser Bool
-> Parser (Maybe (ValidateInput InputWebhook) -> DelPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"backend_only"
Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Parser (Maybe (ValidateInput InputWebhook) -> DelPerm b)
-> Parser (Maybe (ValidateInput InputWebhook))
-> Parser (DelPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe (ValidateInput InputWebhook))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"validate_input"
instance (Backend b) => ToJSON (DelPerm b) where
toJSON :: DelPerm b -> Value
toJSON = Options -> DelPerm b -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance (Backend b) => HasCodec (DelPerm b) where
codec :: JSONCodec (DelPerm b)
codec =
Text
-> ObjectCodec (DelPerm b) (DelPerm b) -> JSONCodec (DelPerm b)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"DelPerm")
(ObjectCodec (DelPerm b) (DelPerm b) -> JSONCodec (DelPerm b))
-> ObjectCodec (DelPerm b) (DelPerm b) -> JSONCodec (DelPerm b)
forall a b. (a -> b) -> a -> b
$ BoolExp b
-> Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b
forall (b :: BackendType).
BoolExp b
-> Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b
DelPerm
(BoolExp b
-> Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b)
-> Codec Object (DelPerm b) (BoolExp b)
-> Codec
Object
(DelPerm b)
(Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec (BoolExp b) (BoolExp b)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"filter"
ObjectCodec (BoolExp b) (BoolExp b)
-> (DelPerm b -> BoolExp b) -> Codec Object (DelPerm b) (BoolExp b)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.== DelPerm b -> BoolExp b
forall (b :: BackendType). DelPerm b -> BoolExp b
dcFilter
Codec
Object
(DelPerm b)
(Bool -> Maybe (ValidateInput InputWebhook) -> DelPerm b)
-> Codec Object (DelPerm b) Bool
-> Codec
Object
(DelPerm b)
(Maybe (ValidateInput InputWebhook) -> DelPerm b)
forall a b.
Codec Object (DelPerm b) (a -> b)
-> Codec Object (DelPerm b) a -> Codec Object (DelPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Bool -> ObjectCodec Bool Bool
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"backend_only" Bool
False
ObjectCodec Bool Bool
-> (DelPerm b -> Bool) -> Codec Object (DelPerm b) Bool
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.== DelPerm b -> Bool
forall (b :: BackendType). DelPerm b -> Bool
dcBackendOnly
Codec
Object
(DelPerm b)
(Maybe (ValidateInput InputWebhook) -> DelPerm b)
-> Codec Object (DelPerm b) (Maybe (ValidateInput InputWebhook))
-> ObjectCodec (DelPerm b) (DelPerm b)
forall a b.
Codec Object (DelPerm b) (a -> b)
-> Codec Object (DelPerm b) a -> Codec Object (DelPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe (ValidateInput InputWebhook))
(Maybe (ValidateInput InputWebhook))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"validate_input"
ObjectCodec
(Maybe (ValidateInput InputWebhook))
(Maybe (ValidateInput InputWebhook))
-> (DelPerm b -> Maybe (ValidateInput InputWebhook))
-> Codec Object (DelPerm b) (Maybe (ValidateInput InputWebhook))
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.== DelPerm b -> Maybe (ValidateInput InputWebhook)
forall (b :: BackendType).
DelPerm b -> Maybe (ValidateInput InputWebhook)
dcValidateInput
where
.== :: ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
(.==) = ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
(AC..=)
type DelPermDef b = PermDef b DelPerm
data UpdPerm (b :: BackendType) = UpdPerm
{ forall (b :: BackendType). UpdPerm b -> PermColSpec b
ucColumns :: PermColSpec b,
forall (b :: BackendType).
UpdPerm b -> Maybe (ColumnValues b Value)
ucSet :: Maybe (ColumnValues b Value),
forall (b :: BackendType). UpdPerm b -> BoolExp b
ucFilter :: BoolExp b,
forall (b :: BackendType). UpdPerm b -> Maybe (BoolExp b)
ucCheck :: Maybe (BoolExp b),
forall (b :: BackendType). UpdPerm b -> Bool
ucBackendOnly :: Bool,
forall (b :: BackendType).
UpdPerm b -> Maybe (ValidateInput InputWebhook)
ucValidateInput :: Maybe (ValidateInput InputWebhook)
}
deriving (Int -> UpdPerm b -> ShowS
[UpdPerm b] -> ShowS
UpdPerm b -> String
(Int -> UpdPerm b -> ShowS)
-> (UpdPerm b -> String)
-> ([UpdPerm b] -> ShowS)
-> Show (UpdPerm b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (b :: BackendType). Backend b => Int -> UpdPerm b -> ShowS
forall (b :: BackendType). Backend b => [UpdPerm b] -> ShowS
forall (b :: BackendType). Backend b => UpdPerm b -> String
$cshowsPrec :: forall (b :: BackendType). Backend b => Int -> UpdPerm b -> ShowS
showsPrec :: Int -> UpdPerm b -> ShowS
$cshow :: forall (b :: BackendType). Backend b => UpdPerm b -> String
show :: UpdPerm b -> String
$cshowList :: forall (b :: BackendType). Backend b => [UpdPerm b] -> ShowS
showList :: [UpdPerm b] -> ShowS
Show, UpdPerm b -> UpdPerm b -> Bool
(UpdPerm b -> UpdPerm b -> Bool)
-> (UpdPerm b -> UpdPerm b -> Bool) -> Eq (UpdPerm b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (b :: BackendType).
Backend b =>
UpdPerm b -> UpdPerm b -> Bool
$c== :: forall (b :: BackendType).
Backend b =>
UpdPerm b -> UpdPerm b -> Bool
== :: UpdPerm b -> UpdPerm b -> Bool
$c/= :: forall (b :: BackendType).
Backend b =>
UpdPerm b -> UpdPerm b -> Bool
/= :: UpdPerm b -> UpdPerm b -> Bool
Eq, (forall x. UpdPerm b -> Rep (UpdPerm b) x)
-> (forall x. Rep (UpdPerm b) x -> UpdPerm b)
-> Generic (UpdPerm b)
forall x. Rep (UpdPerm b) x -> UpdPerm b
forall x. UpdPerm b -> Rep (UpdPerm b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x. Rep (UpdPerm b) x -> UpdPerm b
forall (b :: BackendType) x. UpdPerm b -> Rep (UpdPerm b) x
$cfrom :: forall (b :: BackendType) x. UpdPerm b -> Rep (UpdPerm b) x
from :: forall x. UpdPerm b -> Rep (UpdPerm b) x
$cto :: forall (b :: BackendType) x. Rep (UpdPerm b) x -> UpdPerm b
to :: forall x. Rep (UpdPerm b) x -> UpdPerm b
Generic)
instance (Backend b) => FromJSON (UpdPerm b) where
parseJSON :: Value -> Parser (UpdPerm b)
parseJSON = String
-> (Object -> Parser (UpdPerm b)) -> Value -> Parser (UpdPerm b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UpdPerm" ((Object -> Parser (UpdPerm b)) -> Value -> Parser (UpdPerm b))
-> (Object -> Parser (UpdPerm b)) -> Value -> Parser (UpdPerm b)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
PermColSpec b
-> Maybe (HashMap (Column b) Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b
forall (b :: BackendType).
PermColSpec b
-> Maybe (ColumnValues b Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b
UpdPerm
(PermColSpec b
-> Maybe (HashMap (Column b) Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
-> Parser (PermColSpec b)
-> Parser
(Maybe (HashMap (Column b) Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser (PermColSpec b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"columns"
Parser
(Maybe (HashMap (Column b) Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
-> Parser (Maybe (HashMap (Column b) Value))
-> Parser
(BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe (HashMap (Column b) Value))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"set"
Parser
(BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
-> Parser (BoolExp b)
-> Parser
(Maybe (BoolExp b)
-> Bool -> Maybe (ValidateInput InputWebhook) -> UpdPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (BoolExp b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"filter"
Parser
(Maybe (BoolExp b)
-> Bool -> Maybe (ValidateInput InputWebhook) -> UpdPerm b)
-> Parser (Maybe (BoolExp b))
-> Parser (Bool -> Maybe (ValidateInput InputWebhook) -> UpdPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe (BoolExp b))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"check"
Parser (Bool -> Maybe (ValidateInput InputWebhook) -> UpdPerm b)
-> Parser Bool
-> Parser (Maybe (ValidateInput InputWebhook) -> UpdPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"backend_only"
Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Parser (Maybe (ValidateInput InputWebhook) -> UpdPerm b)
-> Parser (Maybe (ValidateInput InputWebhook))
-> Parser (UpdPerm b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe (ValidateInput InputWebhook))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"validate_input"
instance (Backend b) => ToJSON (UpdPerm b) where
toJSON :: UpdPerm b -> Value
toJSON = Options -> UpdPerm b -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
hasuraJSON {omitNothingFields :: Bool
omitNothingFields = Bool
True}
instance (Backend b) => HasCodec (UpdPerm b) where
codec :: JSONCodec (UpdPerm b)
codec =
Text
-> ObjectCodec (UpdPerm b) (UpdPerm b) -> JSONCodec (UpdPerm b)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"UpdPerm")
(ObjectCodec (UpdPerm b) (UpdPerm b) -> JSONCodec (UpdPerm b))
-> ObjectCodec (UpdPerm b) (UpdPerm b) -> JSONCodec (UpdPerm b)
forall a b. (a -> b) -> a -> b
$ PermColSpec b
-> Maybe (HashMap (Column b) Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b
forall (b :: BackendType).
PermColSpec b
-> Maybe (ColumnValues b Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b
UpdPerm
(PermColSpec b
-> Maybe (HashMap (Column b) Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
-> Codec Object (UpdPerm b) (PermColSpec b)
-> Codec
Object
(UpdPerm b)
(Maybe (HashMap (Column b) Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> ObjectCodec (PermColSpec b) (PermColSpec b)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec output output
requiredField Text
"columns" Text
"Allowed columns"
ObjectCodec (PermColSpec b) (PermColSpec b)
-> (UpdPerm b -> PermColSpec b)
-> Codec Object (UpdPerm b) (PermColSpec b)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= UpdPerm b -> PermColSpec b
forall (b :: BackendType). UpdPerm b -> PermColSpec b
ucColumns
Codec
Object
(UpdPerm b)
(Maybe (HashMap (Column b) Value)
-> BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
-> Codec Object (UpdPerm b) (Maybe (HashMap (Column b) Value))
-> Codec
Object
(UpdPerm b)
(BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
forall a b.
Codec Object (UpdPerm b) (a -> b)
-> Codec Object (UpdPerm b) a -> Codec Object (UpdPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> Text
-> ObjectCodec
(Maybe (HashMap (Column b) Value))
(Maybe (HashMap (Column b) Value))
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"set" Text
"Preset columns"
ObjectCodec
(Maybe (HashMap (Column b) Value))
(Maybe (HashMap (Column b) Value))
-> (UpdPerm b -> Maybe (HashMap (Column b) Value))
-> Codec Object (UpdPerm b) (Maybe (HashMap (Column b) Value))
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= UpdPerm b -> Maybe (HashMap (Column b) Value)
forall (b :: BackendType).
UpdPerm b -> Maybe (ColumnValues b Value)
ucSet
Codec
Object
(UpdPerm b)
(BoolExp b
-> Maybe (BoolExp b)
-> Bool
-> Maybe (ValidateInput InputWebhook)
-> UpdPerm b)
-> Codec Object (UpdPerm b) (BoolExp b)
-> Codec
Object
(UpdPerm b)
(Maybe (BoolExp b)
-> Bool -> Maybe (ValidateInput InputWebhook) -> UpdPerm b)
forall a b.
Codec Object (UpdPerm b) (a -> b)
-> Codec Object (UpdPerm b) a -> Codec Object (UpdPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (BoolExp b) (BoolExp b)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"filter"
ObjectCodec (BoolExp b) (BoolExp b)
-> (UpdPerm b -> BoolExp b) -> Codec Object (UpdPerm b) (BoolExp b)
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= UpdPerm b -> BoolExp b
forall (b :: BackendType). UpdPerm b -> BoolExp b
ucFilter
Codec
Object
(UpdPerm b)
(Maybe (BoolExp b)
-> Bool -> Maybe (ValidateInput InputWebhook) -> UpdPerm b)
-> Codec Object (UpdPerm b) (Maybe (BoolExp b))
-> Codec
Object
(UpdPerm b)
(Bool -> Maybe (ValidateInput InputWebhook) -> UpdPerm b)
forall a b.
Codec Object (UpdPerm b) (a -> b)
-> Codec Object (UpdPerm b) a -> Codec Object (UpdPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe (BoolExp b)) (Maybe (BoolExp b))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalFieldOrIncludedNull' Text
"check"
ObjectCodec (Maybe (BoolExp b)) (Maybe (BoolExp b))
-> (UpdPerm b -> Maybe (BoolExp b))
-> Codec Object (UpdPerm b) (Maybe (BoolExp b))
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= UpdPerm b -> Maybe (BoolExp b)
forall (b :: BackendType). UpdPerm b -> Maybe (BoolExp b)
ucCheck
Codec
Object
(UpdPerm b)
(Bool -> Maybe (ValidateInput InputWebhook) -> UpdPerm b)
-> Codec Object (UpdPerm b) Bool
-> Codec
Object
(UpdPerm b)
(Maybe (ValidateInput InputWebhook) -> UpdPerm b)
forall a b.
Codec Object (UpdPerm b) (a -> b)
-> Codec Object (UpdPerm b) a -> Codec Object (UpdPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Bool -> ObjectCodec Bool Bool
forall output.
(Eq output, HasCodec output) =>
Text -> output -> ObjectCodec output output
optionalFieldWithOmittedDefault' Text
"backend_only" Bool
False
ObjectCodec Bool Bool
-> (UpdPerm b -> Bool) -> Codec Object (UpdPerm b) Bool
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= UpdPerm b -> Bool
forall (b :: BackendType). UpdPerm b -> Bool
ucBackendOnly
Codec
Object
(UpdPerm b)
(Maybe (ValidateInput InputWebhook) -> UpdPerm b)
-> Codec Object (UpdPerm b) (Maybe (ValidateInput InputWebhook))
-> ObjectCodec (UpdPerm b) (UpdPerm b)
forall a b.
Codec Object (UpdPerm b) (a -> b)
-> Codec Object (UpdPerm b) a -> Codec Object (UpdPerm b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe (ValidateInput InputWebhook))
(Maybe (ValidateInput InputWebhook))
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"validate_input"
ObjectCodec
(Maybe (ValidateInput InputWebhook))
(Maybe (ValidateInput InputWebhook))
-> (UpdPerm b -> Maybe (ValidateInput InputWebhook))
-> Codec Object (UpdPerm b) (Maybe (ValidateInput InputWebhook))
forall {oldInput} {output} {newInput}.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= UpdPerm b -> Maybe (ValidateInput InputWebhook)
forall (b :: BackendType).
UpdPerm b -> Maybe (ValidateInput InputWebhook)
ucValidateInput
type UpdPermDef b = PermDef b UpdPerm
$(return [])
instance (Backend b) => FromJSON (PermDef b SelPerm) where
parseJSON :: Value -> Parser (PermDef b SelPerm)
parseJSON = Options -> Value -> Parser (PermDef b SelPerm)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON
instance (Backend b) => FromJSON (PermDef b InsPerm) where
parseJSON :: Value -> Parser (PermDef b InsPerm)
parseJSON = Options -> Value -> Parser (PermDef b InsPerm)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON
instance (Backend b) => FromJSON (PermDef b UpdPerm) where
parseJSON :: Value -> Parser (PermDef b UpdPerm)
parseJSON = Options -> Value -> Parser (PermDef b UpdPerm)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON
instance (Backend b) => FromJSON (PermDef b DelPerm) where
parseJSON :: Value -> Parser (PermDef b DelPerm)
parseJSON = Options -> Value -> Parser (PermDef b DelPerm)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
hasuraJSON
$