{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
-- | The repo commits API as described on
-- .
module Github.Repos.Commits (
CommitQueryOption(..),
commitsFor,
commitsFor',
commitsForR,
commitsWithOptionsFor,
commitsWithOptionsFor',
commitsWithOptionsForR,
commit,
commit',
commitR,
diff,
diff',
diffR,
module Github.Data,
) where
import Data.Time.ISO8601 (formatISO8601)
import Data.Vector (Vector)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BS8
import qualified Data.Text.Encoding as TE
import Github.Auth
import Github.Data
import Github.Request
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 $ BS8.pack $ formatISO8601 date)
renderCommitQueryOption (CommitQueryUntil date) = ("until", Just $ BS8.pack $ formatISO8601 date)
-- | The commit history for a repo.
--
-- > commitsFor "mike-burns" "github"
commitsFor :: Name GithubOwner -> Name Repo -> IO (Either Error (Vector Commit))
commitsFor = commitsFor' Nothing
-- | The commit history for a repo.
-- With authentication.
--
-- > commitsFor' (Just (GithubBasicAuth (user, password))) "mike-burns" "github"
commitsFor' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> IO (Either Error (Vector Commit))
commitsFor' auth user repo =
commitsWithOptionsFor' auth user repo []
-- | List commits on a repository.
-- See
commitsForR :: Name GithubOwner -> Name Repo -> Maybe Count -> GithubRequest k (Vector Commit)
commitsForR user repo limit = commitsWithOptionsForR user repo limit []
commitsWithOptionsFor :: Name GithubOwner -> Name Repo -> [CommitQueryOption] -> IO (Either Error (Vector Commit))
commitsWithOptionsFor = commitsWithOptionsFor' Nothing
-- | The commit history for a repo, with commits filtered to satisfy a list of
-- query options.
-- With authentication.
--
-- > commitsWithOptionsFor' (Just (GithubBasicAuth (user, password))) "mike-burns" "github" [CommitQueryAuthor "djeik"]
commitsWithOptionsFor' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> [CommitQueryOption] -> IO (Either Error (Vector Commit))
commitsWithOptionsFor' auth user repo opts =
executeRequestMaybe auth $ commitsWithOptionsForR user repo Nothing opts
-- | List commits on a repository.
-- See
commitsWithOptionsForR :: Name GithubOwner -> Name Repo -> Maybe Count -> [CommitQueryOption] -> GithubRequest k (Vector Commit)
commitsWithOptionsForR user repo limit opts =
GithubPagedGet ["repos", toPathPart user, toPathPart repo, "commits"] qs limit
where
qs = map renderCommitQueryOption opts
-- | Details on a specific SHA1 for a repo.
--
-- > commit "mike-burns" "github" "9d1a9a361266c3c890b1108ad2fdf52f824b1b81"
commit :: Name GithubOwner -> Name Repo -> Name Commit -> IO (Either Error Commit)
commit = commit' Nothing
-- | Details on a specific SHA1 for a repo.
-- With authentication.
--
-- > commit (Just $ GithubBasicAuth (username, password)) "mike-burns" "github" "9d1a9a361266c3c890b1108ad2fdf52f824b1b81"
commit' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Name Commit -> IO (Either Error Commit)
commit' auth user repo sha =
executeRequestMaybe auth $ commitR user repo sha
-- | Get a single commit.
-- See
commitR :: Name GithubOwner -> Name Repo -> Name Commit -> GithubRequest k Commit
commitR user repo sha =
GithubGet ["repos", toPathPart user, toPathPart repo, "commits", toPathPart sha] []
-- | The diff between two treeishes on a repo.
--
-- > diff "thoughtbot" "paperclip" "41f685f6e01396936bb8cd98e7cca517e2c7d96b" "HEAD"
diff :: Name GithubOwner -> Name Repo -> Name Commit -> Name Commit -> IO (Either Error Diff)
diff = diff' Nothing
-- | The diff between two treeishes on a repo.
--
-- > diff "thoughtbot" "paperclip" "41f685f6e01396936bb8cd98e7cca517e2c7d96b" "HEAD"
diff' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Name Commit -> Name Commit -> IO (Either Error Diff)
diff' auth user repo base headref =
executeRequestMaybe auth $ diffR user repo base headref
-- | Compare two commits.
-- See
diffR :: Name GithubOwner -> Name Repo -> Name Commit -> Name Commit -> GithubRequest k Diff
diffR user repo base headref =
GithubGet ["repos", toPathPart user, toPathPart repo, "compare", toPathPart base ++ "..." ++ toPathPart headref] []