{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- License     :  BSD-3-Clause
-- Maintainer  :  Oleg Grenrus <oleg.grenrus@iki.fi>
--
-- The repo commits API as described on
-- <http://developer.github.com/v3/repos/commits/>.
module GitHub.Endpoints.Repos.Commits (
    CommitQueryOption(..),
    commitsForR,
    commitsWithOptionsForR,
    commitR,
    diffR,
    module GitHub.Data,
    ) where

import GitHub.Data
import GitHub.Internal.Prelude
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 :: CommitQueryOption -> (ByteString, Maybe ByteString)
renderCommitQueryOption (CommitQuerySha Text
sha)      = (ByteString
"sha", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TE.encodeUtf8 Text
sha)
renderCommitQueryOption (CommitQueryPath Text
path)     = (ByteString
"path", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TE.encodeUtf8 Text
path)
renderCommitQueryOption (CommitQueryAuthor Text
author) = (ByteString
"author", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TE.encodeUtf8 Text
author)
renderCommitQueryOption (CommitQuerySince UTCTime
date)    = (ByteString
"since", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> (String -> Text) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ UTCTime -> String
formatISO8601 UTCTime
date)
renderCommitQueryOption (CommitQueryUntil UTCTime
date)    = (ByteString
"until", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> (String -> Text) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ UTCTime -> String
formatISO8601 UTCTime
date)

-- | List commits on a repository.
-- See <https://developer.github.com/v3/repos/commits/#list-commits-on-a-repository>
commitsForR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector Commit)
commitsForR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector Commit)
commitsForR Name Owner
user Name Repo
repo FetchCount
limit = Name Owner
-> Name Repo
-> FetchCount
-> [CommitQueryOption]
-> Request k (Vector Commit)
forall (k :: RW).
Name Owner
-> Name Repo
-> FetchCount
-> [CommitQueryOption]
-> Request k (Vector Commit)
commitsWithOptionsForR Name Owner
user Name Repo
repo FetchCount
limit []

-- | List commits on a repository.
-- See <https://developer.github.com/v3/repos/commits/#list-commits-on-a-repository>
commitsWithOptionsForR :: Name Owner -> Name Repo -> FetchCount -> [CommitQueryOption] -> Request k (Vector Commit)
commitsWithOptionsForR :: Name Owner
-> Name Repo
-> FetchCount
-> [CommitQueryOption]
-> Request k (Vector Commit)
commitsWithOptionsForR Name Owner
user Name Repo
repo FetchCount
limit [CommitQueryOption]
opts =
    Paths -> QueryString -> FetchCount -> Request k (Vector Commit)
forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"commits"] QueryString
qs FetchCount
limit
  where
    qs :: QueryString
qs = (CommitQueryOption -> (ByteString, Maybe ByteString))
-> [CommitQueryOption] -> QueryString
forall a b. (a -> b) -> [a] -> [b]
map CommitQueryOption -> (ByteString, Maybe ByteString)
renderCommitQueryOption [CommitQueryOption]
opts

-- | Query a single commit.
-- See <https://developer.github.com/v3/repos/commits/#get-a-single-commit>
commitR :: Name Owner -> Name Repo -> Name Commit -> Request k Commit
commitR :: Name Owner -> Name Repo -> Name Commit -> Request k Commit
commitR Name Owner
user Name Repo
repo Name Commit
sha =
    Paths -> QueryString -> Request k Commit
forall (mt :: RW) a. Paths -> QueryString -> Request mt a
query [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"commits", Name Commit -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Commit
sha] []

-- | Compare two commits.
-- See <https://developer.github.com/v3/repos/commits/#compare-two-commits>
diffR :: Name Owner -> Name Repo -> Name Commit -> Name Commit -> Request k Diff
diffR :: Name Owner
-> Name Repo -> Name Commit -> Name Commit -> Request k Diff
diffR Name Owner
user Name Repo
repo Name Commit
base Name Commit
headref =
    Paths -> QueryString -> Request k Diff
forall (mt :: RW) a. Paths -> QueryString -> Request mt a
query [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"compare", Name Commit -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Commit
base Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"..." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name Commit -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Commit
headref] []