module GitHub.Endpoints.Actions.WorkflowRuns (
    reRunJobR,
    workflowRunsR,
    workflowRunR,
    deleteWorkflowRunR,
    workflowRunReviewHistoryR,
    approveWorkflowRunR,
    workflowRunAttemptR,
    downloadWorkflowRunAttemptLogsR,
    cancelWorkflowRunR,
    downloadWorkflowRunLogsR,
    deleteWorkflowRunLogsR,
    reRunWorkflowR,
    reRunFailedJobsR,
    workflowRunsForWorkflowR,
    module GitHub.Data
    ) where

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

-- | Re-run a job from a workflow run.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#re-run-a-job-from-a-workflow-run>
reRunJobR
    :: Name Owner
    -> Name Repo
    -> Id Job
    -> GenRequest 'MtUnit 'RW ()
reRunJobR :: Name Owner -> Name Repo -> Id Job -> GenRequest 'MtUnit 'RW ()
reRunJobR Name Owner
user Name Repo
repo Id Job
job = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"rerun"]
    forall a. Monoid a => a
mempty

-- | List workflow runs for a repository.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#list-workflow-runs-for-a-repository>
workflowRunsR
    :: Name Owner
    -> Name Repo
    -> WorkflowRunMod
    -> FetchCount
    -> GenRequest 'MtJSON 'RA (WithTotalCount WorkflowRun)
workflowRunsR :: Name Owner
-> Name Repo
-> WorkflowRunMod
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount WorkflowRun)
workflowRunsR Name Owner
user Name Repo
repo WorkflowRunMod
runMod = 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
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"runs"]
    (WorkflowRunMod -> QueryString
workflowRunModToQueryString WorkflowRunMod
runMod)

-- | Get a workflow run.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#get-a-workflow-run>
workflowRunR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    -> GenRequest 'MtJSON 'RA WorkflowRun
workflowRunR :: Name Owner
-> Name Repo
-> Id WorkflowRun
-> GenRequest 'MtJSON 'RA WorkflowRun
workflowRunR Name Owner
user Name Repo
repo Id WorkflowRun
run = forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"runs", forall a. IsPathPart a => a -> Text
toPathPart Id WorkflowRun
run]
    []

-- | Delete a workflow run.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#delete-a-workflow-run>
deleteWorkflowRunR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    -> GenRequest 'MtUnit 'RW ()
deleteWorkflowRunR :: Name Owner
-> Name Repo -> Id WorkflowRun -> GenRequest 'MtUnit 'RW ()
deleteWorkflowRunR Name Owner
user Name Repo
repo Id WorkflowRun
run = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"runs", forall a. IsPathPart a => a -> Text
toPathPart Id WorkflowRun
run]
    forall a. Monoid a => a
mempty

-- | Get the review history for a workflow run.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#get-the-review-history-for-a-workflow-run>
workflowRunReviewHistoryR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    -> GenRequest 'MtJSON 'RA (Vector ReviewHistory)
workflowRunReviewHistoryR :: Name Owner
-> Name Repo
-> Id WorkflowRun
-> GenRequest 'MtJSON 'RA (Vector ReviewHistory)
workflowRunReviewHistoryR Name Owner
user Name Repo
repo Id WorkflowRun
run = forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"approvals"]
    []

-- | Approve a workflow run for a fork pull request.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#approve-a-workflow-run-for-a-fork-pull-request>
approveWorkflowRunR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    -> GenRequest 'MtUnit 'RW ()
approveWorkflowRunR :: Name Owner
-> Name Repo -> Id WorkflowRun -> GenRequest 'MtUnit 'RW ()
approveWorkflowRunR Name Owner
user Name Repo
repo Id WorkflowRun
run = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"approve"]
    forall a. Monoid a => a
mempty

-- | Get a workflow run attempt.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#get-a-workflow-run-attempt>
workflowRunAttemptR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    -> Id RunAttempt
    -> GenRequest 'MtJSON 'RA WorkflowRun
workflowRunAttemptR :: Name Owner
-> Name Repo
-> Id WorkflowRun
-> Id RunAttempt
-> GenRequest 'MtJSON 'RA WorkflowRun
workflowRunAttemptR Name Owner
user Name Repo
repo Id WorkflowRun
run Id RunAttempt
attempt = forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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]
    []

-- | Download workflow run attempt logs.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#download-workflow-run-attempt-logs>
downloadWorkflowRunAttemptLogsR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    -> Id RunAttempt
    -> GenRequest 'MtRedirect 'RO URI
downloadWorkflowRunAttemptLogsR :: Name Owner
-> Name Repo
-> Id WorkflowRun
-> Id RunAttempt
-> GenRequest 'MtRedirect 'RO URI
downloadWorkflowRunAttemptLogsR Name Owner
user Name Repo
repo Id WorkflowRun
run Id RunAttempt
attempt = forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"logs"]
    []

-- | Cancel a workflow run.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#cancel-a-workflow-run>
cancelWorkflowRunR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    -> GenRequest 'MtUnit 'RW ()
cancelWorkflowRunR :: Name Owner
-> Name Repo -> Id WorkflowRun -> GenRequest 'MtUnit 'RW ()
cancelWorkflowRunR Name Owner
user Name Repo
repo Id WorkflowRun
run = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"cancel"]
    forall a. Monoid a => a
mempty

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

-- | Delete workflow run logs.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#delete-workflow-run-logs>
deleteWorkflowRunLogsR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    ->  GenRequest 'MtUnit 'RW ()
deleteWorkflowRunLogsR :: Name Owner
-> Name Repo -> Id WorkflowRun -> GenRequest 'MtUnit 'RW ()
deleteWorkflowRunLogsR Name Owner
user Name Repo
repo Id WorkflowRun
run = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"logs"]
    forall a. Monoid a => a
mempty

-- | Re-run a workflow.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#re-run-a-workflow>
reRunWorkflowR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    -> GenRequest 'MtUnit 'RW ()
reRunWorkflowR :: Name Owner
-> Name Repo -> Id WorkflowRun -> GenRequest 'MtUnit 'RW ()
reRunWorkflowR Name Owner
user Name Repo
repo Id WorkflowRun
run = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"rerun"]
    forall a. Monoid a => a
mempty

-- | Re-run failed jobs from a workflow run.
-- See <https://docs.github.com/en/rest/actions/re-run-failed-jobs-from-a-workflow-run>
reRunFailedJobsR
    :: Name Owner
    -> Name Repo
    -> Id WorkflowRun
    -> GenRequest 'MtUnit 'RW ()
reRunFailedJobsR :: Name Owner
-> Name Repo -> Id WorkflowRun -> GenRequest 'MtUnit 'RW ()
reRunFailedJobsR Name Owner
user Name Repo
repo Id WorkflowRun
run = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
    [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"rerun-failed-jobs"]
    forall a. Monoid a => a
mempty

-- | List workflow runs for a workflow.
-- See <https://docs.github.com/en/rest/actions/workflow-runs#list-workflow-runs-for-a-workflow>
workflowRunsForWorkflowR
    :: (IsPathPart idOrName) => Name Owner
    -> Name Repo
    -> idOrName
    -> WorkflowRunMod
    -> FetchCount
    -> GenRequest 'MtJSON 'RA (WithTotalCount WorkflowRun)
workflowRunsForWorkflowR :: forall idOrName.
IsPathPart idOrName =>
Name Owner
-> Name Repo
-> idOrName
-> WorkflowRunMod
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount WorkflowRun)
workflowRunsForWorkflowR Name Owner
user Name Repo
repo idOrName
idOrName WorkflowRunMod
runMod = 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
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"workflows", forall a. IsPathPart a => a -> Text
toPathPart idOrName
idOrName, Text
"runs"]
     (WorkflowRunMod -> QueryString
workflowRunModToQueryString WorkflowRunMod
runMod)