{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.CheckCommitRepo where
import Data.Aeson (FromJSON (..), ToJSON (..), object)
import Data.Aeson.Types (Value (..), (.:), (.=))
import Data.Text (Text)
import Data.Text.Arbitrary ()
import Test.QuickCheck.Arbitrary (Arbitrary (..))
data CheckCommitRepo = CheckCommitRepo
{ CheckCommitRepo -> Int
checkCommitRepoId :: Int
, CheckCommitRepo -> Text
checkCommitRepoName :: Text
, CheckCommitRepo -> Text
checkCommitRepoUrl :: Text
} deriving (CheckCommitRepo -> CheckCommitRepo -> Bool
(CheckCommitRepo -> CheckCommitRepo -> Bool)
-> (CheckCommitRepo -> CheckCommitRepo -> Bool)
-> Eq CheckCommitRepo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckCommitRepo -> CheckCommitRepo -> Bool
$c/= :: CheckCommitRepo -> CheckCommitRepo -> Bool
== :: CheckCommitRepo -> CheckCommitRepo -> Bool
$c== :: CheckCommitRepo -> CheckCommitRepo -> Bool
Eq, Int -> CheckCommitRepo -> ShowS
[CheckCommitRepo] -> ShowS
CheckCommitRepo -> String
(Int -> CheckCommitRepo -> ShowS)
-> (CheckCommitRepo -> String)
-> ([CheckCommitRepo] -> ShowS)
-> Show CheckCommitRepo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckCommitRepo] -> ShowS
$cshowList :: [CheckCommitRepo] -> ShowS
show :: CheckCommitRepo -> String
$cshow :: CheckCommitRepo -> String
showsPrec :: Int -> CheckCommitRepo -> ShowS
$cshowsPrec :: Int -> CheckCommitRepo -> ShowS
Show, ReadPrec [CheckCommitRepo]
ReadPrec CheckCommitRepo
Int -> ReadS CheckCommitRepo
ReadS [CheckCommitRepo]
(Int -> ReadS CheckCommitRepo)
-> ReadS [CheckCommitRepo]
-> ReadPrec CheckCommitRepo
-> ReadPrec [CheckCommitRepo]
-> Read CheckCommitRepo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CheckCommitRepo]
$creadListPrec :: ReadPrec [CheckCommitRepo]
readPrec :: ReadPrec CheckCommitRepo
$creadPrec :: ReadPrec CheckCommitRepo
readList :: ReadS [CheckCommitRepo]
$creadList :: ReadS [CheckCommitRepo]
readsPrec :: Int -> ReadS CheckCommitRepo
$creadsPrec :: Int -> ReadS CheckCommitRepo
Read)
instance FromJSON CheckCommitRepo where
parseJSON :: Value -> Parser CheckCommitRepo
parseJSON (Object Object
x) = Int -> Text -> Text -> CheckCommitRepo
CheckCommitRepo
(Int -> Text -> Text -> CheckCommitRepo)
-> Parser Int -> Parser (Text -> Text -> CheckCommitRepo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser (Text -> Text -> CheckCommitRepo)
-> Parser Text -> Parser (Text -> CheckCommitRepo)
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
"name"
Parser (Text -> CheckCommitRepo)
-> Parser Text -> Parser CheckCommitRepo
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"
parseJSON Value
_ = String -> Parser CheckCommitRepo
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"CheckCommitRepo"
instance ToJSON CheckCommitRepo where
toJSON :: CheckCommitRepo -> Value
toJSON CheckCommitRepo{Int
Text
checkCommitRepoUrl :: Text
checkCommitRepoName :: Text
checkCommitRepoId :: Int
checkCommitRepoUrl :: CheckCommitRepo -> Text
checkCommitRepoName :: CheckCommitRepo -> Text
checkCommitRepoId :: CheckCommitRepo -> Int
..} = [Pair] -> Value
object
[ Key
"id" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
checkCommitRepoId
, Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkCommitRepoName
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkCommitRepoUrl
]
instance Arbitrary CheckCommitRepo where
arbitrary :: Gen CheckCommitRepo
arbitrary = Int -> Text -> Text -> CheckCommitRepo
CheckCommitRepo
(Int -> Text -> Text -> CheckCommitRepo)
-> Gen Int -> Gen (Text -> Text -> CheckCommitRepo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> CheckCommitRepo)
-> Gen Text -> Gen (Text -> CheckCommitRepo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> CheckCommitRepo) -> Gen Text -> Gen CheckCommitRepo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary