{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
module GitLab.API.Todos
(
todos,
todoDone,
todosDone,
defaultTodoFilters,
TodoAttrs (..),
)
where
import qualified Data.ByteString.Lazy as BSL
import Data.Maybe
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import GitLab.Types
import GitLab.WebRequests.GitLabWebCalls
import Network.HTTP.Client
todos :: TodoAttrs -> GitLab [Todo]
todos :: TodoAttrs -> GitLab [Todo]
todos TodoAttrs
attrs = GitLab (Either (Response ByteString) (Maybe [Todo]))
-> GitLab [Todo]
forall a b. GitLab (Either a (Maybe b)) -> GitLab b
gitlabUnsafe (Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe [Todo]))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
"/todos" [GitLabParam]
params)
where
params :: [GitLabParam]
params :: [GitLabParam]
params = TodoAttrs -> [GitLabParam]
groupProjectAttrs TodoAttrs
attrs
data TodoAttrs = TodoAttrs
{
TodoAttrs -> Maybe TodoAction
todoFilter_action :: Maybe TodoAction,
TodoAttrs -> Maybe Int
todoFilter_author_id :: Maybe Int,
TodoAttrs -> Maybe Int
todoFilter_project_id :: Maybe Int,
TodoAttrs -> Maybe Int
todoFilter_group_id :: Maybe Int,
TodoAttrs -> Maybe TodoState
todoFilter_state :: Maybe TodoState,
TodoAttrs -> Maybe TodoType
todoFilter_type :: Maybe TodoType
}
groupProjectAttrs :: TodoAttrs -> [GitLabParam]
groupProjectAttrs :: TodoAttrs -> [GitLabParam]
groupProjectAttrs TodoAttrs
filters =
[Maybe GitLabParam] -> [GitLabParam]
forall a. [Maybe a] -> [a]
catMaybes
[ (\TodoAction
x -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"action", Text -> Maybe ByteString
textToBS (String -> Text
T.pack (TodoAction -> String
forall a. Show a => a -> String
show TodoAction
x)))) (TodoAction -> Maybe GitLabParam)
-> Maybe TodoAction -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TodoAttrs -> Maybe TodoAction
todoFilter_action TodoAttrs
filters,
(\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"author_id", Text -> Maybe ByteString
textToBS (String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TodoAttrs -> Maybe Int
todoFilter_author_id TodoAttrs
filters,
(\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"project_id", Text -> Maybe ByteString
textToBS (String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TodoAttrs -> Maybe Int
todoFilter_project_id TodoAttrs
filters,
(\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"group_id", Text -> Maybe ByteString
textToBS (String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TodoAttrs -> Maybe Int
todoFilter_group_id TodoAttrs
filters,
(\TodoState
x -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"state", Text -> Maybe ByteString
textToBS (String -> Text
T.pack (TodoState -> String
forall a. Show a => a -> String
show TodoState
x)))) (TodoState -> Maybe GitLabParam)
-> Maybe TodoState -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TodoAttrs -> Maybe TodoState
todoFilter_state TodoAttrs
filters,
(\TodoType
x -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"type", Text -> Maybe ByteString
textToBS (String -> Text
T.pack (TodoType -> String
forall a. Show a => a -> String
show TodoType
x)))) (TodoType -> Maybe GitLabParam)
-> Maybe TodoType -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TodoAttrs -> Maybe TodoType
todoFilter_type TodoAttrs
filters
]
where
textToBS :: Text -> Maybe ByteString
textToBS = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Text -> ByteString) -> Text -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
defaultTodoFilters :: TodoAttrs
defaultTodoFilters :: TodoAttrs
defaultTodoFilters =
Maybe TodoAction
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe TodoState
-> Maybe TodoType
-> TodoAttrs
TodoAttrs Maybe TodoAction
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe TodoState
forall a. Maybe a
Nothing Maybe TodoType
forall a. Maybe a
Nothing
todoDone ::
Int ->
GitLab (Either (Response BSL.ByteString) (Maybe ()))
todoDone :: Int -> GitLab (Either (Response ByteString) (Maybe ()))
todoDone Int
todoId =
Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe ()))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr []
where
addr :: Text
addr =
String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
String
"/todos/"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
todoId
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"/mark_as_done"
todosDone ::
GitLab
(Either (Response BSL.ByteString) (Maybe ()))
todosDone :: GitLab (Either (Response ByteString) (Maybe ()))
todosDone =
Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe ()))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr []
where
addr :: Text
addr =
String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
String
"/todos"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"/mark_as_done"