module Github.GitData.References (
reference,
reference',
referenceR,
references,
references',
referencesR,
createReference,
createReferenceR,
namespacedReferences,
module Github.Data,
) where
import Data.Aeson.Compat (encode)
import Data.Vector (Vector)
import Github.Auth
import Github.Data
import Github.Request
reference' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Name GitReference -> IO (Either Error GitReference)
reference' auth user repo ref =
executeRequestMaybe auth $ referenceR user repo ref
reference :: Name GithubOwner -> Name Repo -> Name GitReference -> IO (Either Error GitReference)
reference = reference' Nothing
referenceR :: Name GithubOwner -> Name Repo -> Name GitReference -> GithubRequest k GitReference
referenceR user repo ref =
GithubGet ["repos", toPathPart user, toPathPart repo, "git", "refs", toPathPart ref] []
references' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> IO (Either Error (Vector GitReference))
references' auth user repo =
executeRequestMaybe auth $ referencesR user repo Nothing
references :: Name GithubOwner -> Name Repo -> IO (Either Error (Vector GitReference))
references = references' Nothing
referencesR :: Name GithubOwner -> Name Repo -> Maybe Count -> GithubRequest k (Vector GitReference)
referencesR user repo =
GithubPagedGet ["repos", toPathPart user, toPathPart repo, "git", "refs"] []
createReference :: GithubAuth -> Name GithubOwner -> Name Repo -> NewGitReference -> IO (Either Error GitReference)
createReference auth user repo newRef =
executeRequest auth $ createReferenceR user repo newRef
createReferenceR :: Name GithubOwner -> Name Repo -> NewGitReference -> GithubRequest 'True GitReference
createReferenceR user repo newRef =
GithubPost Post ["repos", toPathPart user, toPathPart repo , "git", "refs"] (encode newRef)
namespacedReferences :: Name GithubOwner -> Name Repo -> String -> IO (Either Error [GitReference])
namespacedReferences user repo namespace =
executeRequest' $ namespacedReferencesR user repo namespace
namespacedReferencesR :: Name GithubOwner -> Name Repo -> String -> GithubRequest k [GitReference]
namespacedReferencesR user repo namespace =
GithubGet ["repos", toPathPart user, toPathPart repo, "git", "refs", namespace] []