-- |
-- The repo statuses API as described on
-- .
module GitHub.Endpoints.Repos.Statuses (
createStatusR,
statusesForR,
statusForR,
module GitHub.Data
) where
import GitHub.Data
import GitHub.Internal.Prelude
import Prelude ()
-- | Create a new status
-- See
createStatusR :: Name Owner -> Name Repo -> Name Commit -> NewStatus -> Request 'RW Status
createStatusR owner repo sha =
command Post parts . encode
where
parts = ["repos", toPathPart owner, toPathPart repo, "statuses", toPathPart sha]
-- | All statuses for a commit
-- See
statusesForR :: Name Owner -> Name Repo -> Name Commit -> FetchCount -> Request 'RW (Vector Status)
statusesForR user repo sha =
pagedQuery ["repos", toPathPart user, toPathPart repo, "commits", toPathPart sha, "statuses"] []
-- | The combined status for a specific commit
-- See
statusForR :: Name Owner -> Name Repo -> Name Commit -> Request 'RW CombinedStatus
statusForR user repo sha =
query ["repos", toPathPart user, toPathPart repo, "commits", toPathPart sha, "status"] []