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