{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.CheckRun 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.CheckApp
import GitHub.Types.Base.CheckOutput
import GitHub.Types.Base.CheckPullRequest
import GitHub.Types.Base.CheckSuite
data CheckRun = CheckRun
{ CheckRun -> CheckApp
checkRunApp :: CheckApp
, CheckRun -> CheckSuite
checkRunCheckSuite :: CheckSuite
, CheckRun -> Maybe Text
checkRunCompletedAt :: Maybe Text
, CheckRun -> Maybe Text
checkRunConclusion :: Maybe Text
, CheckRun -> Text
checkRunDetailsUrl :: Text
, CheckRun -> Text
checkRunExternalId :: Text
, CheckRun -> Text
checkRunHeadSha :: Text
, CheckRun -> Text
checkRunHtmlUrl :: Text
, CheckRun -> Int
checkRunId :: Int
, CheckRun -> Text
checkRunName :: Text
, CheckRun -> Text
checkRunNodeId :: Text
, CheckRun -> CheckOutput
checkRunOutput :: CheckOutput
, CheckRun -> [CheckPullRequest]
checkRunPullRequests :: [CheckPullRequest]
, CheckRun -> Text
checkRunStartedAt :: Text
, CheckRun -> Text
checkRunStatus :: Text
, CheckRun -> Text
checkRunUrl :: Text
} deriving (CheckRun -> CheckRun -> Bool
(CheckRun -> CheckRun -> Bool)
-> (CheckRun -> CheckRun -> Bool) -> Eq CheckRun
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckRun -> CheckRun -> Bool
$c/= :: CheckRun -> CheckRun -> Bool
== :: CheckRun -> CheckRun -> Bool
$c== :: CheckRun -> CheckRun -> Bool
Eq, Int -> CheckRun -> ShowS
[CheckRun] -> ShowS
CheckRun -> String
(Int -> CheckRun -> ShowS)
-> (CheckRun -> String) -> ([CheckRun] -> ShowS) -> Show CheckRun
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckRun] -> ShowS
$cshowList :: [CheckRun] -> ShowS
show :: CheckRun -> String
$cshow :: CheckRun -> String
showsPrec :: Int -> CheckRun -> ShowS
$cshowsPrec :: Int -> CheckRun -> ShowS
Show, ReadPrec [CheckRun]
ReadPrec CheckRun
Int -> ReadS CheckRun
ReadS [CheckRun]
(Int -> ReadS CheckRun)
-> ReadS [CheckRun]
-> ReadPrec CheckRun
-> ReadPrec [CheckRun]
-> Read CheckRun
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CheckRun]
$creadListPrec :: ReadPrec [CheckRun]
readPrec :: ReadPrec CheckRun
$creadPrec :: ReadPrec CheckRun
readList :: ReadS [CheckRun]
$creadList :: ReadS [CheckRun]
readsPrec :: Int -> ReadS CheckRun
$creadsPrec :: Int -> ReadS CheckRun
Read)
instance FromJSON CheckRun where
parseJSON :: Value -> Parser CheckRun
parseJSON (Object Object
x) = CheckApp
-> CheckSuite
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun
CheckRun
(CheckApp
-> CheckSuite
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser CheckApp
-> Parser
(CheckSuite
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser CheckApp
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"app"
Parser
(CheckSuite
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser CheckSuite
-> Parser
(Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser CheckSuite
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"check_suite"
Parser
(Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"completed_at"
Parser
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser (Maybe Text)
-> Parser
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"conclusion"
Parser
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
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
"details_url"
Parser
(Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser Text
-> Parser
(Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
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
"external_id"
Parser
(Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser Text
-> Parser
(Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
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
"head_sha"
Parser
(Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser Text
-> Parser
(Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
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
"html_url"
Parser
(Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser Int
-> Parser
(Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
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
"id"
Parser
(Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser Text
-> Parser
(Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
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
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Parser Text
-> Parser
(CheckOutput
-> [CheckPullRequest] -> Text -> Text -> Text -> CheckRun)
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
"node_id"
Parser
(CheckOutput
-> [CheckPullRequest] -> Text -> Text -> Text -> CheckRun)
-> Parser CheckOutput
-> Parser ([CheckPullRequest] -> Text -> Text -> Text -> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser CheckOutput
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"output"
Parser ([CheckPullRequest] -> Text -> Text -> Text -> CheckRun)
-> Parser [CheckPullRequest]
-> Parser (Text -> Text -> Text -> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser [CheckPullRequest]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"pull_requests"
Parser (Text -> Text -> Text -> CheckRun)
-> Parser Text -> Parser (Text -> Text -> CheckRun)
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
"started_at"
Parser (Text -> Text -> CheckRun)
-> Parser Text -> Parser (Text -> CheckRun)
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
"status"
Parser (Text -> CheckRun) -> Parser Text -> Parser CheckRun
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 CheckRun
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"CheckRun"
instance ToJSON CheckRun where
toJSON :: CheckRun -> Value
toJSON CheckRun{Int
[CheckPullRequest]
Maybe Text
Text
CheckOutput
CheckApp
CheckSuite
checkRunUrl :: Text
checkRunStatus :: Text
checkRunStartedAt :: Text
checkRunPullRequests :: [CheckPullRequest]
checkRunOutput :: CheckOutput
checkRunNodeId :: Text
checkRunName :: Text
checkRunId :: Int
checkRunHtmlUrl :: Text
checkRunHeadSha :: Text
checkRunExternalId :: Text
checkRunDetailsUrl :: Text
checkRunConclusion :: Maybe Text
checkRunCompletedAt :: Maybe Text
checkRunCheckSuite :: CheckSuite
checkRunApp :: CheckApp
checkRunUrl :: CheckRun -> Text
checkRunStatus :: CheckRun -> Text
checkRunStartedAt :: CheckRun -> Text
checkRunPullRequests :: CheckRun -> [CheckPullRequest]
checkRunOutput :: CheckRun -> CheckOutput
checkRunNodeId :: CheckRun -> Text
checkRunName :: CheckRun -> Text
checkRunId :: CheckRun -> Int
checkRunHtmlUrl :: CheckRun -> Text
checkRunHeadSha :: CheckRun -> Text
checkRunExternalId :: CheckRun -> Text
checkRunDetailsUrl :: CheckRun -> Text
checkRunConclusion :: CheckRun -> Maybe Text
checkRunCompletedAt :: CheckRun -> Maybe Text
checkRunCheckSuite :: CheckRun -> CheckSuite
checkRunApp :: CheckRun -> CheckApp
..} = [Pair] -> Value
object
[ Key
"app" Key -> CheckApp -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CheckApp
checkRunApp
, Key
"check_suite" Key -> CheckSuite -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CheckSuite
checkRunCheckSuite
, Key
"completed_at" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
checkRunCompletedAt
, Key
"conclusion" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
checkRunConclusion
, Key
"details_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkRunDetailsUrl
, Key
"external_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkRunExternalId
, Key
"head_sha" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkRunHeadSha
, Key
"html_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkRunHtmlUrl
, Key
"id" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
checkRunId
, Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkRunName
, Key
"node_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkRunNodeId
, Key
"output" Key -> CheckOutput -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CheckOutput
checkRunOutput
, Key
"pull_requests" Key -> [CheckPullRequest] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [CheckPullRequest]
checkRunPullRequests
, Key
"started_at" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkRunStartedAt
, Key
"status" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkRunStatus
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
checkRunUrl
]
instance Arbitrary CheckRun where
arbitrary :: Gen CheckRun
arbitrary = CheckApp
-> CheckSuite
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun
CheckRun
(CheckApp
-> CheckSuite
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen CheckApp
-> Gen
(CheckSuite
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen CheckApp
forall a. Arbitrary a => Gen a
arbitrary
Gen
(CheckSuite
-> Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen CheckSuite
-> Gen
(Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen CheckSuite
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Maybe Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen (Maybe Text)
-> Gen
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Maybe Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen (Maybe Text)
-> Gen
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen Text
-> Gen
(Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen Text
-> Gen
(Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen Text
-> Gen
(Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Int
-> Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen Int
-> Gen
(Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen Text
-> Gen
(Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> CheckOutput
-> [CheckPullRequest]
-> Text
-> Text
-> Text
-> CheckRun)
-> Gen Text
-> Gen
(CheckOutput
-> [CheckPullRequest] -> Text -> Text -> Text -> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(CheckOutput
-> [CheckPullRequest] -> Text -> Text -> Text -> CheckRun)
-> Gen CheckOutput
-> Gen ([CheckPullRequest] -> Text -> Text -> Text -> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen CheckOutput
forall a. Arbitrary a => Gen a
arbitrary
Gen ([CheckPullRequest] -> Text -> Text -> Text -> CheckRun)
-> Gen [CheckPullRequest] -> Gen (Text -> Text -> Text -> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen [CheckPullRequest]
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Text -> CheckRun)
-> Gen Text -> Gen (Text -> Text -> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> CheckRun)
-> Gen Text -> Gen (Text -> CheckRun)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> CheckRun) -> Gen Text -> Gen CheckRun
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary