module Hasura.RQL.DDL.Metadata.Types
(
ExportMetadata (..),
ReplaceMetadata (..),
ReplaceMetadataV1 (..),
ReplaceMetadataV2 (..),
AllowInconsistentMetadata (..),
ReloadMetadata (..),
ReloadSpec (..),
ClearMetadata (..),
GetInconsistentMetadata (..),
DropInconsistentMetadata (..),
TestWebhookTransform (..),
twtRequestTransformer,
twtResponseTransformer,
WebHookUrl (..),
DumpInternalState (..),
)
where
import Control.Lens (Lens')
import Control.Lens qualified as Lens
import Data.Aeson (FromJSON, ToJSON, (.!=), (.:), (.:?), (.=))
import Data.Aeson qualified as J
import Data.Aeson.KeyMap qualified as KeyMap
import Data.CaseInsensitive qualified as CI
import Data.Environment qualified as Env
import Hasura.Backends.DataConnector.Adapter.Types (DataConnectorName)
import Hasura.Prelude
import Hasura.RQL.DDL.Warnings (AllowWarnings (..))
import Hasura.RQL.DDL.Webhook.Transform (MetadataResponseTransform, RequestTransform)
import Hasura.RQL.Types.Common qualified as Common
import Hasura.RQL.Types.Metadata (Metadata, MetadataNoSources)
import Hasura.RQL.Types.Metadata qualified as Metadata
import Hasura.RemoteSchema.Metadata (RemoteSchemaName)
import Hasura.Session (SessionVariables)
import Network.HTTP.Client.Transformable qualified as HTTP
data ClearMetadata
= ClearMetadata
deriving (Int -> ClearMetadata -> ShowS
[ClearMetadata] -> ShowS
ClearMetadata -> String
(Int -> ClearMetadata -> ShowS)
-> (ClearMetadata -> String)
-> ([ClearMetadata] -> ShowS)
-> Show ClearMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClearMetadata -> ShowS
showsPrec :: Int -> ClearMetadata -> ShowS
$cshow :: ClearMetadata -> String
show :: ClearMetadata -> String
$cshowList :: [ClearMetadata] -> ShowS
showList :: [ClearMetadata] -> ShowS
Show, (forall x. ClearMetadata -> Rep ClearMetadata x)
-> (forall x. Rep ClearMetadata x -> ClearMetadata)
-> Generic ClearMetadata
forall x. Rep ClearMetadata x -> ClearMetadata
forall x. ClearMetadata -> Rep ClearMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ClearMetadata -> Rep ClearMetadata x
from :: forall x. ClearMetadata -> Rep ClearMetadata x
$cto :: forall x. Rep ClearMetadata x -> ClearMetadata
to :: forall x. Rep ClearMetadata x -> ClearMetadata
Generic, ClearMetadata -> ClearMetadata -> Bool
(ClearMetadata -> ClearMetadata -> Bool)
-> (ClearMetadata -> ClearMetadata -> Bool) -> Eq ClearMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClearMetadata -> ClearMetadata -> Bool
== :: ClearMetadata -> ClearMetadata -> Bool
$c/= :: ClearMetadata -> ClearMetadata -> Bool
/= :: ClearMetadata -> ClearMetadata -> Bool
Eq)
instance J.ToJSON ClearMetadata where
toJSON :: ClearMetadata -> Value
toJSON = Options -> ClearMetadata -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON Options
J.defaultOptions
toEncoding :: ClearMetadata -> Encoding
toEncoding = Options -> ClearMetadata -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
J.genericToEncoding Options
J.defaultOptions
instance FromJSON ClearMetadata where
parseJSON :: Value -> Parser ClearMetadata
parseJSON Value
_ = ClearMetadata -> Parser ClearMetadata
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ClearMetadata
ClearMetadata
data ExportMetadata = ExportMetadata deriving (Int -> ExportMetadata -> ShowS
[ExportMetadata] -> ShowS
ExportMetadata -> String
(Int -> ExportMetadata -> ShowS)
-> (ExportMetadata -> String)
-> ([ExportMetadata] -> ShowS)
-> Show ExportMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExportMetadata -> ShowS
showsPrec :: Int -> ExportMetadata -> ShowS
$cshow :: ExportMetadata -> String
show :: ExportMetadata -> String
$cshowList :: [ExportMetadata] -> ShowS
showList :: [ExportMetadata] -> ShowS
Show, ExportMetadata -> ExportMetadata -> Bool
(ExportMetadata -> ExportMetadata -> Bool)
-> (ExportMetadata -> ExportMetadata -> Bool) -> Eq ExportMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExportMetadata -> ExportMetadata -> Bool
== :: ExportMetadata -> ExportMetadata -> Bool
$c/= :: ExportMetadata -> ExportMetadata -> Bool
/= :: ExportMetadata -> ExportMetadata -> Bool
Eq)
instance ToJSON ExportMetadata where
toJSON :: ExportMetadata -> Value
toJSON ExportMetadata
ExportMetadata = [Pair] -> Value
J.object []
instance FromJSON ExportMetadata where
parseJSON :: Value -> Parser ExportMetadata
parseJSON Value
_ = ExportMetadata -> Parser ExportMetadata
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExportMetadata
ExportMetadata
data ReloadSpec a
= RSReloadAll
| RSReloadList (HashSet a)
deriving (Int -> ReloadSpec a -> ShowS
[ReloadSpec a] -> ShowS
ReloadSpec a -> String
(Int -> ReloadSpec a -> ShowS)
-> (ReloadSpec a -> String)
-> ([ReloadSpec a] -> ShowS)
-> Show (ReloadSpec a)
forall a. Show a => Int -> ReloadSpec a -> ShowS
forall a. Show a => [ReloadSpec a] -> ShowS
forall a. Show a => ReloadSpec a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> ReloadSpec a -> ShowS
showsPrec :: Int -> ReloadSpec a -> ShowS
$cshow :: forall a. Show a => ReloadSpec a -> String
show :: ReloadSpec a -> String
$cshowList :: forall a. Show a => [ReloadSpec a] -> ShowS
showList :: [ReloadSpec a] -> ShowS
Show, ReloadSpec a -> ReloadSpec a -> Bool
(ReloadSpec a -> ReloadSpec a -> Bool)
-> (ReloadSpec a -> ReloadSpec a -> Bool) -> Eq (ReloadSpec a)
forall a. Eq a => ReloadSpec a -> ReloadSpec a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => ReloadSpec a -> ReloadSpec a -> Bool
== :: ReloadSpec a -> ReloadSpec a -> Bool
$c/= :: forall a. Eq a => ReloadSpec a -> ReloadSpec a -> Bool
/= :: ReloadSpec a -> ReloadSpec a -> Bool
Eq)
instance (ToJSON a) => ToJSON (ReloadSpec a) where
toJSON :: ReloadSpec a -> Value
toJSON = \case
ReloadSpec a
RSReloadAll -> Bool -> Value
J.Bool Bool
True
RSReloadList HashSet a
l -> HashSet a -> Value
forall a. ToJSON a => a -> Value
J.toJSON HashSet a
l
instance (FromJSON a, Hashable a) => FromJSON (ReloadSpec a) where
parseJSON :: Value -> Parser (ReloadSpec a)
parseJSON (J.Bool Bool
b) = ReloadSpec a -> Parser (ReloadSpec a)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ReloadSpec a -> Parser (ReloadSpec a))
-> ReloadSpec a -> Parser (ReloadSpec a)
forall a b. (a -> b) -> a -> b
$ if Bool
b then ReloadSpec a
forall a. ReloadSpec a
RSReloadAll else HashSet a -> ReloadSpec a
forall a. HashSet a -> ReloadSpec a
RSReloadList HashSet a
forall a. Monoid a => a
mempty
parseJSON Value
v = HashSet a -> ReloadSpec a
forall a. HashSet a -> ReloadSpec a
RSReloadList (HashSet a -> ReloadSpec a)
-> Parser (HashSet a) -> Parser (ReloadSpec a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (HashSet a)
forall a. FromJSON a => Value -> Parser a
J.parseJSON Value
v
type ReloadRemoteSchemas = ReloadSpec RemoteSchemaName
type ReloadSources = ReloadSpec Common.SourceName
type ReloadDataConnectors = ReloadSpec DataConnectorName
reloadAllRemoteSchemas :: ReloadRemoteSchemas
reloadAllRemoteSchemas :: ReloadRemoteSchemas
reloadAllRemoteSchemas = ReloadRemoteSchemas
forall a. ReloadSpec a
RSReloadAll
reloadAllSources :: ReloadSources
reloadAllSources :: ReloadSources
reloadAllSources = ReloadSources
forall a. ReloadSpec a
RSReloadAll
reloadAllDataConnectors :: ReloadDataConnectors
reloadAllDataConnectors :: ReloadDataConnectors
reloadAllDataConnectors = ReloadDataConnectors
forall a. ReloadSpec a
RSReloadAll
data ReloadMetadata = ReloadMetadata
{ ReloadMetadata -> ReloadRemoteSchemas
_rmReloadRemoteSchemas :: ReloadRemoteSchemas,
ReloadMetadata -> ReloadSources
_rmReloadSources :: ReloadSources,
ReloadMetadata -> ReloadSources
_rmRecreateEventTriggers :: ReloadSources,
ReloadMetadata -> ReloadDataConnectors
_rmReloadDataConnectors :: ReloadDataConnectors
}
deriving (Int -> ReloadMetadata -> ShowS
[ReloadMetadata] -> ShowS
ReloadMetadata -> String
(Int -> ReloadMetadata -> ShowS)
-> (ReloadMetadata -> String)
-> ([ReloadMetadata] -> ShowS)
-> Show ReloadMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReloadMetadata -> ShowS
showsPrec :: Int -> ReloadMetadata -> ShowS
$cshow :: ReloadMetadata -> String
show :: ReloadMetadata -> String
$cshowList :: [ReloadMetadata] -> ShowS
showList :: [ReloadMetadata] -> ShowS
Show, (forall x. ReloadMetadata -> Rep ReloadMetadata x)
-> (forall x. Rep ReloadMetadata x -> ReloadMetadata)
-> Generic ReloadMetadata
forall x. Rep ReloadMetadata x -> ReloadMetadata
forall x. ReloadMetadata -> Rep ReloadMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReloadMetadata -> Rep ReloadMetadata x
from :: forall x. ReloadMetadata -> Rep ReloadMetadata x
$cto :: forall x. Rep ReloadMetadata x -> ReloadMetadata
to :: forall x. Rep ReloadMetadata x -> ReloadMetadata
Generic, ReloadMetadata -> ReloadMetadata -> Bool
(ReloadMetadata -> ReloadMetadata -> Bool)
-> (ReloadMetadata -> ReloadMetadata -> Bool) -> Eq ReloadMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReloadMetadata -> ReloadMetadata -> Bool
== :: ReloadMetadata -> ReloadMetadata -> Bool
$c/= :: ReloadMetadata -> ReloadMetadata -> Bool
/= :: ReloadMetadata -> ReloadMetadata -> Bool
Eq)
instance J.ToJSON ReloadMetadata where
toJSON :: ReloadMetadata -> Value
toJSON = Options -> ReloadMetadata -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON Options
hasuraJSON
toEncoding :: ReloadMetadata -> Encoding
toEncoding = Options -> ReloadMetadata -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
J.genericToEncoding Options
hasuraJSON
instance FromJSON ReloadMetadata where
parseJSON :: Value -> Parser ReloadMetadata
parseJSON = String
-> (Object -> Parser ReloadMetadata)
-> Value
-> Parser ReloadMetadata
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"ReloadMetadata" ((Object -> Parser ReloadMetadata)
-> Value -> Parser ReloadMetadata)
-> (Object -> Parser ReloadMetadata)
-> Value
-> Parser ReloadMetadata
forall a b. (a -> b) -> a -> b
$ \Object
o ->
ReloadRemoteSchemas
-> ReloadSources
-> ReloadSources
-> ReloadDataConnectors
-> ReloadMetadata
ReloadMetadata
(ReloadRemoteSchemas
-> ReloadSources
-> ReloadSources
-> ReloadDataConnectors
-> ReloadMetadata)
-> Parser ReloadRemoteSchemas
-> Parser
(ReloadSources
-> ReloadSources -> ReloadDataConnectors -> ReloadMetadata)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser (Maybe ReloadRemoteSchemas)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"reload_remote_schemas"
Parser (Maybe ReloadRemoteSchemas)
-> ReloadRemoteSchemas -> Parser ReloadRemoteSchemas
forall a. Parser (Maybe a) -> a -> Parser a
.!= ReloadRemoteSchemas
reloadAllRemoteSchemas
Parser
(ReloadSources
-> ReloadSources -> ReloadDataConnectors -> ReloadMetadata)
-> Parser ReloadSources
-> Parser (ReloadSources -> ReloadDataConnectors -> ReloadMetadata)
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 ReloadSources)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"reload_sources"
Parser (Maybe ReloadSources)
-> ReloadSources -> Parser ReloadSources
forall a. Parser (Maybe a) -> a -> Parser a
.!= ReloadSources
reloadAllSources
Parser (ReloadSources -> ReloadDataConnectors -> ReloadMetadata)
-> Parser ReloadSources
-> Parser (ReloadDataConnectors -> ReloadMetadata)
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 ReloadSources)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"recreate_event_triggers"
Parser (Maybe ReloadSources)
-> ReloadSources -> Parser ReloadSources
forall a. Parser (Maybe a) -> a -> Parser a
.!= HashSet SourceName -> ReloadSources
forall a. HashSet a -> ReloadSpec a
RSReloadList HashSet SourceName
forall a. Monoid a => a
mempty
Parser (ReloadDataConnectors -> ReloadMetadata)
-> Parser ReloadDataConnectors -> Parser ReloadMetadata
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 ReloadDataConnectors)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"reload_data_connectors"
Parser (Maybe ReloadDataConnectors)
-> ReloadDataConnectors -> Parser ReloadDataConnectors
forall a. Parser (Maybe a) -> a -> Parser a
.!= ReloadDataConnectors
reloadAllDataConnectors
data DumpInternalState
= DumpInternalState
deriving (Int -> DumpInternalState -> ShowS
[DumpInternalState] -> ShowS
DumpInternalState -> String
(Int -> DumpInternalState -> ShowS)
-> (DumpInternalState -> String)
-> ([DumpInternalState] -> ShowS)
-> Show DumpInternalState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DumpInternalState -> ShowS
showsPrec :: Int -> DumpInternalState -> ShowS
$cshow :: DumpInternalState -> String
show :: DumpInternalState -> String
$cshowList :: [DumpInternalState] -> ShowS
showList :: [DumpInternalState] -> ShowS
Show, (forall x. DumpInternalState -> Rep DumpInternalState x)
-> (forall x. Rep DumpInternalState x -> DumpInternalState)
-> Generic DumpInternalState
forall x. Rep DumpInternalState x -> DumpInternalState
forall x. DumpInternalState -> Rep DumpInternalState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DumpInternalState -> Rep DumpInternalState x
from :: forall x. DumpInternalState -> Rep DumpInternalState x
$cto :: forall x. Rep DumpInternalState x -> DumpInternalState
to :: forall x. Rep DumpInternalState x -> DumpInternalState
Generic, DumpInternalState -> DumpInternalState -> Bool
(DumpInternalState -> DumpInternalState -> Bool)
-> (DumpInternalState -> DumpInternalState -> Bool)
-> Eq DumpInternalState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DumpInternalState -> DumpInternalState -> Bool
== :: DumpInternalState -> DumpInternalState -> Bool
$c/= :: DumpInternalState -> DumpInternalState -> Bool
/= :: DumpInternalState -> DumpInternalState -> Bool
Eq)
instance J.ToJSON DumpInternalState where
toJSON :: DumpInternalState -> Value
toJSON = Options -> DumpInternalState -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON Options
J.defaultOptions
toEncoding :: DumpInternalState -> Encoding
toEncoding = Options -> DumpInternalState -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
J.genericToEncoding Options
J.defaultOptions
instance FromJSON DumpInternalState where
parseJSON :: Value -> Parser DumpInternalState
parseJSON Value
_ = DumpInternalState -> Parser DumpInternalState
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return DumpInternalState
DumpInternalState
data GetInconsistentMetadata
= GetInconsistentMetadata
deriving (Int -> GetInconsistentMetadata -> ShowS
[GetInconsistentMetadata] -> ShowS
GetInconsistentMetadata -> String
(Int -> GetInconsistentMetadata -> ShowS)
-> (GetInconsistentMetadata -> String)
-> ([GetInconsistentMetadata] -> ShowS)
-> Show GetInconsistentMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetInconsistentMetadata -> ShowS
showsPrec :: Int -> GetInconsistentMetadata -> ShowS
$cshow :: GetInconsistentMetadata -> String
show :: GetInconsistentMetadata -> String
$cshowList :: [GetInconsistentMetadata] -> ShowS
showList :: [GetInconsistentMetadata] -> ShowS
Show, (forall x.
GetInconsistentMetadata -> Rep GetInconsistentMetadata x)
-> (forall x.
Rep GetInconsistentMetadata x -> GetInconsistentMetadata)
-> Generic GetInconsistentMetadata
forall x. Rep GetInconsistentMetadata x -> GetInconsistentMetadata
forall x. GetInconsistentMetadata -> Rep GetInconsistentMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GetInconsistentMetadata -> Rep GetInconsistentMetadata x
from :: forall x. GetInconsistentMetadata -> Rep GetInconsistentMetadata x
$cto :: forall x. Rep GetInconsistentMetadata x -> GetInconsistentMetadata
to :: forall x. Rep GetInconsistentMetadata x -> GetInconsistentMetadata
Generic, GetInconsistentMetadata -> GetInconsistentMetadata -> Bool
(GetInconsistentMetadata -> GetInconsistentMetadata -> Bool)
-> (GetInconsistentMetadata -> GetInconsistentMetadata -> Bool)
-> Eq GetInconsistentMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetInconsistentMetadata -> GetInconsistentMetadata -> Bool
== :: GetInconsistentMetadata -> GetInconsistentMetadata -> Bool
$c/= :: GetInconsistentMetadata -> GetInconsistentMetadata -> Bool
/= :: GetInconsistentMetadata -> GetInconsistentMetadata -> Bool
Eq)
instance J.ToJSON GetInconsistentMetadata where
toJSON :: GetInconsistentMetadata -> Value
toJSON = Options -> GetInconsistentMetadata -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON Options
J.defaultOptions
toEncoding :: GetInconsistentMetadata -> Encoding
toEncoding = Options -> GetInconsistentMetadata -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
J.genericToEncoding Options
J.defaultOptions
instance FromJSON GetInconsistentMetadata where
parseJSON :: Value -> Parser GetInconsistentMetadata
parseJSON Value
_ = GetInconsistentMetadata -> Parser GetInconsistentMetadata
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return GetInconsistentMetadata
GetInconsistentMetadata
data DropInconsistentMetadata
= DropInconsistentMetadata
deriving (Int -> DropInconsistentMetadata -> ShowS
[DropInconsistentMetadata] -> ShowS
DropInconsistentMetadata -> String
(Int -> DropInconsistentMetadata -> ShowS)
-> (DropInconsistentMetadata -> String)
-> ([DropInconsistentMetadata] -> ShowS)
-> Show DropInconsistentMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DropInconsistentMetadata -> ShowS
showsPrec :: Int -> DropInconsistentMetadata -> ShowS
$cshow :: DropInconsistentMetadata -> String
show :: DropInconsistentMetadata -> String
$cshowList :: [DropInconsistentMetadata] -> ShowS
showList :: [DropInconsistentMetadata] -> ShowS
Show, (forall x.
DropInconsistentMetadata -> Rep DropInconsistentMetadata x)
-> (forall x.
Rep DropInconsistentMetadata x -> DropInconsistentMetadata)
-> Generic DropInconsistentMetadata
forall x.
Rep DropInconsistentMetadata x -> DropInconsistentMetadata
forall x.
DropInconsistentMetadata -> Rep DropInconsistentMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
DropInconsistentMetadata -> Rep DropInconsistentMetadata x
from :: forall x.
DropInconsistentMetadata -> Rep DropInconsistentMetadata x
$cto :: forall x.
Rep DropInconsistentMetadata x -> DropInconsistentMetadata
to :: forall x.
Rep DropInconsistentMetadata x -> DropInconsistentMetadata
Generic, DropInconsistentMetadata -> DropInconsistentMetadata -> Bool
(DropInconsistentMetadata -> DropInconsistentMetadata -> Bool)
-> (DropInconsistentMetadata -> DropInconsistentMetadata -> Bool)
-> Eq DropInconsistentMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DropInconsistentMetadata -> DropInconsistentMetadata -> Bool
== :: DropInconsistentMetadata -> DropInconsistentMetadata -> Bool
$c/= :: DropInconsistentMetadata -> DropInconsistentMetadata -> Bool
/= :: DropInconsistentMetadata -> DropInconsistentMetadata -> Bool
Eq)
instance J.ToJSON DropInconsistentMetadata where
toJSON :: DropInconsistentMetadata -> Value
toJSON = Options -> DropInconsistentMetadata -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON Options
J.defaultOptions
toEncoding :: DropInconsistentMetadata -> Encoding
toEncoding = Options -> DropInconsistentMetadata -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
J.genericToEncoding Options
J.defaultOptions
instance FromJSON DropInconsistentMetadata where
parseJSON :: Value -> Parser DropInconsistentMetadata
parseJSON Value
_ = DropInconsistentMetadata -> Parser DropInconsistentMetadata
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return DropInconsistentMetadata
DropInconsistentMetadata
data AllowInconsistentMetadata
= AllowInconsistentMetadata
| NoAllowInconsistentMetadata
deriving (Int -> AllowInconsistentMetadata -> ShowS
[AllowInconsistentMetadata] -> ShowS
AllowInconsistentMetadata -> String
(Int -> AllowInconsistentMetadata -> ShowS)
-> (AllowInconsistentMetadata -> String)
-> ([AllowInconsistentMetadata] -> ShowS)
-> Show AllowInconsistentMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AllowInconsistentMetadata -> ShowS
showsPrec :: Int -> AllowInconsistentMetadata -> ShowS
$cshow :: AllowInconsistentMetadata -> String
show :: AllowInconsistentMetadata -> String
$cshowList :: [AllowInconsistentMetadata] -> ShowS
showList :: [AllowInconsistentMetadata] -> ShowS
Show, AllowInconsistentMetadata -> AllowInconsistentMetadata -> Bool
(AllowInconsistentMetadata -> AllowInconsistentMetadata -> Bool)
-> (AllowInconsistentMetadata -> AllowInconsistentMetadata -> Bool)
-> Eq AllowInconsistentMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AllowInconsistentMetadata -> AllowInconsistentMetadata -> Bool
== :: AllowInconsistentMetadata -> AllowInconsistentMetadata -> Bool
$c/= :: AllowInconsistentMetadata -> AllowInconsistentMetadata -> Bool
/= :: AllowInconsistentMetadata -> AllowInconsistentMetadata -> Bool
Eq)
instance FromJSON AllowInconsistentMetadata where
parseJSON :: Value -> Parser AllowInconsistentMetadata
parseJSON =
String
-> (Bool -> Parser AllowInconsistentMetadata)
-> Value
-> Parser AllowInconsistentMetadata
forall a. String -> (Bool -> Parser a) -> Value -> Parser a
J.withBool String
"AllowInconsistentMetadata"
((Bool -> Parser AllowInconsistentMetadata)
-> Value -> Parser AllowInconsistentMetadata)
-> (Bool -> Parser AllowInconsistentMetadata)
-> Value
-> Parser AllowInconsistentMetadata
forall a b. (a -> b) -> a -> b
$ AllowInconsistentMetadata -> Parser AllowInconsistentMetadata
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(AllowInconsistentMetadata -> Parser AllowInconsistentMetadata)
-> (Bool -> AllowInconsistentMetadata)
-> Bool
-> Parser AllowInconsistentMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AllowInconsistentMetadata
-> AllowInconsistentMetadata -> Bool -> AllowInconsistentMetadata
forall a. a -> a -> Bool -> a
bool AllowInconsistentMetadata
NoAllowInconsistentMetadata AllowInconsistentMetadata
AllowInconsistentMetadata
instance ToJSON AllowInconsistentMetadata where
toJSON :: AllowInconsistentMetadata -> Value
toJSON = Bool -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Bool -> Value)
-> (AllowInconsistentMetadata -> Bool)
-> AllowInconsistentMetadata
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AllowInconsistentMetadata -> Bool
toBool
where
toBool :: AllowInconsistentMetadata -> Bool
toBool AllowInconsistentMetadata
AllowInconsistentMetadata = Bool
True
toBool AllowInconsistentMetadata
NoAllowInconsistentMetadata = Bool
False
data ReplaceMetadataV1
= RMWithSources Metadata
| RMWithoutSources MetadataNoSources
deriving (ReplaceMetadataV1 -> ReplaceMetadataV1 -> Bool
(ReplaceMetadataV1 -> ReplaceMetadataV1 -> Bool)
-> (ReplaceMetadataV1 -> ReplaceMetadataV1 -> Bool)
-> Eq ReplaceMetadataV1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReplaceMetadataV1 -> ReplaceMetadataV1 -> Bool
== :: ReplaceMetadataV1 -> ReplaceMetadataV1 -> Bool
$c/= :: ReplaceMetadataV1 -> ReplaceMetadataV1 -> Bool
/= :: ReplaceMetadataV1 -> ReplaceMetadataV1 -> Bool
Eq)
instance FromJSON ReplaceMetadataV1 where
parseJSON :: Value -> Parser ReplaceMetadataV1
parseJSON = String
-> (Object -> Parser ReplaceMetadataV1)
-> Value
-> Parser ReplaceMetadataV1
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"ReplaceMetadataV1" ((Object -> Parser ReplaceMetadataV1)
-> Value -> Parser ReplaceMetadataV1)
-> (Object -> Parser ReplaceMetadataV1)
-> Value
-> Parser ReplaceMetadataV1
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
MetadataVersion
version <- Object
o Object -> Key -> Parser (Maybe MetadataVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"version" Parser (Maybe MetadataVersion)
-> MetadataVersion -> Parser MetadataVersion
forall a. Parser (Maybe a) -> a -> Parser a
.!= MetadataVersion
Metadata.MVVersion1
case MetadataVersion
version of
MetadataVersion
Metadata.MVVersion3 -> Metadata -> ReplaceMetadataV1
RMWithSources (Metadata -> ReplaceMetadataV1)
-> Parser Metadata -> Parser ReplaceMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Metadata
forall a. FromJSON a => Value -> Parser a
J.parseJSON (Object -> Value
J.Object Object
o)
MetadataVersion
_ -> MetadataNoSources -> ReplaceMetadataV1
RMWithoutSources (MetadataNoSources -> ReplaceMetadataV1)
-> Parser MetadataNoSources -> Parser ReplaceMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser MetadataNoSources
forall a. FromJSON a => Value -> Parser a
J.parseJSON (Object -> Value
J.Object Object
o)
instance ToJSON ReplaceMetadataV1 where
toJSON :: ReplaceMetadataV1 -> Value
toJSON = \case
RMWithSources Metadata
v -> Metadata -> Value
forall a. ToJSON a => a -> Value
J.toJSON Metadata
v
RMWithoutSources MetadataNoSources
v -> MetadataNoSources -> Value
forall a. ToJSON a => a -> Value
J.toJSON MetadataNoSources
v
data ReplaceMetadataV2 = ReplaceMetadataV2
{ ReplaceMetadataV2 -> AllowInconsistentMetadata
_rmv2AllowInconsistentMetadata :: AllowInconsistentMetadata,
ReplaceMetadataV2 -> AllowWarnings
_rmv2AllowWarningss :: AllowWarnings,
ReplaceMetadataV2 -> ReplaceMetadataV1
_rmv2Metadata :: ReplaceMetadataV1
}
deriving (ReplaceMetadataV2 -> ReplaceMetadataV2 -> Bool
(ReplaceMetadataV2 -> ReplaceMetadataV2 -> Bool)
-> (ReplaceMetadataV2 -> ReplaceMetadataV2 -> Bool)
-> Eq ReplaceMetadataV2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReplaceMetadataV2 -> ReplaceMetadataV2 -> Bool
== :: ReplaceMetadataV2 -> ReplaceMetadataV2 -> Bool
$c/= :: ReplaceMetadataV2 -> ReplaceMetadataV2 -> Bool
/= :: ReplaceMetadataV2 -> ReplaceMetadataV2 -> Bool
Eq)
instance FromJSON ReplaceMetadataV2 where
parseJSON :: Value -> Parser ReplaceMetadataV2
parseJSON = String
-> (Object -> Parser ReplaceMetadataV2)
-> Value
-> Parser ReplaceMetadataV2
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"ReplaceMetadataV2" ((Object -> Parser ReplaceMetadataV2)
-> Value -> Parser ReplaceMetadataV2)
-> (Object -> Parser ReplaceMetadataV2)
-> Value
-> Parser ReplaceMetadataV2
forall a b. (a -> b) -> a -> b
$ \Object
o ->
AllowInconsistentMetadata
-> AllowWarnings -> ReplaceMetadataV1 -> ReplaceMetadataV2
ReplaceMetadataV2
(AllowInconsistentMetadata
-> AllowWarnings -> ReplaceMetadataV1 -> ReplaceMetadataV2)
-> Parser AllowInconsistentMetadata
-> Parser (AllowWarnings -> ReplaceMetadataV1 -> ReplaceMetadataV2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser (Maybe AllowInconsistentMetadata)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"allow_inconsistent_metadata"
Parser (Maybe AllowInconsistentMetadata)
-> AllowInconsistentMetadata -> Parser AllowInconsistentMetadata
forall a. Parser (Maybe a) -> a -> Parser a
.!= AllowInconsistentMetadata
NoAllowInconsistentMetadata
Parser (AllowWarnings -> ReplaceMetadataV1 -> ReplaceMetadataV2)
-> Parser AllowWarnings
-> Parser (ReplaceMetadataV1 -> ReplaceMetadataV2)
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 AllowWarnings)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"allow_warnings"
Parser (Maybe AllowWarnings)
-> AllowWarnings -> Parser AllowWarnings
forall a. Parser (Maybe a) -> a -> Parser a
.!= AllowWarnings
AllowWarnings
Parser (ReplaceMetadataV1 -> ReplaceMetadataV2)
-> Parser ReplaceMetadataV1 -> Parser ReplaceMetadataV2
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 ReplaceMetadataV1
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"metadata"
instance ToJSON ReplaceMetadataV2 where
toJSON :: ReplaceMetadataV2 -> Value
toJSON ReplaceMetadataV2 {AllowWarnings
ReplaceMetadataV1
AllowInconsistentMetadata
_rmv2AllowInconsistentMetadata :: ReplaceMetadataV2 -> AllowInconsistentMetadata
_rmv2AllowWarningss :: ReplaceMetadataV2 -> AllowWarnings
_rmv2Metadata :: ReplaceMetadataV2 -> ReplaceMetadataV1
_rmv2AllowInconsistentMetadata :: AllowInconsistentMetadata
_rmv2AllowWarningss :: AllowWarnings
_rmv2Metadata :: ReplaceMetadataV1
..} =
[Pair] -> Value
J.object
[ Key
"allow_inconsistent_metadata" Key -> AllowInconsistentMetadata -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= AllowInconsistentMetadata
_rmv2AllowInconsistentMetadata,
Key
"allow_warnings" Key -> AllowWarnings -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= AllowWarnings
_rmv2AllowWarningss,
Key
"metadata" Key -> ReplaceMetadataV1 -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ReplaceMetadataV1
_rmv2Metadata
]
data ReplaceMetadata
= RMReplaceMetadataV1 ReplaceMetadataV1
| RMReplaceMetadataV2 ReplaceMetadataV2
deriving (ReplaceMetadata -> ReplaceMetadata -> Bool
(ReplaceMetadata -> ReplaceMetadata -> Bool)
-> (ReplaceMetadata -> ReplaceMetadata -> Bool)
-> Eq ReplaceMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReplaceMetadata -> ReplaceMetadata -> Bool
== :: ReplaceMetadata -> ReplaceMetadata -> Bool
$c/= :: ReplaceMetadata -> ReplaceMetadata -> Bool
/= :: ReplaceMetadata -> ReplaceMetadata -> Bool
Eq)
instance FromJSON ReplaceMetadata where
parseJSON :: Value -> Parser ReplaceMetadata
parseJSON = String
-> (Object -> Parser ReplaceMetadata)
-> Value
-> Parser ReplaceMetadata
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"ReplaceMetadata" ((Object -> Parser ReplaceMetadata)
-> Value -> Parser ReplaceMetadata)
-> (Object -> Parser ReplaceMetadata)
-> Value
-> Parser ReplaceMetadata
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
if Key -> Object -> Bool
forall a. Key -> KeyMap a -> Bool
KeyMap.member Key
"metadata" Object
o
then ReplaceMetadataV2 -> ReplaceMetadata
RMReplaceMetadataV2 (ReplaceMetadataV2 -> ReplaceMetadata)
-> Parser ReplaceMetadataV2 -> Parser ReplaceMetadata
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser ReplaceMetadataV2
forall a. FromJSON a => Value -> Parser a
J.parseJSON (Object -> Value
J.Object Object
o)
else ReplaceMetadataV1 -> ReplaceMetadata
RMReplaceMetadataV1 (ReplaceMetadataV1 -> ReplaceMetadata)
-> Parser ReplaceMetadataV1 -> Parser ReplaceMetadata
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser ReplaceMetadataV1
forall a. FromJSON a => Value -> Parser a
J.parseJSON (Object -> Value
J.Object Object
o)
instance ToJSON ReplaceMetadata where
toJSON :: ReplaceMetadata -> Value
toJSON = \case
RMReplaceMetadataV1 ReplaceMetadataV1
v1 -> ReplaceMetadataV1 -> Value
forall a. ToJSON a => a -> Value
J.toJSON ReplaceMetadataV1
v1
RMReplaceMetadataV2 ReplaceMetadataV2
v2 -> ReplaceMetadataV2 -> Value
forall a. ToJSON a => a -> Value
J.toJSON ReplaceMetadataV2
v2
data WebHookUrl = EnvVar String | URL Text
deriving (WebHookUrl -> WebHookUrl -> Bool
(WebHookUrl -> WebHookUrl -> Bool)
-> (WebHookUrl -> WebHookUrl -> Bool) -> Eq WebHookUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebHookUrl -> WebHookUrl -> Bool
== :: WebHookUrl -> WebHookUrl -> Bool
$c/= :: WebHookUrl -> WebHookUrl -> Bool
/= :: WebHookUrl -> WebHookUrl -> Bool
Eq)
instance FromJSON WebHookUrl where
parseJSON :: Value -> Parser WebHookUrl
parseJSON (J.Object Object
o) = do
String
var <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"from_env"
WebHookUrl -> Parser WebHookUrl
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WebHookUrl -> Parser WebHookUrl)
-> WebHookUrl -> Parser WebHookUrl
forall a b. (a -> b) -> a -> b
$ String -> WebHookUrl
EnvVar String
var
parseJSON (J.String Text
str) = WebHookUrl -> Parser WebHookUrl
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WebHookUrl -> Parser WebHookUrl)
-> WebHookUrl -> Parser WebHookUrl
forall a b. (a -> b) -> a -> b
$ Text -> WebHookUrl
URL Text
str
parseJSON Value
_ = Parser WebHookUrl
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
instance ToJSON WebHookUrl where
toJSON :: WebHookUrl -> Value
toJSON (EnvVar String
var) = [Pair] -> Value
J.object [Key
"from_env" Key -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= String
var]
toJSON (URL Text
url) = Text -> Value
forall a. ToJSON a => a -> Value
J.toJSON Text
url
data TestWebhookTransform = TestWebhookTransform
{ TestWebhookTransform -> Environment
_twtEnv :: Env.Environment,
:: [HTTP.Header],
TestWebhookTransform -> WebHookUrl
_twtWebhookUrl :: WebHookUrl,
TestWebhookTransform -> Value
_twtPayload :: J.Value,
TestWebhookTransform -> RequestTransform
_twtTransformer :: RequestTransform,
TestWebhookTransform -> Maybe MetadataResponseTransform
_twtResponseTransformer :: Maybe MetadataResponseTransform,
TestWebhookTransform -> Maybe SessionVariables
_twtSessionVariables :: Maybe SessionVariables
}
deriving (TestWebhookTransform -> TestWebhookTransform -> Bool
(TestWebhookTransform -> TestWebhookTransform -> Bool)
-> (TestWebhookTransform -> TestWebhookTransform -> Bool)
-> Eq TestWebhookTransform
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TestWebhookTransform -> TestWebhookTransform -> Bool
== :: TestWebhookTransform -> TestWebhookTransform -> Bool
$c/= :: TestWebhookTransform -> TestWebhookTransform -> Bool
/= :: TestWebhookTransform -> TestWebhookTransform -> Bool
Eq)
twtRequestTransformer :: Lens' TestWebhookTransform RequestTransform
twtRequestTransformer :: Lens' TestWebhookTransform RequestTransform
twtRequestTransformer = (TestWebhookTransform -> RequestTransform)
-> (TestWebhookTransform
-> RequestTransform -> TestWebhookTransform)
-> Lens' TestWebhookTransform RequestTransform
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens TestWebhookTransform -> RequestTransform
_twtTransformer \TestWebhookTransform
twt RequestTransform
a -> TestWebhookTransform
twt {_twtTransformer :: RequestTransform
_twtTransformer = RequestTransform
a}
twtResponseTransformer :: Lens' TestWebhookTransform (Maybe MetadataResponseTransform)
twtResponseTransformer :: Lens' TestWebhookTransform (Maybe MetadataResponseTransform)
twtResponseTransformer = (TestWebhookTransform -> Maybe MetadataResponseTransform)
-> (TestWebhookTransform
-> Maybe MetadataResponseTransform -> TestWebhookTransform)
-> Lens' TestWebhookTransform (Maybe MetadataResponseTransform)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens TestWebhookTransform -> Maybe MetadataResponseTransform
_twtResponseTransformer \TestWebhookTransform
twt Maybe MetadataResponseTransform
a -> TestWebhookTransform
twt {_twtResponseTransformer :: Maybe MetadataResponseTransform
_twtResponseTransformer = Maybe MetadataResponseTransform
a}
instance FromJSON TestWebhookTransform where
parseJSON :: Value -> Parser TestWebhookTransform
parseJSON = String
-> (Object -> Parser TestWebhookTransform)
-> Value
-> Parser TestWebhookTransform
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"TestWebhookTransform" ((Object -> Parser TestWebhookTransform)
-> Value -> Parser TestWebhookTransform)
-> (Object -> Parser TestWebhookTransform)
-> Value
-> Parser TestWebhookTransform
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Environment
env <- (Maybe Environment -> Environment)
-> Parser (Maybe Environment) -> Parser Environment
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Environment -> Maybe Environment -> Environment
forall a. a -> Maybe a -> a
fromMaybe Environment
forall a. Monoid a => a
mempty) (Parser (Maybe Environment) -> Parser Environment)
-> Parser (Maybe Environment) -> Parser Environment
forall a b. (a -> b) -> a -> b
$ Object
o Object -> Key -> Parser (Maybe Environment)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"env"
[Header]
headers <- ([(ByteString, ByteString)] -> [Header])
-> Parser [(ByteString, ByteString)] -> Parser [Header]
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((ByteString, ByteString) -> Header)
-> [(ByteString, ByteString)] -> [Header]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ByteString -> CI ByteString) -> (ByteString, ByteString) -> Header
forall b c d. (b -> c) -> (b, d) -> (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (ByteString -> CI ByteString
forall s. FoldCase s => s -> CI s
CI.mk))) (Parser [(ByteString, ByteString)] -> Parser [Header])
-> Parser [(ByteString, ByteString)] -> Parser [Header]
forall a b. (a -> b) -> a -> b
$ Object
o Object -> Key -> Parser (Maybe [(ByteString, ByteString)])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"request_headers" Parser (Maybe [(ByteString, ByteString)])
-> [(ByteString, ByteString)] -> Parser [(ByteString, ByteString)]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
WebHookUrl
url <- Object
o Object -> Key -> Parser WebHookUrl
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"webhook_url"
Value
payload <- Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"body"
RequestTransform
reqTransform <- Object
o Object -> Key -> Parser RequestTransform
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"request_transform"
Maybe MetadataResponseTransform
respTransform <- Object
o Object -> Key -> Parser (Maybe MetadataResponseTransform)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"response_transform"
Maybe SessionVariables
sessionVars <- Object
o Object -> Key -> Parser (Maybe SessionVariables)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"session_variables"
TestWebhookTransform -> Parser TestWebhookTransform
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TestWebhookTransform -> Parser TestWebhookTransform)
-> TestWebhookTransform -> Parser TestWebhookTransform
forall a b. (a -> b) -> a -> b
$ Environment
-> [Header]
-> WebHookUrl
-> Value
-> RequestTransform
-> Maybe MetadataResponseTransform
-> Maybe SessionVariables
-> TestWebhookTransform
TestWebhookTransform Environment
env [Header]
headers WebHookUrl
url Value
payload RequestTransform
reqTransform Maybe MetadataResponseTransform
respTransform Maybe SessionVariables
sessionVars
instance ToJSON TestWebhookTransform where
toJSON :: TestWebhookTransform -> Value
toJSON (TestWebhookTransform Environment
env [Header]
headers WebHookUrl
url Value
payload RequestTransform
mt Maybe MetadataResponseTransform
mrt Maybe SessionVariables
sv) =
[Pair] -> Value
J.object
[ Key
"env" Key -> Environment -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Environment
env,
Key
"request_headers" Key -> [(ByteString, ByteString)] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= (Header -> (ByteString, ByteString))
-> [Header] -> [(ByteString, ByteString)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CI ByteString -> ByteString) -> Header -> (ByteString, ByteString)
forall b c d. (b -> c) -> (b, d) -> (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first CI ByteString -> ByteString
forall s. CI s -> s
CI.original) [Header]
headers,
Key
"webhook_url" Key -> WebHookUrl -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= WebHookUrl
url,
Key
"body" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Value
payload,
Key
"request_transform" Key -> RequestTransform -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= RequestTransform
mt,
Key
"response_transform" Key -> Maybe MetadataResponseTransform -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe MetadataResponseTransform
mrt,
Key
"session_variables" Key -> Maybe SessionVariables -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe SessionVariables
sv
]