{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module      : Users
-- Description : Queries about registered users
-- Copyright   : (c) Rob Stewart, Heriot-Watt University, 2019
-- License     : BSD3
-- Maintainer  : robstewart57@gmail.com
-- Stability   : stable
module GitLab.API.Users
  ( -- * List users
    users,

    -- * Single user
    user,
    searchUser,

    -- * User creation
    createUser,

    -- * User modification
    userAttributes,
    modifyUser,

    -- * Delete authentication identity from user
    deleteAuthIdentity,

    -- * User deletion
    deleteUser,

    -- * List current user
    currentUser,

    -- * User status
    currentUserStatus,

    -- * Get the status of a user
    userStatus,

    -- * Get user preferences
    userPreferences,

    -- * Follow and unfollow users
    followUser,
    unfollowUser,

    -- * User counts
    currentUserCounts,

    -- * List SSH keys
    currentUserSshKeys,

    -- * List SSH keys for user
    userSshKeys,

    -- * Add SSH key
    addSshKeyCurrentUser,

    -- * Add SSH key for user
    addSshKeyUser,

    -- * Delete SSH key for current user
    deleteSshKeyCurrentUser,

    -- * Delete SSH key for given user
    deleteSshKeyUser,

    -- * List emails
    emails,

    -- * List emails for user
    emailsCurrentUser,

    -- * Block or unblock user
    blockUser,
    unblockUser,

    -- * Activate or deactivate user
    activateUser,
    deactivateUser,

    -- * Ban or unban user
    banUser,
    unbanUser,

    -- * Approve or reject user
    approveUser,
    rejectUser,

    -- * Users attributes
    defaultUserFilters,
    UserAttrs (..),
  )
where

import qualified Data.ByteString.Lazy as BSL
import Data.Either
import Data.Maybe
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

-- | all registered users.
users :: GitLab [User]
users :: GitLab [User]
users = do
  let pathUser :: Text
pathUser = Text
"/users"
  [User] -> Either (Response ByteString) [User] -> [User]
forall b a. b -> Either a b -> b
fromRight ([Char] -> [User]
forall a. HasCallStack => [Char] -> a
error [Char]
"allUsers error") (Either (Response ByteString) [User] -> [User])
-> GitLabT IO (Either (Response ByteString) [User])
-> GitLab [User]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) [User])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
pathUser []

-- | Get a single user.
user ::
  -- | ID of users
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe User))
user :: Int -> GitLab (Either (Response ByteString) (Maybe User))
user Int
usrId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe User))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
pathUser []
  where
    pathUser :: Text
pathUser =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
usrId)

-- | Extracts the user attributes for a user. Useful for modifying
-- attrbibutes with 'modifyUser'.
userAttributes ::
  -- | the user
  User ->
  -- | is the user a GitLab server administrator
  Bool ->
  -- | the extracted user attributes
  UserAttrs
userAttributes :: User -> Bool -> UserAttrs
userAttributes User
usr Bool
isAdmin =
  Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> UserAttrs
UserAttrs
    (Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
isAdmin)
    (User -> Maybe Text
user_bio User
usr)
    (User -> Maybe Bool
user_can_create_group User
usr)
    (User -> Maybe Text
user_email User
usr)
    (User -> Maybe Int
user_extern_uid User
usr)
    (User -> Maybe Bool
user_external User
usr) -- default is false
    (User -> Maybe Bool
user_force_random_password User
usr) -- default is false
    (User -> Maybe Int
user_group_id_for_saml User
usr)
    (User -> Maybe Text
user_linkedin User
usr)
    (User -> Maybe Text
user_location User
usr)
    (Text -> Maybe Text
forall a. a -> Maybe a
Just (User -> Text
user_name User
usr))
    (User -> Maybe Text
user_note User
usr)
    (User -> Maybe Text
user_organization User
usr)
    (User -> Maybe Text
user_password User
usr)
    (User -> Maybe Bool
user_private_profile User
usr) -- default is false
    (User -> Maybe Int
user_projects_limit User
usr)
    (User -> Maybe Text
user_providor User
usr)
    (User -> Maybe Bool
user_reset_password User
usr)
    (User -> Maybe Bool
user_skip_confirmation User
usr)
    (User -> Maybe Text
user_skype User
usr)
    (User -> Maybe Int
user_theme_id User
usr)
    (User -> Maybe Text
user_twitter User
usr)
    (Text -> Maybe Text
forall a. a -> Maybe a
Just (User -> Text
user_username User
usr))
    (User -> Maybe Bool
user_view_diffs_file_by_file User
usr)
    (User -> Maybe Text
user_website_url User
usr)
    (User -> Maybe Text
user_pronouns User
usr)

-- | Creates a new user. Note only administrators can create new
-- users. Either password, reset_password, or force_random_password
-- must be specified. If reset_password and force_random_password are
-- both false, then password is required. force_random_password and
-- reset_password take priority over password. In addition,
-- reset_password and force_random_password can be used together.
createUser ::
  -- | email address
  Text ->
  -- | user's name
  Text ->
  -- | user's username
  Text ->
  -- | optional attributes
  UserAttrs ->
  GitLab (Either (Response BSL.ByteString) (Maybe User))
createUser :: Text
-> Text
-> Text
-> UserAttrs
-> GitLab (Either (Response ByteString) (Maybe User))
createUser Text
emailAddr Text
name Text
username UserAttrs
attrs =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe User))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
    Text
userAddr
    ( [ (ByteString
"name", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
name)),
        (ByteString
"username", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
username)),
        (ByteString
"email", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
emailAddr))
      ]
        [GitLabParam] -> [GitLabParam] -> [GitLabParam]
forall a. Semigroup a => a -> a -> a
<> UserAttrs -> [GitLabParam]
userAttrs UserAttrs
attrs
    )
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users"

-- | Modifies an existing user. Only administrators can change
-- attributes of a user.
modifyUser ::
  -- | user ID
  Int ->
  -- | optional attributes
  UserAttrs ->
  GitLab (Either (Response BSL.ByteString) (Maybe User))
modifyUser :: Int
-> UserAttrs -> GitLab (Either (Response ByteString) (Maybe User))
modifyUser Int
userId UserAttrs
attrs =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe User))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPut
    Text
userAddr
    (UserAttrs -> [GitLabParam]
userAttrs UserAttrs
attrs)
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
userId)

-- | Deletes a user’s authentication identity using the provider name
-- associated with that identity. Available only for administrators.
deleteAuthIdentity ::
  -- | user
  User ->
  -- | external providor name
  Text ->
  GitLab (Either (Response BSL.ByteString) (Maybe ()))
deleteAuthIdentity :: User -> Text -> GitLab (Either (Response ByteString) (Maybe ()))
deleteAuthIdentity User
usr Text
providor =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe ()))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabDelete Text
userAddr []
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/identities/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
providor

-- | Deletes a user. Available only for administrators.
deleteUser ::
  -- | user
  User ->
  GitLab (Either (Response BSL.ByteString) (Maybe ()))
deleteUser :: User -> GitLab (Either (Response ByteString) (Maybe ()))
deleteUser User
usr =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe ()))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabDelete Text
userAddr []
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))

-- | Get current user.
currentUser :: GitLab User
currentUser :: GitLab User
currentUser =
  User -> Maybe User -> User
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> User
forall a. HasCallStack => [Char] -> a
error [Char]
"currentUser") (Maybe User -> User)
-> (Either (Response ByteString) (Maybe User) -> Maybe User)
-> Either (Response ByteString) (Maybe User)
-> User
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe User
-> Either (Response ByteString) (Maybe User) -> Maybe User
forall b a. b -> Either a b -> b
fromRight ([Char] -> Maybe User
forall a. HasCallStack => [Char] -> a
error [Char]
"currentUser error") (Either (Response ByteString) (Maybe User) -> User)
-> GitLab (Either (Response ByteString) (Maybe User))
-> GitLab User
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe User))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
pathUser []
  where
    pathUser :: Text
pathUser =
      Text
"/user"

-- | Get current user status.
currentUserStatus :: GitLab UserStatus
currentUserStatus :: GitLab UserStatus
currentUserStatus =
  UserStatus -> Maybe UserStatus -> UserStatus
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> UserStatus
forall a. HasCallStack => [Char] -> a
error [Char]
"currentUserStatus") (Maybe UserStatus -> UserStatus)
-> (Either (Response ByteString) (Maybe UserStatus)
    -> Maybe UserStatus)
-> Either (Response ByteString) (Maybe UserStatus)
-> UserStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe UserStatus
-> Either (Response ByteString) (Maybe UserStatus)
-> Maybe UserStatus
forall b a. b -> Either a b -> b
fromRight ([Char] -> Maybe UserStatus
forall a. HasCallStack => [Char] -> a
error [Char]
"currentUserStatus error") (Either (Response ByteString) (Maybe UserStatus) -> UserStatus)
-> GitLabT IO (Either (Response ByteString) (Maybe UserStatus))
-> GitLab UserStatus
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) (Maybe UserStatus))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
pathUser []
  where
    pathUser :: Text
pathUser =
      Text
"/user/status"

-- | Get the status of a user.
userStatus ::
  -- | user
  User ->
  GitLab UserStatus
userStatus :: User -> GitLab UserStatus
userStatus User
usr =
  UserStatus -> Maybe UserStatus -> UserStatus
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> UserStatus
forall a. HasCallStack => [Char] -> a
error [Char]
"userStatus") (Maybe UserStatus -> UserStatus)
-> (Either (Response ByteString) (Maybe UserStatus)
    -> Maybe UserStatus)
-> Either (Response ByteString) (Maybe UserStatus)
-> UserStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe UserStatus
-> Either (Response ByteString) (Maybe UserStatus)
-> Maybe UserStatus
forall b a. b -> Either a b -> b
fromRight ([Char] -> Maybe UserStatus
forall a. HasCallStack => [Char] -> a
error [Char]
"userStatus error") (Either (Response ByteString) (Maybe UserStatus) -> UserStatus)
-> GitLabT IO (Either (Response ByteString) (Maybe UserStatus))
-> GitLab UserStatus
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) (Maybe UserStatus))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
pathUser []
  where
    pathUser :: Text
pathUser =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/status"

-- | Get the status of the current user.
userPreferences ::
  GitLab UserPrefs
userPreferences :: GitLab UserPrefs
userPreferences =
  UserPrefs -> Maybe UserPrefs -> UserPrefs
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> UserPrefs
forall a. HasCallStack => [Char] -> a
error [Char]
"userPreferences") (Maybe UserPrefs -> UserPrefs)
-> (Either (Response ByteString) (Maybe UserPrefs)
    -> Maybe UserPrefs)
-> Either (Response ByteString) (Maybe UserPrefs)
-> UserPrefs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe UserPrefs
-> Either (Response ByteString) (Maybe UserPrefs)
-> Maybe UserPrefs
forall b a. b -> Either a b -> b
fromRight ([Char] -> Maybe UserPrefs
forall a. HasCallStack => [Char] -> a
error [Char]
"userPreferences error") (Either (Response ByteString) (Maybe UserPrefs) -> UserPrefs)
-> GitLabT IO (Either (Response ByteString) (Maybe UserPrefs))
-> GitLab UserPrefs
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) (Maybe UserPrefs))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
pathUser []
  where
    pathUser :: Text
pathUser =
      Text
"/user/preferences"

-- | Follow a user.
followUser ::
  -- | user
  User ->
  GitLab (Either (Response BSL.ByteString) (Maybe User))
followUser :: User -> GitLab (Either (Response ByteString) (Maybe User))
followUser User
usr =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe User))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
    Text
userAddr
    []
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/follow"

-- | Unfollow a user.
unfollowUser ::
  -- | user
  User ->
  GitLab (Either (Response BSL.ByteString) (Maybe User))
unfollowUser :: User -> GitLab (Either (Response ByteString) (Maybe User))
unfollowUser User
usr =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe User))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
    Text
userAddr
    []
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/unfollow"

-- | Get the counts of the currently signed in user.
currentUserCounts :: GitLab UserCount
currentUserCounts :: GitLab UserCount
currentUserCounts =
  UserCount -> Maybe UserCount -> UserCount
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> UserCount
forall a. HasCallStack => [Char] -> a
error [Char]
"currentUserCounts") (Maybe UserCount -> UserCount)
-> (Either (Response ByteString) (Maybe UserCount)
    -> Maybe UserCount)
-> Either (Response ByteString) (Maybe UserCount)
-> UserCount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe UserCount
-> Either (Response ByteString) (Maybe UserCount)
-> Maybe UserCount
forall b a. b -> Either a b -> b
fromRight ([Char] -> Maybe UserCount
forall a. HasCallStack => [Char] -> a
error [Char]
"currentUserCounts error") (Either (Response ByteString) (Maybe UserCount) -> UserCount)
-> GitLabT IO (Either (Response ByteString) (Maybe UserCount))
-> GitLab UserCount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) (Maybe UserCount))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
pathUser []
  where
    pathUser :: Text
pathUser =
      Text
"/user_counts"

-- | Get a list of currently authenticated user’s SSH keys.
currentUserSshKeys :: GitLab Key
currentUserSshKeys :: GitLab Key
currentUserSshKeys =
  Key -> Maybe Key -> Key
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> Key
forall a. HasCallStack => [Char] -> a
error [Char]
"currentUserSshKeys") (Maybe Key -> Key)
-> (Either (Response ByteString) (Maybe Key) -> Maybe Key)
-> Either (Response ByteString) (Maybe Key)
-> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Key -> Either (Response ByteString) (Maybe Key) -> Maybe Key
forall b a. b -> Either a b -> b
fromRight ([Char] -> Maybe Key
forall a. HasCallStack => [Char] -> a
error [Char]
"currentUserSshKeys error") (Either (Response ByteString) (Maybe Key) -> Key)
-> GitLabT IO (Either (Response ByteString) (Maybe Key))
-> GitLab Key
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) (Maybe Key))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
pathUser []
  where
    pathUser :: Text
pathUser =
      Text
"/user/keys"

-- | Get a list of a specified user’s SSH keys.
userSshKeys ::
  -- | user
  User ->
  GitLab Key
userSshKeys :: User -> GitLab Key
userSshKeys User
usr =
  Key -> Maybe Key -> Key
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> Key
forall a. HasCallStack => [Char] -> a
error [Char]
"userSshKeys") (Maybe Key -> Key)
-> (Either (Response ByteString) (Maybe Key) -> Maybe Key)
-> Either (Response ByteString) (Maybe Key)
-> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Key -> Either (Response ByteString) (Maybe Key) -> Maybe Key
forall b a. b -> Either a b -> b
fromRight ([Char] -> Maybe Key
forall a. HasCallStack => [Char] -> a
error [Char]
"userSshKeys error") (Either (Response ByteString) (Maybe Key) -> Key)
-> GitLabT IO (Either (Response ByteString) (Maybe Key))
-> GitLab Key
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) (Maybe Key))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
pathUser []
  where
    pathUser :: Text
pathUser =
      Text
"/user/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/keys"

-- | Creates a new key owned by the currently authenticated user.
addSshKeyCurrentUser ::
  -- | key
  Text ->
  -- | title
  Text ->
  GitLab (Either (Response BSL.ByteString) (Maybe Key))
addSshKeyCurrentUser :: Text
-> Text -> GitLabT IO (Either (Response ByteString) (Maybe Key))
addSshKeyCurrentUser Text
theKey Text
theTitle =
  Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) (Maybe Key))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
    Text
userAddr
    [ (ByteString
"key", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
theKey)),
      (ByteString
"title", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
theTitle))
    ]
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/user/keys"

-- | Create new key owned by specified user. Available only for
-- administrator.
addSshKeyUser ::
  -- | User
  User ->
  -- | key
  Text ->
  -- | title
  Text ->
  GitLab (Either (Response BSL.ByteString) (Maybe Key))
addSshKeyUser :: User
-> Text
-> Text
-> GitLabT IO (Either (Response ByteString) (Maybe Key))
addSshKeyUser User
usr Text
theKey Text
theTitle =
  Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) (Maybe Key))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
    Text
userAddr
    [ (ByteString
"key", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
theKey)),
      (ByteString
"title", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
theTitle))
    ]
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/keys"

-- | Deletes key owned by currently authenticated user.
deleteSshKeyCurrentUser ::
  -- | key ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe ()))
deleteSshKeyCurrentUser :: Int -> GitLab (Either (Response ByteString) (Maybe ()))
deleteSshKeyCurrentUser Int
keyId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe ()))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabDelete Text
userAddr []
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users/keys/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
keyId)

-- | Deletes key owned by a specified user. Available only for
-- administrator.
deleteSshKeyUser ::
  -- | user
  User ->
  -- | key ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe ()))
deleteSshKeyUser :: User -> Int -> GitLab (Either (Response ByteString) (Maybe ()))
deleteSshKeyUser User
usr Int
keyId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe ()))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabDelete Text
userAddr []
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/keys/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
keyId)

-- | Get a list of currently authenticated user’s emails.
emails :: GitLab [Email]
emails :: GitLab [Email]
emails = do
  let pathUser :: Text
pathUser = Text
"/user/emails/"
  [Email] -> Either (Response ByteString) [Email] -> [Email]
forall b a. b -> Either a b -> b
fromRight ([Char] -> [Email]
forall a. HasCallStack => [Char] -> a
error [Char]
"emails error") (Either (Response ByteString) [Email] -> [Email])
-> GitLabT IO (Either (Response ByteString) [Email])
-> GitLab [Email]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) [Email])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
pathUser []

-- | Get a list of currently authenticated user’s emails.
emailsCurrentUser ::
  -- | user
  User ->
  GitLab [Email]
emailsCurrentUser :: User -> GitLab [Email]
emailsCurrentUser User
usr = do
  let pathUser :: Text
pathUser =
        Text
"/user/"
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Maybe Text -> [Char]
forall a. Show a => a -> [Char]
show (User -> Maybe Text
user_email User
usr))
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/emails/"
  [Email] -> Either (Response ByteString) [Email] -> [Email]
forall b a. b -> Either a b -> b
fromRight ([Char] -> [Email]
forall a. HasCallStack => [Char] -> a
error [Char]
"emails error") (Either (Response ByteString) [Email] -> [Email])
-> GitLabT IO (Either (Response ByteString) [Email])
-> GitLab [Email]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) [Email])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
pathUser []

-- | Used internally by the following functions
userAction ::
  -- | user action
  Text ->
  -- | function name for the error
  Text ->
  -- | user
  User ->
  GitLab (Maybe User)
userAction :: Text -> Text -> User -> GitLab (Maybe User)
userAction Text
action Text
funcName User
usr =
  Maybe User
-> Either (Response ByteString) (Maybe User) -> Maybe User
forall b a. b -> Either a b -> b
fromRight ([Char] -> Maybe User
forall a. HasCallStack => [Char] -> a
error (Text -> [Char]
T.unpack Text
funcName [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
" error")) (Either (Response ByteString) (Maybe User) -> Maybe User)
-> GitLab (Either (Response ByteString) (Maybe User))
-> GitLab (Maybe User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe User))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
userAddr []
  where
    userAddr :: Text
    userAddr :: Text
userAddr =
      Text
"/users/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
action

-- | Blocks the specified user. Available only for administrator.
blockUser ::
  -- | user
  User ->
  GitLab (Maybe User)
blockUser :: User -> GitLab (Maybe User)
blockUser = Text -> Text -> User -> GitLab (Maybe User)
userAction Text
"/block" Text
"blockUser"

-- | Unblocks the specified user. Available only for administrator.
unblockUser ::
  -- | user
  User ->
  GitLab (Maybe User)
unblockUser :: User -> GitLab (Maybe User)
unblockUser = Text -> Text -> User -> GitLab (Maybe User)
userAction Text
"/unblock" Text
"unblockUser"

-- | Deactivates the specified user. Available only for administrator.
deactivateUser ::
  -- | user
  User ->
  GitLab (Maybe User)
deactivateUser :: User -> GitLab (Maybe User)
deactivateUser = Text -> Text -> User -> GitLab (Maybe User)
userAction Text
"/deactivate" Text
"deactivateUser"

-- | Activates the specified user. Available only for administrator.
activateUser ::
  -- | user
  User ->
  GitLab (Maybe User)
activateUser :: User -> GitLab (Maybe User)
activateUser = Text -> Text -> User -> GitLab (Maybe User)
userAction Text
"/activate" Text
"activateUser"

-- | Bans the specified user. Available only for administrator.
banUser ::
  -- | user
  User ->
  GitLab (Maybe User)
banUser :: User -> GitLab (Maybe User)
banUser = Text -> Text -> User -> GitLab (Maybe User)
userAction Text
"/ban" Text
"banUser"

-- | Unbans the specified user. Available only for administrator.
unbanUser ::
  -- | user
  User ->
  GitLab (Maybe User)
unbanUser :: User -> GitLab (Maybe User)
unbanUser = Text -> Text -> User -> GitLab (Maybe User)
userAction Text
"/unban" Text
"unbanUser"

-- | Approves the specified user. Available only for administrator.
approveUser ::
  -- | user
  User ->
  GitLab (Maybe User)
approveUser :: User -> GitLab (Maybe User)
approveUser = Text -> Text -> User -> GitLab (Maybe User)
userAction Text
"/approve" Text
"approveUser"

-- | Rejects specified user that is pending approval. Available only for administrator.
rejectUser ::
  -- | user
  User ->
  GitLab (Maybe User)
rejectUser :: User -> GitLab (Maybe User)
rejectUser = Text -> Text -> User -> GitLab (Maybe User)
userAction Text
"/reject" Text
"rejectUser"

-- | No group filters applied, thereby returning all groups.
defaultUserFilters :: UserAttrs
defaultUserFilters :: UserAttrs
defaultUserFilters =
  Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> UserAttrs
UserAttrs Maybe Bool
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing

-- | Attributes related to a group
data UserAttrs = UserAttrs
  { -- | User is an administrator - default is false
    UserAttrs -> Maybe Bool
userFilter_admin :: Maybe Bool,
    -- | User’s biography
    UserAttrs -> Maybe Text
userFilter_bio :: Maybe Text,
    -- | User can create groups
    UserAttrs -> Maybe Bool
userFilter_can_create_group :: Maybe Bool,
    -- | email address
    UserAttrs -> Maybe Text
userFilter_email :: Maybe Text,
    -- | External UID
    UserAttrs -> Maybe Int
userFilter_extern_uid :: Maybe Int,
    -- | Flag the user as external - default is fale
    UserAttrs -> Maybe Bool
userFilter_external :: Maybe Bool,
    -- | Set user password to a random value - default is false
    UserAttrs -> Maybe Bool
userFilter_force_random_password :: Maybe Bool,
    -- | ID of group where SAML has been configured
    UserAttrs -> Maybe Int
userFilter_group_id_for_saml :: Maybe Int,
    -- | User's LinkedIn account
    UserAttrs -> Maybe Text
userFilter_linkedin :: Maybe Text,
    -- | User's location
    UserAttrs -> Maybe Text
userFilter_location :: Maybe Text,
    -- | User's name
    UserAttrs -> Maybe Text
userFilter_name :: Maybe Text,
    -- | Administrator notes for this user
    UserAttrs -> Maybe Text
userFilter_note :: Maybe Text,
    -- | Organization name
    UserAttrs -> Maybe Text
userFilter_organization :: Maybe Text,
    -- | User's password
    UserAttrs -> Maybe Text
userFilter_password :: Maybe Text,
    -- | User’s profile is private - default is false
    UserAttrs -> Maybe Bool
userFilter_private_profile :: Maybe Bool,
    -- | Number of projects user can create
    UserAttrs -> Maybe Int
userFilter_projects_limit :: Maybe Int,
    -- | External provider name
    UserAttrs -> Maybe Text
userFilter_providor :: Maybe Text,
    -- | Send user password reset link - default is false
    UserAttrs -> Maybe Bool
userFilter_reset_password :: Maybe Bool,
    -- | Skip confirmation - default is false
    UserAttrs -> Maybe Bool
userFilter_skip_confirmation :: Maybe Bool,
    -- | User's Skype ID
    UserAttrs -> Maybe Text
userFilter_skype :: Maybe Text,
    -- | User's theme ID - GitLab theme for the user
    UserAttrs -> Maybe Int
userFilter_theme_id :: Maybe Int,
    -- | User's Twitter account
    UserAttrs -> Maybe Text
userFilter_twitter :: Maybe Text,
    -- | User's username
    UserAttrs -> Maybe Text
userFilter_username :: Maybe Text,
    -- | Flag indicating the user sees only one file diff per page
    UserAttrs -> Maybe Bool
userFilter_view_diffs_file_by_file :: Maybe Bool,
    -- | User's website URL
    UserAttrs -> Maybe Text
userFilter_website :: Maybe Text,
    -- | User's pronouns
    UserAttrs -> Maybe Text
userFilter_pronouns :: Maybe Text
  }

userAttrs :: UserAttrs -> [GitLabParam]
userAttrs :: UserAttrs -> [GitLabParam]
userAttrs UserAttrs
filters =
  [Maybe GitLabParam] -> [GitLabParam]
forall a. [Maybe a] -> [a]
catMaybes
    [ (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"admin", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_name UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"bio", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_bio UserAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"can_create_group", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Bool
userFilter_can_create_group UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"email", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_email UserAttrs
filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"extern_uid", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Int
userFilter_extern_uid UserAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"external", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Bool
userFilter_external UserAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"force_random_password", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Bool
userFilter_force_random_password UserAttrs
filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"group_id_for_saml", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Int
userFilter_group_id_for_saml UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"linkedin", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_linkedin UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"location", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_location UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"name", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_name UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"note", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_note UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"organization", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_organization UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"password", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_password UserAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"private_profile", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Bool
userFilter_private_profile UserAttrs
filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"projects_limit", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Int
userFilter_projects_limit UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"providor", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_providor UserAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"reset_password", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Bool
userFilter_reset_password UserAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"skip_confirmation", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Bool
userFilter_skip_confirmation UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"skype", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_skype UserAttrs
filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"theme_id", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Int
userFilter_theme_id UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"twitter", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_twitter UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"username", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_username UserAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"view_diffs_file_by_file", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Bool
userFilter_view_diffs_file_by_file UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"website", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_website UserAttrs
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"pronouns", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< UserAttrs -> Maybe Text
userFilter_pronouns UserAttrs
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
    showBool :: Bool -> Text
    showBool :: Bool -> Text
showBool Bool
True = Text
"true"
    showBool Bool
False = Text
"false"

-- | searches for a user given a username.
searchUser ::
  -- | username to search for
  Text ->
  GitLab (Maybe User)
searchUser :: Text -> GitLab (Maybe User)
searchUser Text
username = do
  let pathUser :: Text
pathUser = Text
"/users"
      params :: [GitLabParam]
params = [(ByteString
"username", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
username))]
  Either (Response ByteString) [User]
result <- Text
-> [GitLabParam]
-> GitLabT IO (Either (Response ByteString) [User])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
pathUser [GitLabParam]
params
  case Either (Response ByteString) [User]
result of
    Left Response ByteString
_err -> Maybe User -> GitLab (Maybe User)
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe User
forall a. Maybe a
Nothing
    Right [] -> Maybe User -> GitLab (Maybe User)
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe User
forall a. Maybe a
Nothing
    Right (User
x : [User]
_) -> Maybe User -> GitLab (Maybe User)
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (User -> Maybe User
forall a. a -> Maybe a
Just User
x)