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