{-# LANGUAGE CPP #-}
module GitHub.Endpoints.Repos.Commits (
CommitQueryOption(..),
commitsFor,
commitsFor',
commitsForR,
commitsWithOptionsFor,
commitsWithOptionsFor',
commitsWithOptionsForR,
commit,
commit',
commitR,
diff,
diff',
diffR,
module GitHub.Data,
) where
import GitHub.Data
import GitHub.Internal.Prelude
import GitHub.Request
import Prelude ()
import qualified Data.ByteString as BS
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
renderCommitQueryOption :: CommitQueryOption -> (BS.ByteString, Maybe BS.ByteString)
renderCommitQueryOption (CommitQuerySha sha) = ("sha", Just $ TE.encodeUtf8 sha)
renderCommitQueryOption (CommitQueryPath path) = ("path", Just $ TE.encodeUtf8 path)
renderCommitQueryOption (CommitQueryAuthor author) = ("author", Just $ TE.encodeUtf8 author)
renderCommitQueryOption (CommitQuerySince date) = ("since", Just $ TE.encodeUtf8 . T.pack $ formatISO8601 date)
renderCommitQueryOption (CommitQueryUntil date) = ("until", Just $ TE.encodeUtf8 . T.pack $ formatISO8601 date)
commitsFor :: Name Owner -> Name Repo -> IO (Either Error (Vector Commit))
commitsFor = commitsFor' Nothing
commitsFor' :: Maybe Auth -> Name Owner -> Name Repo -> IO (Either Error (Vector Commit))
commitsFor' auth user repo =
commitsWithOptionsFor' auth user repo []
commitsForR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector Commit)
commitsForR user repo limit = commitsWithOptionsForR user repo limit []
commitsWithOptionsFor :: Name Owner -> Name Repo -> [CommitQueryOption] -> IO (Either Error (Vector Commit))
commitsWithOptionsFor = commitsWithOptionsFor' Nothing
commitsWithOptionsFor' :: Maybe Auth -> Name Owner -> Name Repo -> [CommitQueryOption] -> IO (Either Error (Vector Commit))
commitsWithOptionsFor' auth user repo opts =
executeRequestMaybe auth $ commitsWithOptionsForR user repo FetchAll opts
commitsWithOptionsForR :: Name Owner -> Name Repo -> FetchCount -> [CommitQueryOption] -> Request k (Vector Commit)
commitsWithOptionsForR user repo limit opts =
pagedQuery ["repos", toPathPart user, toPathPart repo, "commits"] qs limit
where
qs = map renderCommitQueryOption opts
commit :: Name Owner -> Name Repo -> Name Commit -> IO (Either Error Commit)
commit = commit' Nothing
commit' :: Maybe Auth -> Name Owner -> Name Repo -> Name Commit -> IO (Either Error Commit)
commit' auth user repo sha =
executeRequestMaybe auth $ commitR user repo sha
commitR :: Name Owner -> Name Repo -> Name Commit -> Request k Commit
commitR user repo sha =
query ["repos", toPathPart user, toPathPart repo, "commits", toPathPart sha] []
diff :: Name Owner -> Name Repo -> Name Commit -> Name Commit -> IO (Either Error Diff)
diff = diff' Nothing
diff' :: Maybe Auth -> Name Owner -> Name Repo -> Name Commit -> Name Commit -> IO (Either Error Diff)
diff' auth user repo base headref =
executeRequestMaybe auth $ diffR user repo base headref
diffR :: Name Owner -> Name Repo -> Name Commit -> Name Commit -> Request k Diff
diffR user repo base headref =
query ["repos", toPathPart user, toPathPart repo, "compare", toPathPart base <> "..." <> toPathPart headref] []