{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.PullRequestLinks where
import Data.Aeson (FromJSON (..), ToJSON (..), object)
import Data.Aeson.Types (Value (..), (.:), (.=))
import Test.QuickCheck.Arbitrary (Arbitrary (..))
import GitHub.Types.Base.Link
data PullRequestLinks = PullRequestLinks
{ PullRequestLinks -> Link
pullRequestLinksSelf :: Link
, PullRequestLinks -> Link
pullRequestLinksCommits :: Link
, PullRequestLinks -> Link
pullRequestLinksStatuses :: Link
, :: Link
, PullRequestLinks -> Link
pullRequestLinksHtml :: Link
, :: Link
, :: Link
, PullRequestLinks -> Link
pullRequestLinksIssue :: Link
} deriving (PullRequestLinks -> PullRequestLinks -> Bool
(PullRequestLinks -> PullRequestLinks -> Bool)
-> (PullRequestLinks -> PullRequestLinks -> Bool)
-> Eq PullRequestLinks
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PullRequestLinks -> PullRequestLinks -> Bool
$c/= :: PullRequestLinks -> PullRequestLinks -> Bool
== :: PullRequestLinks -> PullRequestLinks -> Bool
$c== :: PullRequestLinks -> PullRequestLinks -> Bool
Eq, Int -> PullRequestLinks -> ShowS
[PullRequestLinks] -> ShowS
PullRequestLinks -> String
(Int -> PullRequestLinks -> ShowS)
-> (PullRequestLinks -> String)
-> ([PullRequestLinks] -> ShowS)
-> Show PullRequestLinks
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PullRequestLinks] -> ShowS
$cshowList :: [PullRequestLinks] -> ShowS
show :: PullRequestLinks -> String
$cshow :: PullRequestLinks -> String
showsPrec :: Int -> PullRequestLinks -> ShowS
$cshowsPrec :: Int -> PullRequestLinks -> ShowS
Show, ReadPrec [PullRequestLinks]
ReadPrec PullRequestLinks
Int -> ReadS PullRequestLinks
ReadS [PullRequestLinks]
(Int -> ReadS PullRequestLinks)
-> ReadS [PullRequestLinks]
-> ReadPrec PullRequestLinks
-> ReadPrec [PullRequestLinks]
-> Read PullRequestLinks
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PullRequestLinks]
$creadListPrec :: ReadPrec [PullRequestLinks]
readPrec :: ReadPrec PullRequestLinks
$creadPrec :: ReadPrec PullRequestLinks
readList :: ReadS [PullRequestLinks]
$creadList :: ReadS [PullRequestLinks]
readsPrec :: Int -> ReadS PullRequestLinks
$creadsPrec :: Int -> ReadS PullRequestLinks
Read)
instance FromJSON PullRequestLinks where
parseJSON :: Value -> Parser PullRequestLinks
parseJSON (Object Object
x) = Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> PullRequestLinks
PullRequestLinks
(Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> PullRequestLinks)
-> Parser Link
-> Parser
(Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> PullRequestLinks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser Link
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"self"
Parser
(Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> PullRequestLinks)
-> Parser Link
-> Parser
(Link -> Link -> Link -> Link -> Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Link
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"commits"
Parser
(Link -> Link -> Link -> Link -> Link -> Link -> PullRequestLinks)
-> Parser Link
-> Parser
(Link -> Link -> Link -> Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Link
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"statuses"
Parser (Link -> Link -> Link -> Link -> Link -> PullRequestLinks)
-> Parser Link
-> Parser (Link -> Link -> Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Link
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"review_comments"
Parser (Link -> Link -> Link -> Link -> PullRequestLinks)
-> Parser Link -> Parser (Link -> Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Link
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"html"
Parser (Link -> Link -> Link -> PullRequestLinks)
-> Parser Link -> Parser (Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Link
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"comments"
Parser (Link -> Link -> PullRequestLinks)
-> Parser Link -> Parser (Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Link
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"review_comment"
Parser (Link -> PullRequestLinks)
-> Parser Link -> Parser PullRequestLinks
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Link
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"issue"
parseJSON Value
_ = String -> Parser PullRequestLinks
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"PullRequestLinks"
instance ToJSON PullRequestLinks where
toJSON :: PullRequestLinks -> Value
toJSON PullRequestLinks{Link
pullRequestLinksIssue :: Link
pullRequestLinksReviewComment :: Link
pullRequestLinksComments :: Link
pullRequestLinksHtml :: Link
pullRequestLinksReviewComments :: Link
pullRequestLinksStatuses :: Link
pullRequestLinksCommits :: Link
pullRequestLinksSelf :: Link
pullRequestLinksIssue :: PullRequestLinks -> Link
pullRequestLinksReviewComment :: PullRequestLinks -> Link
pullRequestLinksComments :: PullRequestLinks -> Link
pullRequestLinksHtml :: PullRequestLinks -> Link
pullRequestLinksReviewComments :: PullRequestLinks -> Link
pullRequestLinksStatuses :: PullRequestLinks -> Link
pullRequestLinksCommits :: PullRequestLinks -> Link
pullRequestLinksSelf :: PullRequestLinks -> Link
..} = [Pair] -> Value
object
[ Key
"self" Key -> Link -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Link
pullRequestLinksSelf
, Key
"commits" Key -> Link -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Link
pullRequestLinksCommits
, Key
"statuses" Key -> Link -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Link
pullRequestLinksStatuses
, Key
"review_comments" Key -> Link -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Link
pullRequestLinksReviewComments
, Key
"html" Key -> Link -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Link
pullRequestLinksHtml
, Key
"comments" Key -> Link -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Link
pullRequestLinksComments
, Key
"review_comment" Key -> Link -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Link
pullRequestLinksReviewComment
, Key
"issue" Key -> Link -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Link
pullRequestLinksIssue
]
instance Arbitrary PullRequestLinks where
arbitrary :: Gen PullRequestLinks
arbitrary = Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> PullRequestLinks
PullRequestLinks
(Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> PullRequestLinks)
-> Gen Link
-> Gen
(Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> PullRequestLinks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Link
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> Link
-> PullRequestLinks)
-> Gen Link
-> Gen
(Link -> Link -> Link -> Link -> Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Link
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Link -> Link -> Link -> Link -> Link -> Link -> PullRequestLinks)
-> Gen Link
-> Gen (Link -> Link -> Link -> Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Link
forall a. Arbitrary a => Gen a
arbitrary
Gen (Link -> Link -> Link -> Link -> Link -> PullRequestLinks)
-> Gen Link
-> Gen (Link -> Link -> Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Link
forall a. Arbitrary a => Gen a
arbitrary
Gen (Link -> Link -> Link -> Link -> PullRequestLinks)
-> Gen Link -> Gen (Link -> Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Link
forall a. Arbitrary a => Gen a
arbitrary
Gen (Link -> Link -> Link -> PullRequestLinks)
-> Gen Link -> Gen (Link -> Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Link
forall a. Arbitrary a => Gen a
arbitrary
Gen (Link -> Link -> PullRequestLinks)
-> Gen Link -> Gen (Link -> PullRequestLinks)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Link
forall a. Arbitrary a => Gen a
arbitrary
Gen (Link -> PullRequestLinks) -> Gen Link -> Gen PullRequestLinks
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Link
forall a. Arbitrary a => Gen a
arbitrary