module GitHub.Endpoints.Actions.Workflows (
    repositoryWorkflowsR,
    workflowR,
    disableWorkflowR,
    triggerWorkflowR,
    enableWorkflowR,
    module GitHub.Data
    ) where

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

-- | List repository workflows.
-- See <https://docs.github.com/en/rest/actions/workflows#list-repository-workflows>
repositoryWorkflowsR
    :: Name Owner
    -> Name Repo
    -> FetchCount
    -> GenRequest 'MtJSON 'RA (WithTotalCount Workflow)
repositoryWorkflowsR :: Name Owner
-> Name Repo
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount Workflow)
repositoryWorkflowsR Name Owner
user Name Repo
repo  = 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"]
    []

-- | Get a workflow.
-- See <https://docs.github.com/en/rest/actions/workflows#get-a-workflow>
workflowR
    :: (IsPathPart idOrName) => Name Owner
    -> Name Repo
    -> idOrName
    -> GenRequest 'MtJSON 'RA  Workflow
workflowR :: forall idOrName.
IsPathPart idOrName =>
Name Owner
-> Name Repo -> idOrName -> GenRequest 'MtJSON 'RA Workflow
workflowR Name Owner
user Name Repo
repo idOrName
idOrName  = 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
"workflows", forall a. IsPathPart a => a -> Text
toPathPart idOrName
idOrName]
    []

-- | Disable a workflow.
-- See <https://docs.github.com/en/rest/actions/workflows#disable-a-workflow>
disableWorkflowR
    :: (IsPathPart idOrName) => Name Owner
    -> Name Repo
    -> idOrName
    -> GenRequest 'MtUnit 'RW  ()
disableWorkflowR :: forall idOrName.
IsPathPart idOrName =>
Name Owner -> Name Repo -> idOrName -> GenRequest 'MtUnit 'RW ()
disableWorkflowR Name Owner
user Name Repo
repo idOrName
idOrName  = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Put
    [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
"disable"]
    forall a. Monoid a => a
mempty

-- | Create a workflow dispatch event.
-- See <https://docs.github.com/en/rest/actions/workflows#create-a-workflow-dispatch-event>
triggerWorkflowR
    :: (ToJSON a, IsPathPart idOrName) => Name Owner
    -> Name Repo
    -> idOrName
    -> CreateWorkflowDispatchEvent a
    -> GenRequest 'MtUnit 'RW  ()
triggerWorkflowR :: forall a idOrName.
(ToJSON a, IsPathPart idOrName) =>
Name Owner
-> Name Repo
-> idOrName
-> CreateWorkflowDispatchEvent a
-> GenRequest 'MtUnit 'RW ()
triggerWorkflowR Name Owner
user Name Repo
repo idOrName
idOrName  = 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
"workflows", forall a. IsPathPart a => a -> Text
toPathPart idOrName
idOrName, Text
"dispatches"]
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
encode

-- | Enable a workflow.
-- See <https://docs.github.com/en/rest/actions/workflows#enable-a-workflow>
enableWorkflowR
    :: (IsPathPart idOrName) => Name Owner
    -> Name Repo
    -> idOrName
    -> GenRequest 'MtUnit 'RW  ()
enableWorkflowR :: forall idOrName.
IsPathPart idOrName =>
Name Owner -> Name Repo -> idOrName -> GenRequest 'MtUnit 'RW ()
enableWorkflowR Name Owner
user Name Repo
repo idOrName
idOrName  = forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Put
    [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
"enable"]
    forall a. Monoid a => a
mempty