{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.HookConfig where
import Data.Aeson (FromJSON (..), ToJSON (..), object)
import Data.Aeson.Types (Value (..), (.:), (.=))
import Data.Text (Text)
import Data.Text.Arbitrary ()
import Test.QuickCheck.Arbitrary (Arbitrary (..))
data HookConfig = HookConfig
{ HookConfig -> Text
hookConfigContentType :: Text
, HookConfig -> Text
hookConfigInsecureSsl :: Text
, HookConfig -> Text
hookConfigSecret :: Text
, HookConfig -> Text
hookConfigUrl :: Text
} deriving (HookConfig -> HookConfig -> Bool
(HookConfig -> HookConfig -> Bool)
-> (HookConfig -> HookConfig -> Bool) -> Eq HookConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HookConfig -> HookConfig -> Bool
$c/= :: HookConfig -> HookConfig -> Bool
== :: HookConfig -> HookConfig -> Bool
$c== :: HookConfig -> HookConfig -> Bool
Eq, Int -> HookConfig -> ShowS
[HookConfig] -> ShowS
HookConfig -> String
(Int -> HookConfig -> ShowS)
-> (HookConfig -> String)
-> ([HookConfig] -> ShowS)
-> Show HookConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HookConfig] -> ShowS
$cshowList :: [HookConfig] -> ShowS
show :: HookConfig -> String
$cshow :: HookConfig -> String
showsPrec :: Int -> HookConfig -> ShowS
$cshowsPrec :: Int -> HookConfig -> ShowS
Show, ReadPrec [HookConfig]
ReadPrec HookConfig
Int -> ReadS HookConfig
ReadS [HookConfig]
(Int -> ReadS HookConfig)
-> ReadS [HookConfig]
-> ReadPrec HookConfig
-> ReadPrec [HookConfig]
-> Read HookConfig
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HookConfig]
$creadListPrec :: ReadPrec [HookConfig]
readPrec :: ReadPrec HookConfig
$creadPrec :: ReadPrec HookConfig
readList :: ReadS [HookConfig]
$creadList :: ReadS [HookConfig]
readsPrec :: Int -> ReadS HookConfig
$creadsPrec :: Int -> ReadS HookConfig
Read)
instance FromJSON HookConfig where
parseJSON :: Value -> Parser HookConfig
parseJSON (Object Object
x) = Text -> Text -> Text -> Text -> HookConfig
HookConfig
(Text -> Text -> Text -> Text -> HookConfig)
-> Parser Text -> Parser (Text -> Text -> Text -> HookConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"content_type"
Parser (Text -> Text -> Text -> HookConfig)
-> Parser Text -> Parser (Text -> Text -> HookConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"insecure_ssl"
Parser (Text -> Text -> HookConfig)
-> Parser Text -> Parser (Text -> HookConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"secret"
Parser (Text -> HookConfig) -> Parser Text -> Parser HookConfig
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
parseJSON Value
_ = String -> Parser HookConfig
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"HookConfig"
instance ToJSON HookConfig where
toJSON :: HookConfig -> Value
toJSON HookConfig{Text
hookConfigUrl :: Text
hookConfigSecret :: Text
hookConfigInsecureSsl :: Text
hookConfigContentType :: Text
hookConfigUrl :: HookConfig -> Text
hookConfigSecret :: HookConfig -> Text
hookConfigInsecureSsl :: HookConfig -> Text
hookConfigContentType :: HookConfig -> Text
..} = [Pair] -> Value
object
[ Key
"content_type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
hookConfigContentType
, Key
"insecure_ssl" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
hookConfigInsecureSsl
, Key
"secret" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
hookConfigSecret
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
hookConfigUrl
]
instance Arbitrary HookConfig where
arbitrary :: Gen HookConfig
arbitrary = Text -> Text -> Text -> Text -> HookConfig
HookConfig
(Text -> Text -> Text -> Text -> HookConfig)
-> Gen Text -> Gen (Text -> Text -> Text -> HookConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Text -> HookConfig)
-> Gen Text -> Gen (Text -> Text -> HookConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> HookConfig)
-> Gen Text -> Gen (Text -> HookConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> HookConfig) -> Gen Text -> Gen HookConfig
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary