{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.CommitDetails 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.CommitRef
import GitHub.Types.Base.UserStamp
import GitHub.Types.Base.Verification
data CommitDetails = CommitDetails
{ CommitDetails -> UserStamp
commitDetailsAuthor :: UserStamp
, :: Int
, CommitDetails -> UserStamp
commitDetailsCommitter :: UserStamp
, CommitDetails -> Text
commitDetailsMessage :: Text
, CommitDetails -> CommitRef
commitDetailsTree :: CommitRef
, CommitDetails -> Text
commitDetailsUrl :: Text
, CommitDetails -> Verification
commitDetailsVerification :: Verification
} deriving (CommitDetails -> CommitDetails -> Bool
(CommitDetails -> CommitDetails -> Bool)
-> (CommitDetails -> CommitDetails -> Bool) -> Eq CommitDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommitDetails -> CommitDetails -> Bool
$c/= :: CommitDetails -> CommitDetails -> Bool
== :: CommitDetails -> CommitDetails -> Bool
$c== :: CommitDetails -> CommitDetails -> Bool
Eq, Int -> CommitDetails -> ShowS
[CommitDetails] -> ShowS
CommitDetails -> String
(Int -> CommitDetails -> ShowS)
-> (CommitDetails -> String)
-> ([CommitDetails] -> ShowS)
-> Show CommitDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommitDetails] -> ShowS
$cshowList :: [CommitDetails] -> ShowS
show :: CommitDetails -> String
$cshow :: CommitDetails -> String
showsPrec :: Int -> CommitDetails -> ShowS
$cshowsPrec :: Int -> CommitDetails -> ShowS
Show, ReadPrec [CommitDetails]
ReadPrec CommitDetails
Int -> ReadS CommitDetails
ReadS [CommitDetails]
(Int -> ReadS CommitDetails)
-> ReadS [CommitDetails]
-> ReadPrec CommitDetails
-> ReadPrec [CommitDetails]
-> Read CommitDetails
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CommitDetails]
$creadListPrec :: ReadPrec [CommitDetails]
readPrec :: ReadPrec CommitDetails
$creadPrec :: ReadPrec CommitDetails
readList :: ReadS [CommitDetails]
$creadList :: ReadS [CommitDetails]
readsPrec :: Int -> ReadS CommitDetails
$creadsPrec :: Int -> ReadS CommitDetails
Read)
instance FromJSON CommitDetails where
parseJSON :: Value -> Parser CommitDetails
parseJSON (Object Object
x) = UserStamp
-> Int
-> UserStamp
-> Text
-> CommitRef
-> Text
-> Verification
-> CommitDetails
CommitDetails
(UserStamp
-> Int
-> UserStamp
-> Text
-> CommitRef
-> Text
-> Verification
-> CommitDetails)
-> Parser UserStamp
-> Parser
(Int
-> UserStamp
-> Text
-> CommitRef
-> Text
-> Verification
-> CommitDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser UserStamp
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"author"
Parser
(Int
-> UserStamp
-> Text
-> CommitRef
-> Text
-> Verification
-> CommitDetails)
-> Parser Int
-> Parser
(UserStamp
-> Text -> CommitRef -> Text -> Verification -> CommitDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"comment_count"
Parser
(UserStamp
-> Text -> CommitRef -> Text -> Verification -> CommitDetails)
-> Parser UserStamp
-> Parser
(Text -> CommitRef -> Text -> Verification -> CommitDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser UserStamp
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"committer"
Parser (Text -> CommitRef -> Text -> Verification -> CommitDetails)
-> Parser Text
-> Parser (CommitRef -> Text -> Verification -> CommitDetails)
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
"message"
Parser (CommitRef -> Text -> Verification -> CommitDetails)
-> Parser CommitRef
-> Parser (Text -> Verification -> CommitDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser CommitRef
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tree"
Parser (Text -> Verification -> CommitDetails)
-> Parser Text -> Parser (Verification -> CommitDetails)
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
"url"
Parser (Verification -> CommitDetails)
-> Parser Verification -> Parser CommitDetails
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Verification
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"verification"
parseJSON Value
_ = String -> Parser CommitDetails
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"CommitDetails"
instance ToJSON CommitDetails where
toJSON :: CommitDetails -> Value
toJSON CommitDetails{Int
Text
CommitRef
UserStamp
Verification
commitDetailsVerification :: Verification
commitDetailsUrl :: Text
commitDetailsTree :: CommitRef
commitDetailsMessage :: Text
commitDetailsCommitter :: UserStamp
commitDetailsCommentCount :: Int
commitDetailsAuthor :: UserStamp
commitDetailsVerification :: CommitDetails -> Verification
commitDetailsUrl :: CommitDetails -> Text
commitDetailsTree :: CommitDetails -> CommitRef
commitDetailsMessage :: CommitDetails -> Text
commitDetailsCommitter :: CommitDetails -> UserStamp
commitDetailsCommentCount :: CommitDetails -> Int
commitDetailsAuthor :: CommitDetails -> UserStamp
..} = [Pair] -> Value
object
[ Key
"author" Key -> UserStamp -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UserStamp
commitDetailsAuthor
, Key
"comment_count" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
commitDetailsCommentCount
, Key
"committer" Key -> UserStamp -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UserStamp
commitDetailsCommitter
, Key
"message" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
commitDetailsMessage
, Key
"tree" Key -> CommitRef -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CommitRef
commitDetailsTree
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
commitDetailsUrl
, Key
"verification" Key -> Verification -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Verification
commitDetailsVerification
]
instance Arbitrary CommitDetails where
arbitrary :: Gen CommitDetails
arbitrary = UserStamp
-> Int
-> UserStamp
-> Text
-> CommitRef
-> Text
-> Verification
-> CommitDetails
CommitDetails
(UserStamp
-> Int
-> UserStamp
-> Text
-> CommitRef
-> Text
-> Verification
-> CommitDetails)
-> Gen UserStamp
-> Gen
(Int
-> UserStamp
-> Text
-> CommitRef
-> Text
-> Verification
-> CommitDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen UserStamp
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Int
-> UserStamp
-> Text
-> CommitRef
-> Text
-> Verification
-> CommitDetails)
-> Gen Int
-> Gen
(UserStamp
-> Text -> CommitRef -> Text -> Verification -> CommitDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
Gen
(UserStamp
-> Text -> CommitRef -> Text -> Verification -> CommitDetails)
-> Gen UserStamp
-> Gen (Text -> CommitRef -> Text -> Verification -> CommitDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen UserStamp
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> CommitRef -> Text -> Verification -> CommitDetails)
-> Gen Text
-> Gen (CommitRef -> Text -> Verification -> CommitDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (CommitRef -> Text -> Verification -> CommitDetails)
-> Gen CommitRef -> Gen (Text -> Verification -> CommitDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen CommitRef
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Verification -> CommitDetails)
-> Gen Text -> Gen (Verification -> CommitDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Verification -> CommitDetails)
-> Gen Verification -> Gen CommitDetails
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Verification
forall a. Arbitrary a => Gen a
arbitrary