module GitHub.Endpoints.Actions.WorkflowJobs (
jobR,
downloadJobLogsR,
jobsForWorkflowRunAttemptR,
jobsForWorkflowRunR,
module GitHub.Data
) where
import GitHub.Data
import Network.URI (URI)
import Prelude ()
jobR
:: Name Owner
-> Name Repo
-> Id Job
-> Request 'RA Job
jobR :: Name Owner -> Name Repo -> Id Job -> Request 'RA Job
jobR Name Owner
owner Name Repo
repo Id Job
job =
Paths -> QueryString -> Request 'RA Job
forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"jobs", Id Job -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Job
job] []
downloadJobLogsR
:: Name Owner
-> Name Repo
-> Id Job
-> GenRequest 'MtRedirect 'RO URI
downloadJobLogsR :: Name Owner -> Name Repo -> Id Job -> GenRequest 'MtRedirect 'RO URI
downloadJobLogsR Name Owner
owner Name Repo
repo Id Job
job =
Paths -> QueryString -> GenRequest 'MtRedirect 'RO URI
forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"jobs", Id Job -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Job
job, Text
"logs"] []
jobsForWorkflowRunAttemptR
:: Name Owner
-> Name Repo
-> Id WorkflowRun
-> Id RunAttempt
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount Job)
jobsForWorkflowRunAttemptR :: Name Owner
-> Name Repo
-> Id WorkflowRun
-> Id RunAttempt
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount Job)
jobsForWorkflowRunAttemptR Name Owner
owner Name Repo
repo Id WorkflowRun
run Id RunAttempt
attempt =
Paths
-> QueryString
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount Job)
forall a (t :: * -> *) b (mt :: MediaType (*)) (rw :: RW).
(a ~ t b, Foldable t, Semigroup a) =>
Paths -> QueryString -> FetchCount -> GenRequest mt rw a
PagedQuery [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"runs", Id WorkflowRun -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id WorkflowRun
run, Text
"attempts", Id RunAttempt -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id RunAttempt
attempt, Text
"jobs"] []
jobsForWorkflowRunR
:: Name Owner
-> Name Repo
-> Id WorkflowRun
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount Job)
jobsForWorkflowRunR :: Name Owner
-> Name Repo
-> Id WorkflowRun
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount Job)
jobsForWorkflowRunR Name Owner
owner Name Repo
repo Id WorkflowRun
run =
Paths
-> QueryString
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount Job)
forall a (t :: * -> *) b (mt :: MediaType (*)) (rw :: RW).
(a ~ t b, Foldable t, Semigroup a) =>
Paths -> QueryString -> FetchCount -> GenRequest mt rw a
PagedQuery [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"runs", Id WorkflowRun -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id WorkflowRun
run, Text
"jobs"] []