{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.Hook where
import Data.Aeson (FromJSON (..), ToJSON (..),
object)
import Data.Aeson.Types (Value (..), (.:), (.=))
import Data.Text (Text)
import Test.QuickCheck.Arbitrary (Arbitrary (..))
import GitHub.Types.Base.DateTime
import GitHub.Types.Base.HookConfig
data Hook = Hook
{ Hook -> Bool
hookActive :: Bool
, Hook -> HookConfig
hookConfig :: HookConfig
, Hook -> DateTime
hookCreatedAt :: DateTime
, Hook -> [Text]
hookEvents :: [Text]
, Hook -> Int
hookId :: Int
, Hook -> Text
hookName :: Text
, Hook -> Text
hookPingUrl :: Text
, Hook -> Text
hookType :: Text
, Hook -> DateTime
hookUpdatedAt :: DateTime
, Hook -> Text
hookUrl :: Text
} deriving (Hook -> Hook -> Bool
(Hook -> Hook -> Bool) -> (Hook -> Hook -> Bool) -> Eq Hook
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hook -> Hook -> Bool
$c/= :: Hook -> Hook -> Bool
== :: Hook -> Hook -> Bool
$c== :: Hook -> Hook -> Bool
Eq, Int -> Hook -> ShowS
[Hook] -> ShowS
Hook -> String
(Int -> Hook -> ShowS)
-> (Hook -> String) -> ([Hook] -> ShowS) -> Show Hook
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hook] -> ShowS
$cshowList :: [Hook] -> ShowS
show :: Hook -> String
$cshow :: Hook -> String
showsPrec :: Int -> Hook -> ShowS
$cshowsPrec :: Int -> Hook -> ShowS
Show, ReadPrec [Hook]
ReadPrec Hook
Int -> ReadS Hook
ReadS [Hook]
(Int -> ReadS Hook)
-> ReadS [Hook] -> ReadPrec Hook -> ReadPrec [Hook] -> Read Hook
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Hook]
$creadListPrec :: ReadPrec [Hook]
readPrec :: ReadPrec Hook
$creadPrec :: ReadPrec Hook
readList :: ReadS [Hook]
$creadList :: ReadS [Hook]
readsPrec :: Int -> ReadS Hook
$creadsPrec :: Int -> ReadS Hook
Read)
instance FromJSON Hook where
parseJSON :: Value -> Parser Hook
parseJSON (Object Object
x) = Bool
-> HookConfig
-> DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook
Hook
(Bool
-> HookConfig
-> DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
-> Parser Bool
-> Parser
(HookConfig
-> DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"active"
Parser
(HookConfig
-> DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
-> Parser HookConfig
-> Parser
(DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser HookConfig
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"config"
Parser
(DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
-> Parser DateTime
-> Parser
([Text] -> Int -> Text -> Text -> Text -> DateTime -> Text -> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser DateTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created_at"
Parser
([Text] -> Int -> Text -> Text -> Text -> DateTime -> Text -> Hook)
-> Parser [Text]
-> Parser (Int -> Text -> Text -> Text -> DateTime -> Text -> Hook)
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
"events"
Parser (Int -> Text -> Text -> Text -> DateTime -> Text -> Hook)
-> Parser Int
-> Parser (Text -> Text -> Text -> DateTime -> Text -> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser (Text -> Text -> Text -> DateTime -> Text -> Hook)
-> Parser Text -> Parser (Text -> Text -> DateTime -> Text -> Hook)
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
"name"
Parser (Text -> Text -> DateTime -> Text -> Hook)
-> Parser Text -> Parser (Text -> DateTime -> Text -> Hook)
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
"ping_url"
Parser (Text -> DateTime -> Text -> Hook)
-> Parser Text -> Parser (DateTime -> Text -> Hook)
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
"type"
Parser (DateTime -> Text -> Hook)
-> Parser DateTime -> Parser (Text -> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser DateTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"updated_at"
Parser (Text -> Hook) -> Parser Text -> Parser Hook
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 Hook
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Hook"
instance ToJSON Hook where
toJSON :: Hook -> Value
toJSON Hook{Bool
Int
[Text]
Text
DateTime
HookConfig
hookUrl :: Text
hookUpdatedAt :: DateTime
hookType :: Text
hookPingUrl :: Text
hookName :: Text
hookId :: Int
hookEvents :: [Text]
hookCreatedAt :: DateTime
hookConfig :: HookConfig
hookActive :: Bool
hookUrl :: Hook -> Text
hookUpdatedAt :: Hook -> DateTime
hookType :: Hook -> Text
hookPingUrl :: Hook -> Text
hookName :: Hook -> Text
hookId :: Hook -> Int
hookEvents :: Hook -> [Text]
hookCreatedAt :: Hook -> DateTime
hookConfig :: Hook -> HookConfig
hookActive :: Hook -> Bool
..} = [Pair] -> Value
object
[ Key
"active" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
hookActive
, Key
"config" Key -> HookConfig -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= HookConfig
hookConfig
, Key
"created_at" Key -> DateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DateTime
hookCreatedAt
, Key
"events" Key -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
hookEvents
, Key
"id" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
hookId
, Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
hookName
, Key
"ping_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
hookPingUrl
, Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
hookType
, Key
"updated_at" Key -> DateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DateTime
hookUpdatedAt
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
hookUrl
]
instance Arbitrary Hook where
arbitrary :: Gen Hook
arbitrary = Bool
-> HookConfig
-> DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook
Hook
(Bool
-> HookConfig
-> DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
-> Gen Bool
-> Gen
(HookConfig
-> DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
Gen
(HookConfig
-> DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
-> Gen HookConfig
-> Gen
(DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen HookConfig
forall a. Arbitrary a => Gen a
arbitrary
Gen
(DateTime
-> [Text]
-> Int
-> Text
-> Text
-> Text
-> DateTime
-> Text
-> Hook)
-> Gen DateTime
-> Gen
([Text] -> Int -> Text -> Text -> Text -> DateTime -> Text -> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen DateTime
forall a. Arbitrary a => Gen a
arbitrary
Gen
([Text] -> Int -> Text -> Text -> Text -> DateTime -> Text -> Hook)
-> Gen [Text]
-> Gen (Int -> Text -> Text -> Text -> DateTime -> Text -> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen [Text]
forall a. Arbitrary a => Gen a
arbitrary
Gen (Int -> Text -> Text -> Text -> DateTime -> Text -> Hook)
-> Gen Int
-> Gen (Text -> Text -> Text -> DateTime -> Text -> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Text -> DateTime -> Text -> Hook)
-> Gen Text -> Gen (Text -> Text -> DateTime -> Text -> Hook)
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 -> DateTime -> Text -> Hook)
-> Gen Text -> Gen (Text -> DateTime -> Text -> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> DateTime -> Text -> Hook)
-> Gen Text -> Gen (DateTime -> Text -> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (DateTime -> Text -> Hook)
-> Gen DateTime -> Gen (Text -> Hook)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen DateTime
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Hook) -> Gen Text -> Gen Hook
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary