module GitHub.Endpoints.Activity.Starring (
stargazersFor,
stargazersForR,
reposStarredBy,
reposStarredByR,
myStarred,
myStarredR,
myStarredAcceptStar,
myStarredAcceptStarR,
starRepo,
starRepoR,
unstarRepo,
unstarRepoR,
module GitHub.Data,
) where
import GitHub.Auth
import GitHub.Data
import GitHub.Internal.Prelude
import GitHub.Request
import Prelude ()
stargazersFor :: Maybe Auth -> Name Owner -> Name Repo -> IO (Either Error (Vector SimpleUser))
stargazersFor auth user repo =
executeRequestMaybe auth $ stargazersForR user repo FetchAll
stargazersForR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector SimpleUser)
stargazersForR user repo =
pagedQuery ["repos", toPathPart user, toPathPart repo, "stargazers"] []
reposStarredBy :: Maybe Auth -> Name Owner -> IO (Either Error (Vector Repo))
reposStarredBy auth user =
executeRequestMaybe auth $ reposStarredByR user FetchAll
reposStarredByR :: Name Owner -> FetchCount -> Request k (Vector Repo)
reposStarredByR user =
pagedQuery ["users", toPathPart user, "starred"] []
myStarred :: Auth -> IO (Either Error (Vector Repo))
myStarred auth =
executeRequest auth $ myStarredR FetchAll
myStarredR :: FetchCount -> Request 'RA (Vector Repo)
myStarredR = pagedQuery ["user", "starred"] []
myStarredAcceptStar :: Auth -> IO (Either Error (Vector RepoStarred))
myStarredAcceptStar auth =
executeRequest auth $ myStarredAcceptStarR FetchAll
myStarredAcceptStarR :: FetchCount -> GenRequest 'MtStar 'RA (Vector RepoStarred)
myStarredAcceptStarR = PagedQuery ["user", "starred"] []
starRepo :: Auth -> Name Owner -> Name Repo -> IO (Either Error ())
starRepo auth user repo = executeRequest auth $ starRepoR user repo
starRepoR :: Name Owner -> Name Repo -> GenRequest 'MtUnit 'RW ()
starRepoR user repo = Command Put paths mempty
where
paths = ["user", "starred", toPathPart user, toPathPart repo]
unstarRepo :: Auth -> Name Owner -> Name Repo -> IO (Either Error ())
unstarRepo auth user repo = executeRequest auth $ unstarRepoR user repo
unstarRepoR :: Name Owner -> Name Repo -> GenRequest 'MtUnit 'RW ()
unstarRepoR user repo = Command Delete paths mempty
where
paths = ["user", "starred", toPathPart user, toPathPart repo]