{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
module Hercules.API.Projects.SimpleJob where
import Hercules.API.Prelude
import Hercules.API.Projects.SimpleProject (SimpleProject)
data SimpleJob = SimpleJob
  { SimpleJob -> Id "Job"
id :: Id "Job",
    SimpleJob -> SimpleProject
project :: SimpleProject,
    SimpleJob -> Int64
index :: Int64,
    SimpleJob -> JobStatus
status :: JobStatus,
    SimpleJob -> JobPhase
phase :: JobPhase
  }
  deriving (forall x. Rep SimpleJob x -> SimpleJob
forall x. SimpleJob -> Rep SimpleJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SimpleJob x -> SimpleJob
$cfrom :: forall x. SimpleJob -> Rep SimpleJob x
Generic, Int -> SimpleJob -> ShowS
[SimpleJob] -> ShowS
SimpleJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleJob] -> ShowS
$cshowList :: [SimpleJob] -> ShowS
show :: SimpleJob -> String
$cshow :: SimpleJob -> String
showsPrec :: Int -> SimpleJob -> ShowS
$cshowsPrec :: Int -> SimpleJob -> ShowS
Show, SimpleJob -> SimpleJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleJob -> SimpleJob -> Bool
$c/= :: SimpleJob -> SimpleJob -> Bool
== :: SimpleJob -> SimpleJob -> Bool
$c== :: SimpleJob -> SimpleJob -> Bool
Eq)
  deriving anyclass (SimpleJob -> ()
forall a. (a -> ()) -> NFData a
rnf :: SimpleJob -> ()
$crnf :: SimpleJob -> ()
NFData, [SimpleJob] -> Encoding
[SimpleJob] -> Value
SimpleJob -> Encoding
SimpleJob -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SimpleJob] -> Encoding
$ctoEncodingList :: [SimpleJob] -> Encoding
toJSONList :: [SimpleJob] -> Value
$ctoJSONList :: [SimpleJob] -> Value
toEncoding :: SimpleJob -> Encoding
$ctoEncoding :: SimpleJob -> Encoding
toJSON :: SimpleJob -> Value
$ctoJSON :: SimpleJob -> Value
ToJSON, Value -> Parser [SimpleJob]
Value -> Parser SimpleJob
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SimpleJob]
$cparseJSONList :: Value -> Parser [SimpleJob]
parseJSON :: Value -> Parser SimpleJob
$cparseJSON :: Value -> Parser SimpleJob
FromJSON, Proxy SimpleJob -> Declare (Definitions Schema) NamedSchema
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy SimpleJob -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy SimpleJob -> Declare (Definitions Schema) NamedSchema
ToSchema)
data JobPhase
  = Queued
  | Evaluating
  | Building
  | Effects
  | Done
  deriving (forall x. Rep JobPhase x -> JobPhase
forall x. JobPhase -> Rep JobPhase x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobPhase x -> JobPhase
$cfrom :: forall x. JobPhase -> Rep JobPhase x
Generic, Int -> JobPhase -> ShowS
[JobPhase] -> ShowS
JobPhase -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobPhase] -> ShowS
$cshowList :: [JobPhase] -> ShowS
show :: JobPhase -> String
$cshow :: JobPhase -> String
showsPrec :: Int -> JobPhase -> ShowS
$cshowsPrec :: Int -> JobPhase -> ShowS
Show, JobPhase -> JobPhase -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobPhase -> JobPhase -> Bool
$c/= :: JobPhase -> JobPhase -> Bool
== :: JobPhase -> JobPhase -> Bool
$c== :: JobPhase -> JobPhase -> Bool
Eq)
  deriving anyclass (JobPhase -> ()
forall a. (a -> ()) -> NFData a
rnf :: JobPhase -> ()
$crnf :: JobPhase -> ()
NFData, [JobPhase] -> Encoding
[JobPhase] -> Value
JobPhase -> Encoding
JobPhase -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [JobPhase] -> Encoding
$ctoEncodingList :: [JobPhase] -> Encoding
toJSONList :: [JobPhase] -> Value
$ctoJSONList :: [JobPhase] -> Value
toEncoding :: JobPhase -> Encoding
$ctoEncoding :: JobPhase -> Encoding
toJSON :: JobPhase -> Value
$ctoJSON :: JobPhase -> Value
ToJSON, Value -> Parser [JobPhase]
Value -> Parser JobPhase
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [JobPhase]
$cparseJSONList :: Value -> Parser [JobPhase]
parseJSON :: Value -> Parser JobPhase
$cparseJSON :: Value -> Parser JobPhase
FromJSON, Proxy JobPhase -> Declare (Definitions Schema) NamedSchema
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy JobPhase -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy JobPhase -> Declare (Definitions Schema) NamedSchema
ToSchema)
data JobStatus
  = Pending
  | Failure
  | Success
  deriving (forall x. Rep JobStatus x -> JobStatus
forall x. JobStatus -> Rep JobStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobStatus x -> JobStatus
$cfrom :: forall x. JobStatus -> Rep JobStatus x
Generic, Int -> JobStatus -> ShowS
[JobStatus] -> ShowS
JobStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobStatus] -> ShowS
$cshowList :: [JobStatus] -> ShowS
show :: JobStatus -> String
$cshow :: JobStatus -> String
showsPrec :: Int -> JobStatus -> ShowS
$cshowsPrec :: Int -> JobStatus -> ShowS
Show, JobStatus -> JobStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobStatus -> JobStatus -> Bool
$c/= :: JobStatus -> JobStatus -> Bool
== :: JobStatus -> JobStatus -> Bool
$c== :: JobStatus -> JobStatus -> Bool
Eq)
  deriving anyclass (JobStatus -> ()
forall a. (a -> ()) -> NFData a
rnf :: JobStatus -> ()
$crnf :: JobStatus -> ()
NFData, [JobStatus] -> Encoding
[JobStatus] -> Value
JobStatus -> Encoding
JobStatus -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [JobStatus] -> Encoding
$ctoEncodingList :: [JobStatus] -> Encoding
toJSONList :: [JobStatus] -> Value
$ctoJSONList :: [JobStatus] -> Value
toEncoding :: JobStatus -> Encoding
$ctoEncoding :: JobStatus -> Encoding
toJSON :: JobStatus -> Value
$ctoJSON :: JobStatus -> Value
ToJSON, Value -> Parser [JobStatus]
Value -> Parser JobStatus
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [JobStatus]
$cparseJSONList :: Value -> Parser [JobStatus]
parseJSON :: Value -> Parser JobStatus
$cparseJSON :: Value -> Parser JobStatus
FromJSON, Proxy JobStatus -> Declare (Definitions Schema) NamedSchema
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy JobStatus -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy JobStatus -> Declare (Definitions Schema) NamedSchema
ToSchema)
instance Semigroup JobStatus where
  JobStatus
Failure <> :: JobStatus -> JobStatus -> JobStatus
<> JobStatus
_ = JobStatus
Failure
  JobStatus
_ <> JobStatus
Failure = JobStatus
Failure
  JobStatus
Pending <> JobStatus
_ = JobStatus
Pending
  JobStatus
_ <> JobStatus
Pending = JobStatus
Pending
  JobStatus
Success <> JobStatus
Success = JobStatus
Success
instance Monoid JobStatus where
  mappend :: JobStatus -> JobStatus -> JobStatus
mappend = forall a. Semigroup a => a -> a -> a
(<>)
  mempty :: JobStatus
mempty = JobStatus
Success