module Github.Repos.Collaborators (
collaboratorsOn,
collaboratorsOn',
collaboratorsOnR,
isCollaboratorOn,
isCollaboratorOnR,
module Github.Data,
) where
import Data.Vector (Vector)
import Github.Auth
import Github.Data
import Github.Request
import Network.HTTP.Types (Status)
collaboratorsOn :: Name GithubOwner -> Name Repo -> IO (Either Error (Vector GithubOwner))
collaboratorsOn = collaboratorsOn' Nothing
collaboratorsOn' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> IO (Either Error (Vector GithubOwner))
collaboratorsOn' auth user repo =
executeRequestMaybe auth $ collaboratorsOnR user repo Nothing
collaboratorsOnR :: Name GithubOwner -> Name Repo -> Maybe Count -> GithubRequest k (Vector GithubOwner)
collaboratorsOnR user repo =
GithubPagedGet ["repos", toPathPart user, toPathPart repo, "collaborators"] []
isCollaboratorOn :: Maybe GithubAuth
-> Name GithubOwner
-> Name Repo
-> Name GithubOwner
-> IO (Either Error Status)
isCollaboratorOn auth user repo coll =
executeRequestMaybe auth $ isCollaboratorOnR user repo coll
isCollaboratorOnR :: Name GithubOwner
-> Name Repo
-> Name GithubOwner
-> GithubRequest k Status
isCollaboratorOnR user repo coll = GithubStatus $
GithubGet ["repos", toPathPart user, toPathPart repo, "collaborators", toPathPart coll] []