{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.WorkflowJob 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.WorkflowStep
data WorkflowJob = WorkflowJob
{ WorkflowJob -> Maybe Text
workflowJobConclusion :: Maybe Text
, WorkflowJob -> Text
workflowJobHeadSha :: Text
, WorkflowJob -> Int
workflowJobRunAttempt :: Int
, WorkflowJob -> Int
workflowJobRunId :: Int
, WorkflowJob -> Text
workflowJobRunUrl :: Text
, WorkflowJob -> Text
workflowJobCheckRunUrl :: Text
, WorkflowJob -> Text
workflowJobHtmlUrl :: Text
, WorkflowJob -> Int
workflowJobId :: Int
, WorkflowJob -> Text
workflowJobNodeId :: Text
, WorkflowJob -> Text
workflowJobName :: Text
, WorkflowJob -> [Text]
workflowJobLabels :: [Text]
, WorkflowJob -> [WorkflowStep]
workflowJobSteps :: [WorkflowStep]
, WorkflowJob -> Text
workflowJobStatus :: Text
, WorkflowJob -> Text
workflowJobUrl :: Text
, WorkflowJob -> Text
workflowJobStartedAt :: Text
, WorkflowJob -> Maybe Text
workflowJobCompletedAt :: Maybe Text
, WorkflowJob -> Maybe Int
workflowJobRunnerId :: Maybe Int
, WorkflowJob -> Maybe Text
workflowJobRunnerName :: Maybe Text
, WorkflowJob -> Maybe Int
workflowJobRunnerGroupId :: Maybe Int
, WorkflowJob -> Maybe Text
workflowJobRunnerGroupName :: Maybe Text
} deriving (WorkflowJob -> WorkflowJob -> Bool
(WorkflowJob -> WorkflowJob -> Bool)
-> (WorkflowJob -> WorkflowJob -> Bool) -> Eq WorkflowJob
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WorkflowJob -> WorkflowJob -> Bool
$c/= :: WorkflowJob -> WorkflowJob -> Bool
== :: WorkflowJob -> WorkflowJob -> Bool
$c== :: WorkflowJob -> WorkflowJob -> Bool
Eq, Int -> WorkflowJob -> ShowS
[WorkflowJob] -> ShowS
WorkflowJob -> String
(Int -> WorkflowJob -> ShowS)
-> (WorkflowJob -> String)
-> ([WorkflowJob] -> ShowS)
-> Show WorkflowJob
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WorkflowJob] -> ShowS
$cshowList :: [WorkflowJob] -> ShowS
show :: WorkflowJob -> String
$cshow :: WorkflowJob -> String
showsPrec :: Int -> WorkflowJob -> ShowS
$cshowsPrec :: Int -> WorkflowJob -> ShowS
Show, ReadPrec [WorkflowJob]
ReadPrec WorkflowJob
Int -> ReadS WorkflowJob
ReadS [WorkflowJob]
(Int -> ReadS WorkflowJob)
-> ReadS [WorkflowJob]
-> ReadPrec WorkflowJob
-> ReadPrec [WorkflowJob]
-> Read WorkflowJob
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WorkflowJob]
$creadListPrec :: ReadPrec [WorkflowJob]
readPrec :: ReadPrec WorkflowJob
$creadPrec :: ReadPrec WorkflowJob
readList :: ReadS [WorkflowJob]
$creadList :: ReadS [WorkflowJob]
readsPrec :: Int -> ReadS WorkflowJob
$creadsPrec :: Int -> ReadS WorkflowJob
Read)
instance FromJSON WorkflowJob where
parseJSON :: Value -> Parser WorkflowJob
parseJSON (Object Object
x) = Maybe Text
-> Text
-> Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob
WorkflowJob
(Maybe Text
-> Text
-> Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser (Maybe Text)
-> Parser
(Text
-> Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Functor 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
-> Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Text
-> Parser
(Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
(Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Int
-> Parser
(Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
"run_attempt"
Parser
(Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Int
-> Parser
(Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
"run_id"
Parser
(Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Text
-> Parser
(Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
"run_url"
Parser
(Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Text
-> Parser
(Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
"check_run_url"
Parser
(Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Text
-> Parser
(Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Int
-> Parser
(Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Text
-> Parser
(Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
(Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Text
-> Parser
([Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser [Text]
-> Parser
([WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
"labels"
Parser
([WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser [WorkflowStep]
-> Parser
(Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser [WorkflowStep]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"steps"
Parser
(Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Text
-> Parser
(Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Text
-> Parser
(Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
(Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser Text
-> Parser
(Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
(Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Parser (Maybe Text)
-> Parser
(Maybe Int -> Maybe Text -> Maybe Int -> Maybe Text -> WorkflowJob)
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 Int -> Maybe Text -> Maybe Int -> Maybe Text -> WorkflowJob)
-> Parser (Maybe Int)
-> Parser (Maybe Text -> Maybe Int -> Maybe Text -> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"runner_id"
Parser (Maybe Text -> Maybe Int -> Maybe Text -> WorkflowJob)
-> Parser (Maybe Text)
-> Parser (Maybe Int -> Maybe Text -> WorkflowJob)
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
"runner_name"
Parser (Maybe Int -> Maybe Text -> WorkflowJob)
-> Parser (Maybe Int) -> Parser (Maybe Text -> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"runner_group_id"
Parser (Maybe Text -> WorkflowJob)
-> Parser (Maybe Text) -> Parser WorkflowJob
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
"runner_group_name"
parseJSON Value
_ = String -> Parser WorkflowJob
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"WorkflowJob"
instance ToJSON WorkflowJob where
toJSON :: WorkflowJob -> Value
toJSON WorkflowJob{Int
[Text]
[WorkflowStep]
Maybe Int
Maybe Text
Text
workflowJobRunnerGroupName :: Maybe Text
workflowJobRunnerGroupId :: Maybe Int
workflowJobRunnerName :: Maybe Text
workflowJobRunnerId :: Maybe Int
workflowJobCompletedAt :: Maybe Text
workflowJobStartedAt :: Text
workflowJobUrl :: Text
workflowJobStatus :: Text
workflowJobSteps :: [WorkflowStep]
workflowJobLabels :: [Text]
workflowJobName :: Text
workflowJobNodeId :: Text
workflowJobId :: Int
workflowJobHtmlUrl :: Text
workflowJobCheckRunUrl :: Text
workflowJobRunUrl :: Text
workflowJobRunId :: Int
workflowJobRunAttempt :: Int
workflowJobHeadSha :: Text
workflowJobConclusion :: Maybe Text
workflowJobRunnerGroupName :: WorkflowJob -> Maybe Text
workflowJobRunnerGroupId :: WorkflowJob -> Maybe Int
workflowJobRunnerName :: WorkflowJob -> Maybe Text
workflowJobRunnerId :: WorkflowJob -> Maybe Int
workflowJobCompletedAt :: WorkflowJob -> Maybe Text
workflowJobStartedAt :: WorkflowJob -> Text
workflowJobUrl :: WorkflowJob -> Text
workflowJobStatus :: WorkflowJob -> Text
workflowJobSteps :: WorkflowJob -> [WorkflowStep]
workflowJobLabels :: WorkflowJob -> [Text]
workflowJobName :: WorkflowJob -> Text
workflowJobNodeId :: WorkflowJob -> Text
workflowJobId :: WorkflowJob -> Int
workflowJobHtmlUrl :: WorkflowJob -> Text
workflowJobCheckRunUrl :: WorkflowJob -> Text
workflowJobRunUrl :: WorkflowJob -> Text
workflowJobRunId :: WorkflowJob -> Int
workflowJobRunAttempt :: WorkflowJob -> Int
workflowJobHeadSha :: WorkflowJob -> Text
workflowJobConclusion :: WorkflowJob -> Maybe Text
..} = [Pair] -> Value
object
[ Key
"conclusion" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
workflowJobConclusion
, Key
"head_sha" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowJobHeadSha
, Key
"run_attempt" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
workflowJobRunAttempt
, Key
"run_id" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
workflowJobRunId
, Key
"run_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowJobRunUrl
, Key
"check_run_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowJobCheckRunUrl
, Key
"html_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowJobHtmlUrl
, Key
"id" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
workflowJobId
, Key
"node_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowJobNodeId
, Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowJobName
, Key
"labels" Key -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
workflowJobLabels
, Key
"steps" Key -> [WorkflowStep] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [WorkflowStep]
workflowJobSteps
, Key
"status" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowJobStatus
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowJobUrl
, Key
"started_at" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowJobStartedAt
, Key
"completed_at" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
workflowJobCompletedAt
, Key
"runner_id" Key -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
workflowJobRunnerId
, Key
"runner_name" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
workflowJobRunnerName
, Key
"runner_group_id" Key -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
workflowJobRunnerGroupId
, Key
"runner_group_name" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
workflowJobRunnerGroupName
]
instance Arbitrary WorkflowJob where
arbitrary :: Gen WorkflowJob
arbitrary = Maybe Text
-> Text
-> Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob
WorkflowJob
(Maybe Text
-> Text
-> Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen (Maybe Text)
-> Gen
(Text
-> Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Text
-> Gen
(Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Int
-> Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Int
-> Gen
(Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Int
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Int
-> Gen
(Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Text
-> Gen
(Text
-> Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Text
-> Gen
(Text
-> Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Text
-> Gen
(Int
-> Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Int
-> Gen
(Text
-> Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Text
-> Gen
(Text
-> [Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Text
-> Gen
([Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
([Text]
-> [WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen [Text]
-> Gen
([WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen [Text]
forall a. Arbitrary a => Gen a
arbitrary
Gen
([WorkflowStep]
-> Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen [WorkflowStep]
-> Gen
(Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen [WorkflowStep]
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Text
-> Gen
(Text
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
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
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Text
-> Gen
(Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen Text
-> Gen
(Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> WorkflowJob)
-> Gen (Maybe Text)
-> Gen
(Maybe Int -> Maybe Text -> Maybe Int -> Maybe Text -> WorkflowJob)
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 Int -> Maybe Text -> Maybe Int -> Maybe Text -> WorkflowJob)
-> Gen (Maybe Int)
-> Gen (Maybe Text -> Maybe Int -> Maybe Text -> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Int)
forall a. Arbitrary a => Gen a
arbitrary
Gen (Maybe Text -> Maybe Int -> Maybe Text -> WorkflowJob)
-> Gen (Maybe Text) -> Gen (Maybe Int -> Maybe Text -> WorkflowJob)
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 Int -> Maybe Text -> WorkflowJob)
-> Gen (Maybe Int) -> Gen (Maybe Text -> WorkflowJob)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Int)
forall a. Arbitrary a => Gen a
arbitrary
Gen (Maybe Text -> WorkflowJob)
-> Gen (Maybe Text) -> Gen WorkflowJob
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary