{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}

module Hercules.API.Projects.LegacySimpleJob where

import Data.OpenApi qualified as O3
import Hercules.API.Prelude
import Hercules.API.Projects.Project (Project)
import Hercules.API.Projects.SimpleJob (JobPhase, JobStatus)

-- | Legacy data type for hci < 0.3
data LegacySimpleJob = LegacySimpleJob
  { LegacySimpleJob -> Id "Job"
id :: Id "Job",
    LegacySimpleJob -> Project
project :: Project,
    LegacySimpleJob -> Int64
index :: Int64,
    LegacySimpleJob -> JobStatus
status :: JobStatus,
    LegacySimpleJob -> JobPhase
phase :: JobPhase
  }
  deriving ((forall x. LegacySimpleJob -> Rep LegacySimpleJob x)
-> (forall x. Rep LegacySimpleJob x -> LegacySimpleJob)
-> Generic LegacySimpleJob
forall x. Rep LegacySimpleJob x -> LegacySimpleJob
forall x. LegacySimpleJob -> Rep LegacySimpleJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LegacySimpleJob -> Rep LegacySimpleJob x
from :: forall x. LegacySimpleJob -> Rep LegacySimpleJob x
$cto :: forall x. Rep LegacySimpleJob x -> LegacySimpleJob
to :: forall x. Rep LegacySimpleJob x -> LegacySimpleJob
Generic, Int -> LegacySimpleJob -> ShowS
[LegacySimpleJob] -> ShowS
LegacySimpleJob -> String
(Int -> LegacySimpleJob -> ShowS)
-> (LegacySimpleJob -> String)
-> ([LegacySimpleJob] -> ShowS)
-> Show LegacySimpleJob
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LegacySimpleJob -> ShowS
showsPrec :: Int -> LegacySimpleJob -> ShowS
$cshow :: LegacySimpleJob -> String
show :: LegacySimpleJob -> String
$cshowList :: [LegacySimpleJob] -> ShowS
showList :: [LegacySimpleJob] -> ShowS
Show, LegacySimpleJob -> LegacySimpleJob -> Bool
(LegacySimpleJob -> LegacySimpleJob -> Bool)
-> (LegacySimpleJob -> LegacySimpleJob -> Bool)
-> Eq LegacySimpleJob
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LegacySimpleJob -> LegacySimpleJob -> Bool
== :: LegacySimpleJob -> LegacySimpleJob -> Bool
$c/= :: LegacySimpleJob -> LegacySimpleJob -> Bool
/= :: LegacySimpleJob -> LegacySimpleJob -> Bool
Eq)
  deriving anyclass (LegacySimpleJob -> ()
(LegacySimpleJob -> ()) -> NFData LegacySimpleJob
forall a. (a -> ()) -> NFData a
$crnf :: LegacySimpleJob -> ()
rnf :: LegacySimpleJob -> ()
NFData, [LegacySimpleJob] -> Value
[LegacySimpleJob] -> Encoding
LegacySimpleJob -> Value
LegacySimpleJob -> Encoding
(LegacySimpleJob -> Value)
-> (LegacySimpleJob -> Encoding)
-> ([LegacySimpleJob] -> Value)
-> ([LegacySimpleJob] -> Encoding)
-> ToJSON LegacySimpleJob
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: LegacySimpleJob -> Value
toJSON :: LegacySimpleJob -> Value
$ctoEncoding :: LegacySimpleJob -> Encoding
toEncoding :: LegacySimpleJob -> Encoding
$ctoJSONList :: [LegacySimpleJob] -> Value
toJSONList :: [LegacySimpleJob] -> Value
$ctoEncodingList :: [LegacySimpleJob] -> Encoding
toEncodingList :: [LegacySimpleJob] -> Encoding
ToJSON, Value -> Parser [LegacySimpleJob]
Value -> Parser LegacySimpleJob
(Value -> Parser LegacySimpleJob)
-> (Value -> Parser [LegacySimpleJob]) -> FromJSON LegacySimpleJob
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser LegacySimpleJob
parseJSON :: Value -> Parser LegacySimpleJob
$cparseJSONList :: Value -> Parser [LegacySimpleJob]
parseJSONList :: Value -> Parser [LegacySimpleJob]
FromJSON, Proxy LegacySimpleJob -> Declare (Definitions Schema) NamedSchema
(Proxy LegacySimpleJob -> Declare (Definitions Schema) NamedSchema)
-> ToSchema LegacySimpleJob
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy LegacySimpleJob -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy LegacySimpleJob -> Declare (Definitions Schema) NamedSchema
ToSchema, Typeable LegacySimpleJob
Typeable LegacySimpleJob =>
(Proxy LegacySimpleJob -> Declare (Definitions Schema) NamedSchema)
-> ToSchema LegacySimpleJob
Proxy LegacySimpleJob -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy LegacySimpleJob -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy LegacySimpleJob -> Declare (Definitions Schema) NamedSchema
O3.ToSchema)