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

module GitHub.Endpoints.Actions.Cache (
    cacheUsageOrganizationR,
    cacheUsageByRepositoryR,
    cacheUsageR,
    cachesForRepoR,
    deleteCacheR,
    module GitHub.Data
    ) where

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

-- | Get Actions cache usage for the organization.
-- See <https://docs.github.com/en/rest/actions/cache#get-github-actions-cache-usage-for-an-organization>
cacheUsageOrganizationR
    :: Name Organization
    -> GenRequest 'MtJSON 'RA OrganizationCacheUsage
cacheUsageOrganizationR :: Name Organization -> GenRequest 'MtJSON 'RA OrganizationCacheUsage
cacheUsageOrganizationR Name Organization
org =
    forall (mt :: MediaType (*)) (rw :: RW) a.
Paths -> QueryString -> GenRequest mt rw a
Query [Text
"orgs", forall a. IsPathPart a => a -> Text
toPathPart Name Organization
org, Text
"actions", Text
"cache", Text
"usage"] []

-- | List repositories with GitHub Actions cache usage for an organization.
-- See <https://docs.github.com/en/rest/actions/cache#list-repositories-with-github-actions-cache-usage-for-an-organization>
cacheUsageByRepositoryR
    :: Name Organization
    -> FetchCount
    -> GenRequest 'MtJSON 'RA (WithTotalCount RepositoryCacheUsage)
cacheUsageByRepositoryR :: Name Organization
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount RepositoryCacheUsage)
cacheUsageByRepositoryR Name Organization
org =
    forall a (t :: * -> *) b (mt :: MediaType (*)) (rw :: RW).
(a ~ t b, Foldable t, Semigroup a) =>
Paths -> QueryString -> FetchCount -> GenRequest mt rw a
PagedQuery [Text
"orgs", forall a. IsPathPart a => a -> Text
toPathPart Name Organization
org, Text
"actions", Text
"cache", Text
"usage-by-repository"] []

-- | Get GitHub Actions cache usage for a repository.
-- See <https://docs.github.com/en/rest/actions/cache#get-github-actions-cache-usage-for-a-repository>
cacheUsageR
    :: Name Owner
    -> Name Repo
    -> Request k RepositoryCacheUsage
cacheUsageR :: forall (k :: RW).
Name Owner -> Name Repo -> Request k RepositoryCacheUsage
cacheUsageR Name Owner
user Name Repo
repo =
    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
"cache", Text
"usage"] []

-- | List the GitHub Actions caches for a repository.
-- See <https://docs.github.com/en/rest/actions/cache#list-github-actions-caches-for-a-repository>
cachesForRepoR
    :: Name Owner
    -> Name Repo
    -> CacheMod
    -> FetchCount
    -> GenRequest 'MtJSON 'RA (WithTotalCount Cache)
cachesForRepoR :: Name Owner
-> Name Repo
-> CacheMod
-> FetchCount
-> GenRequest 'MtJSON 'RA (WithTotalCount Cache)
cachesForRepoR Name Owner
user Name Repo
repo CacheMod
opts = 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
"caches"]
    (CacheMod -> QueryString
cacheModToQueryString CacheMod
opts)

-- | Delete GitHub Actions cache for a repository.
-- See <https://docs.github.com/en/rest/actions/cache#delete-a-github-actions-cache-for-a-repository-using-a-cache-id>
deleteCacheR
    :: Name Owner
    -> Name Repo
    -> Id Cache
    -> GenRequest 'MtUnit 'RW ()
deleteCacheR :: Name Owner -> Name Repo -> Id Cache -> GenRequest 'MtUnit 'RW ()
deleteCacheR Name Owner
user Name Repo
repo Id Cache
cacheid =
    forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete Paths
parts forall a. Monoid a => a
mempty
  where
    parts :: Paths
parts = [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
"caches", forall a. IsPathPart a => a -> Text
toPathPart Id Cache
cacheid]