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 ()
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 = CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
[Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"rerun"]
ByteString
forall a. Monoid a => a
mempty
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 = Paths
-> QueryString
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount WorkflowRun)
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
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"runs"]
(WorkflowRunMod -> QueryString
workflowRunModToQueryString WorkflowRunMod
runMod)
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 = Paths -> QueryString -> GenRequest 'MtJSON 'RA WorkflowRun
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
user, 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]
[]
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 = CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete
[Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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]
ByteString
forall a. Monoid a => a
mempty
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 = Paths
-> QueryString -> GenRequest 'MtJSON 'RA (Vector ReviewHistory)
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
user, 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
"approvals"]
[]
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 = CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
[Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"approve"]
ByteString
forall a. Monoid a => a
mempty
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 = Paths -> QueryString -> GenRequest 'MtJSON 'RA WorkflowRun
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
user, 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]
[]
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 = 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
user, 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
"logs"]
[]
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 = CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
[Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"cancel"]
ByteString
forall a. Monoid a => a
mempty
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 = Paths -> QueryString -> GenRequest 'MtRedirect 'RA 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
user, 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
"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 = CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete
[Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"logs"]
ByteString
forall a. Monoid a => a
mempty
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 = CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
[Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"rerun"]
ByteString
forall a. Monoid a => a
mempty
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 = CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post
[Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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
"rerun-failed-jobs"]
ByteString
forall a. Monoid a => a
mempty
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 = Paths
-> QueryString
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount WorkflowRun)
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
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"actions", Text
"workflows", idOrName -> Text
forall a. IsPathPart a => a -> Text
toPathPart idOrName
idOrName, Text
"runs"]
(WorkflowRunMod -> QueryString
workflowRunModToQueryString WorkflowRunMod
runMod)