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