-----------------------------------------------------------------------------
-- |
-- License     :  BSD-3-Clause
-- Maintainer  :  Oleg Grenrus <oleg.grenrus@iki.fi>
--
-- The repo watching API as described on
-- <https://developer.github.com/v3/activity/watching/>.
module GitHub.Endpoints.Activity.Watching (
    watchersForR,
    reposWatchedByR,
    unwatchRepoR,
    module GitHub.Data,
) where

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

-- | List watchers.
-- See <https://developer.github.com/v3/activity/watching/#list-watchers>
watchersForR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector SimpleUser)
watchersForR :: Name Owner
-> Name Repo -> FetchCount -> Request k (Vector SimpleUser)
watchersForR Name Owner
user Name Repo
repo FetchCount
limit =
    Paths -> QueryString -> FetchCount -> Request k (Vector SimpleUser)
forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector 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
"watchers"] [] FetchCount
limit

-- | List repositories being watched.
-- See <https://developer.github.com/v3/activity/watching/#list-repositories-being-watched>
reposWatchedByR :: Name Owner -> FetchCount -> Request k (Vector Repo)
reposWatchedByR :: Name Owner -> FetchCount -> Request k (Vector Repo)
reposWatchedByR Name Owner
user =
    Paths -> QueryString -> FetchCount -> Request k (Vector Repo)
forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery [Text
"users", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Text
"subscriptions"] []

-- | Stop watching repository.
-- See <https://docs.github.com/en/rest/reference/activity#delete-a-repository-subscription>
unwatchRepoR :: Name Owner -> Name Repo -> Request 'RW ()
unwatchRepoR :: Name Owner -> Name Repo -> Request 'RW ()
unwatchRepoR Name Owner
owner Name Repo
repo =
    CommandMethod -> Paths -> ByteString -> Request 'RW ()
forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Delete [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"subscription"] ByteString
forall a. Monoid a => a
mempty