-- |
-- The actions API as documented at
-- <https://docs.github.com/en/rest/reference/actions>.

module GitHub.Endpoints.Actions.WorkflowJobs (
    jobR,
    downloadJobLogsR,
    jobsForWorkflowRunAttemptR,
    jobsForWorkflowRunR,
    module GitHub.Data
    ) where

import GitHub.Data
import Network.URI (URI)
import Prelude ()

-- | Get a job for a workflow run.
-- See <https://docs.github.com/en/rest/actions/workflow-jobs#get-a-job-for-a-workflow-run>
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 =
    forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"jobs", forall a. IsPathPart a => a -> Text
toPathPart Id Job
job] []

-- | Download job logs for a workflow run.
-- See <https://docs.github.com/en/rest/actions/workflow-jobs#download-job-logs-for-a-workflow-run>
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 =
    forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"jobs", forall a. IsPathPart a => a -> Text
toPathPart Id Job
job, Text
"logs"] []

-- | List jobs for a workflow run attempt.
-- See <https://docs.github.com/en/rest/actions/workflow-jobs#list-jobs-for-a-workflow-run-attempt>
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 =
    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", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"runs", forall a. IsPathPart a => a -> Text
toPathPart Id WorkflowRun
run, Text
"attempts", forall a. IsPathPart a => a -> Text
toPathPart Id RunAttempt
attempt, Text
"jobs"] []

-- | List jobs for a workflow run.
-- See <https://docs.github.com/en/rest/actions/workflow-jobs#list-jobs-for-a-workflow-run>
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 =
    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", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"runs", forall a. IsPathPart a => a -> Text
toPathPart Id WorkflowRun
run, Text
"jobs"] []