{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
module GitLab.API.Commits
(
repoCommits,
createCommitMultipleFilesActions,
singleCommit,
cheryPickCommit,
revertCommit,
commitDiff,
commitComments,
postCommitComment,
commitDiscussions,
commitMergeRequests,
branchCommits,
CommitAction (..),
ContentEncoding (..),
Action (..),
)
where
import qualified Data.ByteString.Lazy as BSL
import Data.Either
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import GitLab.Types
import GitLab.WebRequests.GitLabWebCalls
import Network.HTTP.Client
repoCommits ::
Project ->
GitLab [Commit]
repoCommits :: Project -> GitLab [Commit]
repoCommits Project
prj = do
Either (Response ByteString) [Commit]
result <- Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) [Commit])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany (Int -> Text
commitsAddr (Project -> Int
project_id Project
prj)) [(ByteString
"with_stats", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"true")]
[Commit] -> GitLab [Commit]
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Commit] -> Either (Response ByteString) [Commit] -> [Commit]
forall b a. b -> Either a b -> b
fromRight [] Either (Response ByteString) [Commit]
result)
where
commitsAddr :: Int -> Text
commitsAddr :: Int -> Text
commitsAddr Int
projId =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits"
createCommitMultipleFilesActions ::
Project ->
Text ->
Text ->
[CommitAction] ->
GitLab (Maybe Commit)
createCommitMultipleFilesActions :: Project -> Text -> Text -> [CommitAction] -> GitLab (Maybe Commit)
createCommitMultipleFilesActions Project
prj Text
branchName Text
commitMsg [CommitAction]
actions = do
Either (Response ByteString) (Maybe Commit)
result <-
Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Commit))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
(Int -> Text
commitsAddr (Project -> Int
project_id Project
prj))
[ (ByteString
"branch", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
branchName)),
(ByteString
"commit_message", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
commitMsg)),
(ByteString
"actions", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 ([Char] -> Text
T.pack ([CommitAction] -> [Char]
forall a. Show a => a -> [Char]
show [CommitAction]
actions))))
]
case Either (Response ByteString) (Maybe Commit)
result of
Left Response ByteString
resp -> [Char] -> GitLab (Maybe Commit)
forall a. HasCallStack => [Char] -> a
error ([Char]
"createCommitMultipleFilesActions: " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Response ByteString -> [Char]
forall a. Show a => a -> [Char]
show Response ByteString
resp)
Right Maybe Commit
x -> Maybe Commit -> GitLab (Maybe Commit)
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Commit
x
where
commitsAddr :: Int -> Text
commitsAddr :: Int -> Text
commitsAddr Int
projId =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits"
data CommitAction = CommitAction
{ CommitAction -> Action
commit_action_action :: Action,
CommitAction -> [Char]
commit_action_file_path :: FilePath,
CommitAction -> Maybe Text
commit_action_previous_path :: Maybe Text,
CommitAction -> Maybe Text
commit_action_content :: Maybe Text,
CommitAction -> Maybe ContentEncoding
commit_action_encoding :: Maybe ContentEncoding,
CommitAction -> Maybe Text
commit_action_last_commit_id :: Maybe Text,
CommitAction -> Maybe Bool
commit_action_execute_filemode :: Maybe Bool
}
deriving (Int -> CommitAction -> [Char] -> [Char]
[CommitAction] -> [Char] -> [Char]
CommitAction -> [Char]
(Int -> CommitAction -> [Char] -> [Char])
-> (CommitAction -> [Char])
-> ([CommitAction] -> [Char] -> [Char])
-> Show CommitAction
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> CommitAction -> [Char] -> [Char]
showsPrec :: Int -> CommitAction -> [Char] -> [Char]
$cshow :: CommitAction -> [Char]
show :: CommitAction -> [Char]
$cshowList :: [CommitAction] -> [Char] -> [Char]
showList :: [CommitAction] -> [Char] -> [Char]
Show, CommitAction -> CommitAction -> Bool
(CommitAction -> CommitAction -> Bool)
-> (CommitAction -> CommitAction -> Bool) -> Eq CommitAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CommitAction -> CommitAction -> Bool
== :: CommitAction -> CommitAction -> Bool
$c/= :: CommitAction -> CommitAction -> Bool
/= :: CommitAction -> CommitAction -> Bool
Eq)
data Action
= ActionCreate
| ActionDelete
| ActionMove
| ActionUpdate
| ActionChmod
deriving (Action -> Action -> Bool
(Action -> Action -> Bool)
-> (Action -> Action -> Bool) -> Eq Action
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Action -> Action -> Bool
== :: Action -> Action -> Bool
$c/= :: Action -> Action -> Bool
/= :: Action -> Action -> Bool
Eq)
instance Show Action where
show :: Action -> [Char]
show Action
ActionCreate = [Char]
"create"
show Action
ActionDelete = [Char]
"delete"
show Action
ActionMove = [Char]
"move"
show Action
ActionUpdate = [Char]
"update"
show Action
ActionChmod = [Char]
"chmod"
data ContentEncoding
= EncodingText
| EncodingBase64
deriving (ContentEncoding -> ContentEncoding -> Bool
(ContentEncoding -> ContentEncoding -> Bool)
-> (ContentEncoding -> ContentEncoding -> Bool)
-> Eq ContentEncoding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ContentEncoding -> ContentEncoding -> Bool
== :: ContentEncoding -> ContentEncoding -> Bool
$c/= :: ContentEncoding -> ContentEncoding -> Bool
/= :: ContentEncoding -> ContentEncoding -> Bool
Eq)
instance Show ContentEncoding where
show :: ContentEncoding -> [Char]
show ContentEncoding
EncodingText = [Char]
"text"
show ContentEncoding
EncodingBase64 = [Char]
"base64"
branchCommits ::
Project ->
Text ->
GitLab (Either (Response BSL.ByteString) [Commit])
branchCommits :: Project -> Text -> GitLab (Either (Response ByteString) [Commit])
branchCommits Project
prj Text
branchName = do
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) [Commit])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany (Int -> Text
commitsAddr (Project -> Int
project_id Project
prj)) [(ByteString
"ref_name", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
branchName))]
where
commitsAddr :: Int -> Text
commitsAddr :: Int -> Text
commitsAddr Int
projId =
Text
"/projects/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits"
singleCommit ::
Project ->
Text ->
GitLab (Maybe Commit)
singleCommit :: Project -> Text -> GitLab (Maybe Commit)
singleCommit Project
project Text
theHash = do
Either (Response ByteString) (Maybe Commit)
result <- Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Commit))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne (Int -> Text
commitsAddr (Project -> Int
project_id Project
project)) []
Maybe Commit -> GitLab (Maybe Commit)
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Commit
-> Either (Response ByteString) (Maybe Commit) -> Maybe Commit
forall b a. b -> Either a b -> b
fromRight Maybe Commit
forall a. Maybe a
Nothing Either (Response ByteString) (Maybe Commit)
result)
where
commitsAddr :: Int -> Text
commitsAddr :: Int -> Text
commitsAddr Int
projId =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
theHash
cheryPickCommit ::
Project ->
Text ->
Text ->
GitLab (Maybe Commit)
cheryPickCommit :: Project -> Text -> Text -> GitLab (Maybe Commit)
cheryPickCommit Project
project Text
theHash Text
branchName = do
Either (Response ByteString) (Maybe Commit)
result <-
Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Commit))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
Text
commitsAddr
[ (ByteString
"branch", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
branchName))
]
case Either (Response ByteString) (Maybe Commit)
result of
Left Response ByteString
_ -> Maybe Commit -> GitLab (Maybe Commit)
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Commit
forall a. Maybe a
Nothing
Right Maybe Commit
x -> Maybe Commit -> GitLab (Maybe Commit)
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Commit
x
where
commitsAddr :: Text
commitsAddr :: Text
commitsAddr =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
project))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
theHash
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/cherry_pick"
revertCommit ::
Project ->
Text ->
Text ->
GitLab (Maybe Commit)
revertCommit :: Project -> Text -> Text -> GitLab (Maybe Commit)
revertCommit Project
project Text
theHash Text
branchName = do
Either (Response ByteString) (Maybe Commit)
result <-
Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Commit))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
Text
commitsAddr
[ (ByteString
"branch", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
branchName))
]
case Either (Response ByteString) (Maybe Commit)
result of
Left Response ByteString
_ -> Maybe Commit -> GitLab (Maybe Commit)
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Commit
forall a. Maybe a
Nothing
Right Maybe Commit
x -> Maybe Commit -> GitLab (Maybe Commit)
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Commit
x
where
commitsAddr :: Text
commitsAddr :: Text
commitsAddr =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
project))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
theHash
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/revert"
commitDiff ::
Project ->
Text ->
GitLab (Either (Response BSL.ByteString) [Diff])
commitDiff :: Project -> Text -> GitLab (Either (Response ByteString) [Diff])
commitDiff Project
project Text
sha = do
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) [Diff])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany (Int -> Text
commitsAddr (Project -> Int
project_id Project
project)) []
where
commitsAddr :: Int -> Text
commitsAddr :: Int -> Text
commitsAddr Int
projId =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
sha
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/diff"
commitComments ::
Project ->
Text ->
GitLab (Either (Response BSL.ByteString) [CommitNote])
Project
project Text
sha = do
Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) [CommitNote])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany (Int -> Text
commitsAddr (Project -> Int
project_id Project
project)) []
where
commitsAddr :: Int -> Text
commitsAddr :: Int -> Text
commitsAddr Int
projId =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
sha
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/comments"
postCommitComment ::
Project ->
Text ->
Text ->
GitLab (Either (Response BSL.ByteString) (Maybe CommitNote))
Project
project Text
sha Text
note = do
Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe CommitNote))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
(Int -> Text
commitsAddr (Project -> Int
project_id Project
project))
[(ByteString
"note", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
note))]
where
commitsAddr :: Int -> Text
commitsAddr :: Int -> Text
commitsAddr Int
projId =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
sha
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/comments"
commitDiscussions ::
Project ->
Text ->
GitLab (Either (Response BSL.ByteString) [Discussion])
commitDiscussions :: Project
-> Text -> GitLab (Either (Response ByteString) [Discussion])
commitDiscussions Project
project Text
sha = do
Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) [Discussion])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany (Int -> Text
commitsAddr (Project -> Int
project_id Project
project)) []
where
commitsAddr :: Int -> Text
commitsAddr :: Int -> Text
commitsAddr Int
projId =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
sha
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/discussions"
commitMergeRequests ::
Project ->
Text ->
GitLab (Either (Response BSL.ByteString) [MergeRequest])
commitMergeRequests :: Project
-> Text -> GitLab (Either (Response ByteString) [MergeRequest])
commitMergeRequests Project
project Text
sha = do
Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) [MergeRequest])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany (Int -> Text
commitsAddr (Project -> Int
project_id Project
project)) []
where
commitsAddr :: Int -> Text
commitsAddr :: Int -> Text
commitsAddr Int
projId =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/commits/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
sha
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/merge_requests"