{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE StrictData #-} module GitHub.Types.Events.CheckSuiteEvent 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 import GitHub.Types.Event data CheckSuiteEvent = CheckSuiteEvent { CheckSuiteEvent -> Maybe Installation checkSuiteEventInstallation :: Maybe Installation , CheckSuiteEvent -> Organization checkSuiteEventOrganization :: Organization , CheckSuiteEvent -> Repository checkSuiteEventRepository :: Repository , CheckSuiteEvent -> User checkSuiteEventSender :: User , CheckSuiteEvent -> Text checkSuiteEventAction :: Text , CheckSuiteEvent -> CheckSuite checkSuiteEventCheckSuite :: CheckSuite } deriving (CheckSuiteEvent -> CheckSuiteEvent -> Bool (CheckSuiteEvent -> CheckSuiteEvent -> Bool) -> (CheckSuiteEvent -> CheckSuiteEvent -> Bool) -> Eq CheckSuiteEvent forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: CheckSuiteEvent -> CheckSuiteEvent -> Bool $c/= :: CheckSuiteEvent -> CheckSuiteEvent -> Bool == :: CheckSuiteEvent -> CheckSuiteEvent -> Bool $c== :: CheckSuiteEvent -> CheckSuiteEvent -> Bool Eq, Int -> CheckSuiteEvent -> ShowS [CheckSuiteEvent] -> ShowS CheckSuiteEvent -> String (Int -> CheckSuiteEvent -> ShowS) -> (CheckSuiteEvent -> String) -> ([CheckSuiteEvent] -> ShowS) -> Show CheckSuiteEvent forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [CheckSuiteEvent] -> ShowS $cshowList :: [CheckSuiteEvent] -> ShowS show :: CheckSuiteEvent -> String $cshow :: CheckSuiteEvent -> String showsPrec :: Int -> CheckSuiteEvent -> ShowS $cshowsPrec :: Int -> CheckSuiteEvent -> ShowS Show, ReadPrec [CheckSuiteEvent] ReadPrec CheckSuiteEvent Int -> ReadS CheckSuiteEvent ReadS [CheckSuiteEvent] (Int -> ReadS CheckSuiteEvent) -> ReadS [CheckSuiteEvent] -> ReadPrec CheckSuiteEvent -> ReadPrec [CheckSuiteEvent] -> Read CheckSuiteEvent forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [CheckSuiteEvent] $creadListPrec :: ReadPrec [CheckSuiteEvent] readPrec :: ReadPrec CheckSuiteEvent $creadPrec :: ReadPrec CheckSuiteEvent readList :: ReadS [CheckSuiteEvent] $creadList :: ReadS [CheckSuiteEvent] readsPrec :: Int -> ReadS CheckSuiteEvent $creadsPrec :: Int -> ReadS CheckSuiteEvent Read) instance Event CheckSuiteEvent where typeName :: TypeName CheckSuiteEvent typeName = Text -> TypeName CheckSuiteEvent forall a. Text -> TypeName a TypeName Text "CheckSuiteEvent" eventName :: EventName CheckSuiteEvent eventName = Text -> EventName CheckSuiteEvent forall a. Text -> EventName a EventName Text "check_suite" instance FromJSON CheckSuiteEvent where parseJSON :: Value -> Parser CheckSuiteEvent parseJSON (Object Object x) = Maybe Installation -> Organization -> Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent CheckSuiteEvent (Maybe Installation -> Organization -> Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) -> Parser (Maybe Installation) -> Parser (Organization -> Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Object x Object -> Key -> Parser (Maybe Installation) forall a. FromJSON a => Object -> Key -> Parser (Maybe a) .:? Key "installation" Parser (Organization -> Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) -> Parser Organization -> Parser (Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object x Object -> Key -> Parser Organization forall a. FromJSON a => Object -> Key -> Parser a .: Key "organization" Parser (Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) -> Parser Repository -> Parser (User -> Text -> CheckSuite -> CheckSuiteEvent) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object x Object -> Key -> Parser Repository forall a. FromJSON a => Object -> Key -> Parser a .: Key "repository" Parser (User -> Text -> CheckSuite -> CheckSuiteEvent) -> Parser User -> Parser (Text -> CheckSuite -> CheckSuiteEvent) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object x Object -> Key -> Parser User forall a. FromJSON a => Object -> Key -> Parser a .: Key "sender" Parser (Text -> CheckSuite -> CheckSuiteEvent) -> Parser Text -> Parser (CheckSuite -> CheckSuiteEvent) 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 "action" Parser (CheckSuite -> CheckSuiteEvent) -> Parser CheckSuite -> Parser CheckSuiteEvent forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Object x Object -> Key -> Parser CheckSuite forall a. FromJSON a => Object -> Key -> Parser a .: Key "check_suite" parseJSON Value _ = String -> Parser CheckSuiteEvent forall (m :: * -> *) a. MonadFail m => String -> m a fail String "CheckSuiteEvent" instance ToJSON CheckSuiteEvent where toJSON :: CheckSuiteEvent -> Value toJSON CheckSuiteEvent{Maybe Installation Text Organization User CheckSuite Repository checkSuiteEventCheckSuite :: CheckSuite checkSuiteEventAction :: Text checkSuiteEventSender :: User checkSuiteEventRepository :: Repository checkSuiteEventOrganization :: Organization checkSuiteEventInstallation :: Maybe Installation checkSuiteEventCheckSuite :: CheckSuiteEvent -> CheckSuite checkSuiteEventAction :: CheckSuiteEvent -> Text checkSuiteEventSender :: CheckSuiteEvent -> User checkSuiteEventRepository :: CheckSuiteEvent -> Repository checkSuiteEventOrganization :: CheckSuiteEvent -> Organization checkSuiteEventInstallation :: CheckSuiteEvent -> Maybe Installation ..} = [Pair] -> Value object [ Key "installation" Key -> Maybe Installation -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Maybe Installation checkSuiteEventInstallation , Key "organization" Key -> Organization -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Organization checkSuiteEventOrganization , Key "repository" Key -> Repository -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Repository checkSuiteEventRepository , Key "sender" Key -> User -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= User checkSuiteEventSender , Key "action" Key -> Text -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= Text checkSuiteEventAction , Key "check_suite" Key -> CheckSuite -> Pair forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv .= CheckSuite checkSuiteEventCheckSuite ] instance Arbitrary CheckSuiteEvent where arbitrary :: Gen CheckSuiteEvent arbitrary = Maybe Installation -> Organization -> Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent CheckSuiteEvent (Maybe Installation -> Organization -> Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) -> Gen (Maybe Installation) -> Gen (Organization -> Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Gen (Maybe Installation) forall a. Arbitrary a => Gen a arbitrary Gen (Organization -> Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) -> Gen Organization -> Gen (Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen Organization forall a. Arbitrary a => Gen a arbitrary Gen (Repository -> User -> Text -> CheckSuite -> CheckSuiteEvent) -> Gen Repository -> Gen (User -> Text -> CheckSuite -> CheckSuiteEvent) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen Repository forall a. Arbitrary a => Gen a arbitrary Gen (User -> Text -> CheckSuite -> CheckSuiteEvent) -> Gen User -> Gen (Text -> CheckSuite -> CheckSuiteEvent) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen User forall a. Arbitrary a => Gen a arbitrary Gen (Text -> CheckSuite -> CheckSuiteEvent) -> Gen Text -> Gen (CheckSuite -> CheckSuiteEvent) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen Text forall a. Arbitrary a => Gen a arbitrary Gen (CheckSuite -> CheckSuiteEvent) -> Gen CheckSuite -> Gen CheckSuiteEvent forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Gen CheckSuite forall a. Arbitrary a => Gen a arbitrary