{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.WorkflowStep 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 WorkflowStep = WorkflowStep
{ WorkflowStep -> Text
workflowStepName :: Text
, WorkflowStep -> Text
workflowStepStatus :: Text
, WorkflowStep -> Maybe Text
workflowStepConclusion :: Maybe Text
, WorkflowStep -> Int
workflowStepNumber :: Int
, WorkflowStep -> Maybe Text
workflowStepStartedAt :: Maybe Text
, WorkflowStep -> Maybe Text
workflowStepCompletedAt :: Maybe Text
} deriving (WorkflowStep -> WorkflowStep -> Bool
(WorkflowStep -> WorkflowStep -> Bool)
-> (WorkflowStep -> WorkflowStep -> Bool) -> Eq WorkflowStep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WorkflowStep -> WorkflowStep -> Bool
$c/= :: WorkflowStep -> WorkflowStep -> Bool
== :: WorkflowStep -> WorkflowStep -> Bool
$c== :: WorkflowStep -> WorkflowStep -> Bool
Eq, Int -> WorkflowStep -> ShowS
[WorkflowStep] -> ShowS
WorkflowStep -> String
(Int -> WorkflowStep -> ShowS)
-> (WorkflowStep -> String)
-> ([WorkflowStep] -> ShowS)
-> Show WorkflowStep
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WorkflowStep] -> ShowS
$cshowList :: [WorkflowStep] -> ShowS
show :: WorkflowStep -> String
$cshow :: WorkflowStep -> String
showsPrec :: Int -> WorkflowStep -> ShowS
$cshowsPrec :: Int -> WorkflowStep -> ShowS
Show, ReadPrec [WorkflowStep]
ReadPrec WorkflowStep
Int -> ReadS WorkflowStep
ReadS [WorkflowStep]
(Int -> ReadS WorkflowStep)
-> ReadS [WorkflowStep]
-> ReadPrec WorkflowStep
-> ReadPrec [WorkflowStep]
-> Read WorkflowStep
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WorkflowStep]
$creadListPrec :: ReadPrec [WorkflowStep]
readPrec :: ReadPrec WorkflowStep
$creadPrec :: ReadPrec WorkflowStep
readList :: ReadS [WorkflowStep]
$creadList :: ReadS [WorkflowStep]
readsPrec :: Int -> ReadS WorkflowStep
$creadsPrec :: Int -> ReadS WorkflowStep
Read)
instance FromJSON WorkflowStep where
parseJSON :: Value -> Parser WorkflowStep
parseJSON (Object Object
x) = Text
-> Text
-> Maybe Text
-> Int
-> Maybe Text
-> Maybe Text
-> WorkflowStep
WorkflowStep
(Text
-> Text
-> Maybe Text
-> Int
-> Maybe Text
-> Maybe Text
-> WorkflowStep)
-> Parser Text
-> Parser
(Text
-> Maybe Text -> Int -> Maybe Text -> Maybe Text -> WorkflowStep)
forall (f :: * -> *) a b. Functor 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
-> Maybe Text -> Int -> Maybe Text -> Maybe Text -> WorkflowStep)
-> Parser Text
-> Parser
(Maybe Text -> Int -> Maybe Text -> Maybe Text -> WorkflowStep)
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
(Maybe Text -> Int -> Maybe Text -> Maybe Text -> WorkflowStep)
-> Parser (Maybe Text)
-> Parser (Int -> Maybe Text -> Maybe Text -> WorkflowStep)
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 (Int -> Maybe Text -> Maybe Text -> WorkflowStep)
-> Parser Int -> Parser (Maybe Text -> Maybe Text -> WorkflowStep)
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
"number"
Parser (Maybe Text -> Maybe Text -> WorkflowStep)
-> Parser (Maybe Text) -> Parser (Maybe Text -> WorkflowStep)
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
"started_at"
Parser (Maybe Text -> WorkflowStep)
-> Parser (Maybe Text) -> Parser WorkflowStep
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"
parseJSON Value
_ = String -> Parser WorkflowStep
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"WorkflowStep"
instance ToJSON WorkflowStep where
toJSON :: WorkflowStep -> Value
toJSON WorkflowStep{Int
Maybe Text
Text
workflowStepCompletedAt :: Maybe Text
workflowStepStartedAt :: Maybe Text
workflowStepNumber :: Int
workflowStepConclusion :: Maybe Text
workflowStepStatus :: Text
workflowStepName :: Text
workflowStepCompletedAt :: WorkflowStep -> Maybe Text
workflowStepStartedAt :: WorkflowStep -> Maybe Text
workflowStepNumber :: WorkflowStep -> Int
workflowStepConclusion :: WorkflowStep -> Maybe Text
workflowStepStatus :: WorkflowStep -> Text
workflowStepName :: WorkflowStep -> Text
..} = [Pair] -> Value
object
[ Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowStepName
, Key
"status" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
workflowStepStatus
, Key
"conclusion" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
workflowStepConclusion
, Key
"number" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
workflowStepNumber
, Key
"started_at" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
workflowStepStartedAt
, Key
"completed_at" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
workflowStepCompletedAt
]
instance Arbitrary WorkflowStep where
arbitrary :: Gen WorkflowStep
arbitrary = Text
-> Text
-> Maybe Text
-> Int
-> Maybe Text
-> Maybe Text
-> WorkflowStep
WorkflowStep
(Text
-> Text
-> Maybe Text
-> Int
-> Maybe Text
-> Maybe Text
-> WorkflowStep)
-> Gen Text
-> Gen
(Text
-> Maybe Text -> Int -> Maybe Text -> Maybe Text -> WorkflowStep)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Maybe Text -> Int -> Maybe Text -> Maybe Text -> WorkflowStep)
-> Gen Text
-> Gen
(Maybe Text -> Int -> Maybe Text -> Maybe Text -> WorkflowStep)
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 -> Int -> Maybe Text -> Maybe Text -> WorkflowStep)
-> Gen (Maybe Text)
-> Gen (Int -> Maybe Text -> Maybe Text -> WorkflowStep)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
Gen (Int -> Maybe Text -> Maybe Text -> WorkflowStep)
-> Gen Int -> Gen (Maybe Text -> Maybe Text -> WorkflowStep)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
Gen (Maybe Text -> Maybe Text -> WorkflowStep)
-> Gen (Maybe Text) -> Gen (Maybe Text -> WorkflowStep)
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 -> WorkflowStep)
-> Gen (Maybe Text) -> Gen WorkflowStep
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary