{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
module Hercules.API.Projects.Job
( module Hercules.API.Projects.Job,
JobStatus (..),
JobPhase (..),
)
where
import Data.OpenApi qualified as O3
import Data.Swagger (ToParamSchema)
import Hercules.API.Accounts.Account (Account)
import Hercules.API.Evaluation.Evaluation
( Evaluation,
)
import Hercules.API.Forge.Forge (Forge)
import Hercules.API.Inputs.ImmutableInput (ImmutableInput)
import Hercules.API.Prelude
import Hercules.API.Projects.Project (Project)
import Hercules.API.Projects.SimpleJob (JobPhase (..), JobStatus (..))
import Hercules.API.Repos.Repo (Repo)
import Hercules.API.ShowRead (ShowRead (ShowRead))
import Web.HttpApiData (FromHttpApiData, ToHttpApiData)
data Job = Job
{ Job -> Id Job
id :: Id Job,
Job -> Id Project
projectId :: Id Project,
Job -> Int64
index :: Int64,
Job -> Name Project
repoName :: Name Project,
Job -> Name Account
ownerName :: Name Account,
Job -> Name Forge
forgeName :: Name Forge,
Job -> Id Repo
repoId :: Id Repo,
Job -> UTCTime
startTime :: UTCTime,
Job -> Maybe UTCTime
endTime :: Maybe UTCTime,
Job -> JobPhase
jobPhase :: JobPhase,
Job -> Bool
isCancelled :: Bool,
Job -> JobStatus
jobStatus :: JobStatus,
Job -> JobStatus
evaluationStatus :: JobStatus,
Job -> JobStatus
derivationStatus :: JobStatus,
Job -> JobStatus
effectsStatus :: JobStatus,
Job -> Id Evaluation
evaluationId :: Id Evaluation,
Job -> GitCommitSource
source :: GitCommitSource,
:: Map Text ImmutableInput,
Job -> JobType
jobType :: JobType,
Job -> Maybe Text
jobName :: Maybe Text,
Job -> Maybe (Id Job)
rerunOf :: Maybe (Id Job),
Job -> Maybe Int
rerunOfIndex :: Maybe Int,
Job -> Maybe (Id Account)
startedBy :: Maybe (Id Account),
Job -> Maybe (Id Account)
cancelledBy :: Maybe (Id Account),
Job -> Bool
mayCancel :: Bool,
Job -> Bool
mayRerun :: Bool
}
deriving ((forall x. Job -> Rep Job x)
-> (forall x. Rep Job x -> Job) -> Generic Job
forall x. Rep Job x -> Job
forall x. Job -> Rep Job x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Job -> Rep Job x
from :: forall x. Job -> Rep Job x
$cto :: forall x. Rep Job x -> Job
to :: forall x. Rep Job x -> Job
Generic, Int -> Job -> ShowS
[Job] -> ShowS
Job -> String
(Int -> Job -> ShowS)
-> (Job -> String) -> ([Job] -> ShowS) -> Show Job
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Job -> ShowS
showsPrec :: Int -> Job -> ShowS
$cshow :: Job -> String
show :: Job -> String
$cshowList :: [Job] -> ShowS
showList :: [Job] -> ShowS
Show, Job -> Job -> Bool
(Job -> Job -> Bool) -> (Job -> Job -> Bool) -> Eq Job
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Job -> Job -> Bool
== :: Job -> Job -> Bool
$c/= :: Job -> Job -> Bool
/= :: Job -> Job -> Bool
Eq)
deriving anyclass (Job -> ()
(Job -> ()) -> NFData Job
forall a. (a -> ()) -> NFData a
$crnf :: Job -> ()
rnf :: Job -> ()
NFData, [Job] -> Value
[Job] -> Encoding
Job -> Value
Job -> Encoding
(Job -> Value)
-> (Job -> Encoding)
-> ([Job] -> Value)
-> ([Job] -> Encoding)
-> ToJSON Job
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: Job -> Value
toJSON :: Job -> Value
$ctoEncoding :: Job -> Encoding
toEncoding :: Job -> Encoding
$ctoJSONList :: [Job] -> Value
toJSONList :: [Job] -> Value
$ctoEncodingList :: [Job] -> Encoding
toEncodingList :: [Job] -> Encoding
ToJSON, Value -> Parser [Job]
Value -> Parser Job
(Value -> Parser Job) -> (Value -> Parser [Job]) -> FromJSON Job
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser Job
parseJSON :: Value -> Parser Job
$cparseJSONList :: Value -> Parser [Job]
parseJSONList :: Value -> Parser [Job]
FromJSON, Proxy Job -> Declare (Definitions Schema) NamedSchema
(Proxy Job -> Declare (Definitions Schema) NamedSchema)
-> ToSchema Job
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy Job -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy Job -> Declare (Definitions Schema) NamedSchema
ToSchema, Typeable Job
Typeable Job =>
(Proxy Job -> Declare (Definitions Schema) NamedSchema)
-> ToSchema Job
Proxy Job -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy Job -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy Job -> Declare (Definitions Schema) NamedSchema
O3.ToSchema)
data JobType
= Config
| Legacy
| OnPush
| OnSchedule
deriving ((forall x. JobType -> Rep JobType x)
-> (forall x. Rep JobType x -> JobType) -> Generic JobType
forall x. Rep JobType x -> JobType
forall x. JobType -> Rep JobType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. JobType -> Rep JobType x
from :: forall x. JobType -> Rep JobType x
$cto :: forall x. Rep JobType x -> JobType
to :: forall x. Rep JobType x -> JobType
Generic, JobType -> JobType -> Bool
(JobType -> JobType -> Bool)
-> (JobType -> JobType -> Bool) -> Eq JobType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JobType -> JobType -> Bool
== :: JobType -> JobType -> Bool
$c/= :: JobType -> JobType -> Bool
/= :: JobType -> JobType -> Bool
Eq, Int -> JobType
JobType -> Int
JobType -> [JobType]
JobType -> JobType
JobType -> JobType -> [JobType]
JobType -> JobType -> JobType -> [JobType]
(JobType -> JobType)
-> (JobType -> JobType)
-> (Int -> JobType)
-> (JobType -> Int)
-> (JobType -> [JobType])
-> (JobType -> JobType -> [JobType])
-> (JobType -> JobType -> [JobType])
-> (JobType -> JobType -> JobType -> [JobType])
-> Enum JobType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: JobType -> JobType
succ :: JobType -> JobType
$cpred :: JobType -> JobType
pred :: JobType -> JobType
$ctoEnum :: Int -> JobType
toEnum :: Int -> JobType
$cfromEnum :: JobType -> Int
fromEnum :: JobType -> Int
$cenumFrom :: JobType -> [JobType]
enumFrom :: JobType -> [JobType]
$cenumFromThen :: JobType -> JobType -> [JobType]
enumFromThen :: JobType -> JobType -> [JobType]
$cenumFromTo :: JobType -> JobType -> [JobType]
enumFromTo :: JobType -> JobType -> [JobType]
$cenumFromThenTo :: JobType -> JobType -> JobType -> [JobType]
enumFromThenTo :: JobType -> JobType -> JobType -> [JobType]
Enum, JobType
JobType -> JobType -> Bounded JobType
forall a. a -> a -> Bounded a
$cminBound :: JobType
minBound :: JobType
$cmaxBound :: JobType
maxBound :: JobType
Bounded, Int -> JobType -> ShowS
[JobType] -> ShowS
JobType -> String
(Int -> JobType -> ShowS)
-> (JobType -> String) -> ([JobType] -> ShowS) -> Show JobType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> JobType -> ShowS
showsPrec :: Int -> JobType -> ShowS
$cshow :: JobType -> String
show :: JobType -> String
$cshowList :: [JobType] -> ShowS
showList :: [JobType] -> ShowS
Show, ReadPrec [JobType]
ReadPrec JobType
Int -> ReadS JobType
ReadS [JobType]
(Int -> ReadS JobType)
-> ReadS [JobType]
-> ReadPrec JobType
-> ReadPrec [JobType]
-> Read JobType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS JobType
readsPrec :: Int -> ReadS JobType
$creadList :: ReadS [JobType]
readList :: ReadS [JobType]
$creadPrec :: ReadPrec JobType
readPrec :: ReadPrec JobType
$creadListPrec :: ReadPrec [JobType]
readListPrec :: ReadPrec [JobType]
Read)
deriving anyclass (JobType -> ()
(JobType -> ()) -> NFData JobType
forall a. (a -> ()) -> NFData a
$crnf :: JobType -> ()
rnf :: JobType -> ()
NFData, [JobType] -> Value
[JobType] -> Encoding
JobType -> Value
JobType -> Encoding
(JobType -> Value)
-> (JobType -> Encoding)
-> ([JobType] -> Value)
-> ([JobType] -> Encoding)
-> ToJSON JobType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: JobType -> Value
toJSON :: JobType -> Value
$ctoEncoding :: JobType -> Encoding
toEncoding :: JobType -> Encoding
$ctoJSONList :: [JobType] -> Value
toJSONList :: [JobType] -> Value
$ctoEncodingList :: [JobType] -> Encoding
toEncodingList :: [JobType] -> Encoding
ToJSON, Value -> Parser [JobType]
Value -> Parser JobType
(Value -> Parser JobType)
-> (Value -> Parser [JobType]) -> FromJSON JobType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser JobType
parseJSON :: Value -> Parser JobType
$cparseJSONList :: Value -> Parser [JobType]
parseJSONList :: Value -> Parser [JobType]
FromJSON, Proxy JobType -> Declare (Definitions Schema) NamedSchema
(Proxy JobType -> Declare (Definitions Schema) NamedSchema)
-> ToSchema JobType
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy JobType -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy JobType -> Declare (Definitions Schema) NamedSchema
ToSchema, (forall (t :: SwaggerKind (*)). Proxy JobType -> ParamSchema t)
-> ToParamSchema JobType
forall a.
(forall (t :: SwaggerKind (*)). Proxy a -> ParamSchema t)
-> ToParamSchema a
forall (t :: SwaggerKind (*)). Proxy JobType -> ParamSchema t
$ctoParamSchema :: forall (t :: SwaggerKind (*)). Proxy JobType -> ParamSchema t
toParamSchema :: forall (t :: SwaggerKind (*)). Proxy JobType -> ParamSchema t
ToParamSchema, Typeable JobType
Typeable JobType =>
(Proxy JobType -> Declare (Definitions Schema) NamedSchema)
-> ToSchema JobType
Proxy JobType -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy JobType -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy JobType -> Declare (Definitions Schema) NamedSchema
O3.ToSchema, Proxy JobType -> Schema
(Proxy JobType -> Schema) -> ToParamSchema JobType
forall a. (Proxy a -> Schema) -> ToParamSchema a
$ctoParamSchema :: Proxy JobType -> Schema
toParamSchema :: Proxy JobType -> Schema
O3.ToParamSchema)
deriving (JobType -> Text
JobType -> ByteString
JobType -> Builder
(JobType -> Text)
-> (JobType -> Builder)
-> (JobType -> ByteString)
-> (JobType -> Text)
-> (JobType -> Builder)
-> ToHttpApiData JobType
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: JobType -> Text
toUrlPiece :: JobType -> Text
$ctoEncodedUrlPiece :: JobType -> Builder
toEncodedUrlPiece :: JobType -> Builder
$ctoHeader :: JobType -> ByteString
toHeader :: JobType -> ByteString
$ctoQueryParam :: JobType -> Text
toQueryParam :: JobType -> Text
$ctoEncodedQueryParam :: JobType -> Builder
toEncodedQueryParam :: JobType -> Builder
ToHttpApiData, Text -> Either Text JobType
ByteString -> Either Text JobType
(Text -> Either Text JobType)
-> (ByteString -> Either Text JobType)
-> (Text -> Either Text JobType)
-> FromHttpApiData JobType
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text JobType
parseUrlPiece :: Text -> Either Text JobType
$cparseHeader :: ByteString -> Either Text JobType
parseHeader :: ByteString -> Either Text JobType
$cparseQueryParam :: Text -> Either Text JobType
parseQueryParam :: Text -> Either Text JobType
FromHttpApiData) via (ShowRead JobType)
data GitCommitSource = GitCommitSource
{ GitCommitSource -> Text
revision :: Text,
GitCommitSource -> Text
ref :: Text,
GitCommitSource -> Text
message :: Text,
GitCommitSource -> Text
gitCommitterName :: Text,
GitCommitSource -> Maybe Account
committer :: Maybe Account,
GitCommitSource -> Text
link :: Text
}
deriving ((forall x. GitCommitSource -> Rep GitCommitSource x)
-> (forall x. Rep GitCommitSource x -> GitCommitSource)
-> Generic GitCommitSource
forall x. Rep GitCommitSource x -> GitCommitSource
forall x. GitCommitSource -> Rep GitCommitSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GitCommitSource -> Rep GitCommitSource x
from :: forall x. GitCommitSource -> Rep GitCommitSource x
$cto :: forall x. Rep GitCommitSource x -> GitCommitSource
to :: forall x. Rep GitCommitSource x -> GitCommitSource
Generic, Int -> GitCommitSource -> ShowS
[GitCommitSource] -> ShowS
GitCommitSource -> String
(Int -> GitCommitSource -> ShowS)
-> (GitCommitSource -> String)
-> ([GitCommitSource] -> ShowS)
-> Show GitCommitSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GitCommitSource -> ShowS
showsPrec :: Int -> GitCommitSource -> ShowS
$cshow :: GitCommitSource -> String
show :: GitCommitSource -> String
$cshowList :: [GitCommitSource] -> ShowS
showList :: [GitCommitSource] -> ShowS
Show, GitCommitSource -> GitCommitSource -> Bool
(GitCommitSource -> GitCommitSource -> Bool)
-> (GitCommitSource -> GitCommitSource -> Bool)
-> Eq GitCommitSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GitCommitSource -> GitCommitSource -> Bool
== :: GitCommitSource -> GitCommitSource -> Bool
$c/= :: GitCommitSource -> GitCommitSource -> Bool
/= :: GitCommitSource -> GitCommitSource -> Bool
Eq)
deriving anyclass (GitCommitSource -> ()
(GitCommitSource -> ()) -> NFData GitCommitSource
forall a. (a -> ()) -> NFData a
$crnf :: GitCommitSource -> ()
rnf :: GitCommitSource -> ()
NFData, [GitCommitSource] -> Value
[GitCommitSource] -> Encoding
GitCommitSource -> Value
GitCommitSource -> Encoding
(GitCommitSource -> Value)
-> (GitCommitSource -> Encoding)
-> ([GitCommitSource] -> Value)
-> ([GitCommitSource] -> Encoding)
-> ToJSON GitCommitSource
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: GitCommitSource -> Value
toJSON :: GitCommitSource -> Value
$ctoEncoding :: GitCommitSource -> Encoding
toEncoding :: GitCommitSource -> Encoding
$ctoJSONList :: [GitCommitSource] -> Value
toJSONList :: [GitCommitSource] -> Value
$ctoEncodingList :: [GitCommitSource] -> Encoding
toEncodingList :: [GitCommitSource] -> Encoding
ToJSON, Value -> Parser [GitCommitSource]
Value -> Parser GitCommitSource
(Value -> Parser GitCommitSource)
-> (Value -> Parser [GitCommitSource]) -> FromJSON GitCommitSource
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser GitCommitSource
parseJSON :: Value -> Parser GitCommitSource
$cparseJSONList :: Value -> Parser [GitCommitSource]
parseJSONList :: Value -> Parser [GitCommitSource]
FromJSON, Proxy GitCommitSource -> Declare (Definitions Schema) NamedSchema
(Proxy GitCommitSource -> Declare (Definitions Schema) NamedSchema)
-> ToSchema GitCommitSource
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GitCommitSource -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GitCommitSource -> Declare (Definitions Schema) NamedSchema
ToSchema, Typeable GitCommitSource
Typeable GitCommitSource =>
(Proxy GitCommitSource -> Declare (Definitions Schema) NamedSchema)
-> ToSchema GitCommitSource
Proxy GitCommitSource -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy GitCommitSource -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy GitCommitSource -> Declare (Definitions Schema) NamedSchema
O3.ToSchema)
data ProjectAndJobs = ProjectAndJobs
{ ProjectAndJobs -> Project
project :: Project,
ProjectAndJobs -> [Job]
jobs :: [Job]
}
deriving ((forall x. ProjectAndJobs -> Rep ProjectAndJobs x)
-> (forall x. Rep ProjectAndJobs x -> ProjectAndJobs)
-> Generic ProjectAndJobs
forall x. Rep ProjectAndJobs x -> ProjectAndJobs
forall x. ProjectAndJobs -> Rep ProjectAndJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProjectAndJobs -> Rep ProjectAndJobs x
from :: forall x. ProjectAndJobs -> Rep ProjectAndJobs x
$cto :: forall x. Rep ProjectAndJobs x -> ProjectAndJobs
to :: forall x. Rep ProjectAndJobs x -> ProjectAndJobs
Generic, Int -> ProjectAndJobs -> ShowS
[ProjectAndJobs] -> ShowS
ProjectAndJobs -> String
(Int -> ProjectAndJobs -> ShowS)
-> (ProjectAndJobs -> String)
-> ([ProjectAndJobs] -> ShowS)
-> Show ProjectAndJobs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProjectAndJobs -> ShowS
showsPrec :: Int -> ProjectAndJobs -> ShowS
$cshow :: ProjectAndJobs -> String
show :: ProjectAndJobs -> String
$cshowList :: [ProjectAndJobs] -> ShowS
showList :: [ProjectAndJobs] -> ShowS
Show, ProjectAndJobs -> ProjectAndJobs -> Bool
(ProjectAndJobs -> ProjectAndJobs -> Bool)
-> (ProjectAndJobs -> ProjectAndJobs -> Bool) -> Eq ProjectAndJobs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProjectAndJobs -> ProjectAndJobs -> Bool
== :: ProjectAndJobs -> ProjectAndJobs -> Bool
$c/= :: ProjectAndJobs -> ProjectAndJobs -> Bool
/= :: ProjectAndJobs -> ProjectAndJobs -> Bool
Eq)
deriving anyclass (ProjectAndJobs -> ()
(ProjectAndJobs -> ()) -> NFData ProjectAndJobs
forall a. (a -> ()) -> NFData a
$crnf :: ProjectAndJobs -> ()
rnf :: ProjectAndJobs -> ()
NFData, [ProjectAndJobs] -> Value
[ProjectAndJobs] -> Encoding
ProjectAndJobs -> Value
ProjectAndJobs -> Encoding
(ProjectAndJobs -> Value)
-> (ProjectAndJobs -> Encoding)
-> ([ProjectAndJobs] -> Value)
-> ([ProjectAndJobs] -> Encoding)
-> ToJSON ProjectAndJobs
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ProjectAndJobs -> Value
toJSON :: ProjectAndJobs -> Value
$ctoEncoding :: ProjectAndJobs -> Encoding
toEncoding :: ProjectAndJobs -> Encoding
$ctoJSONList :: [ProjectAndJobs] -> Value
toJSONList :: [ProjectAndJobs] -> Value
$ctoEncodingList :: [ProjectAndJobs] -> Encoding
toEncodingList :: [ProjectAndJobs] -> Encoding
ToJSON, Value -> Parser [ProjectAndJobs]
Value -> Parser ProjectAndJobs
(Value -> Parser ProjectAndJobs)
-> (Value -> Parser [ProjectAndJobs]) -> FromJSON ProjectAndJobs
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ProjectAndJobs
parseJSON :: Value -> Parser ProjectAndJobs
$cparseJSONList :: Value -> Parser [ProjectAndJobs]
parseJSONList :: Value -> Parser [ProjectAndJobs]
FromJSON, Proxy ProjectAndJobs -> Declare (Definitions Schema) NamedSchema
(Proxy ProjectAndJobs -> Declare (Definitions Schema) NamedSchema)
-> ToSchema ProjectAndJobs
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy ProjectAndJobs -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy ProjectAndJobs -> Declare (Definitions Schema) NamedSchema
ToSchema, Typeable ProjectAndJobs
Typeable ProjectAndJobs =>
(Proxy ProjectAndJobs -> Declare (Definitions Schema) NamedSchema)
-> ToSchema ProjectAndJobs
Proxy ProjectAndJobs -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy ProjectAndJobs -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy ProjectAndJobs -> Declare (Definitions Schema) NamedSchema
O3.ToSchema)