{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
module Web.Bugzilla.RedHat
(
newBugzillaContext
, loginSession
, apikeySession
, anonymousSession
, BugzillaServer
, BugzillaContext
, BugzillaSession (..)
, BugzillaToken (..)
, BugzillaApikey (..)
, searchBugs
, searchBugsAll
, searchBugs'
, searchBugsWithLimit
, searchBugsAllWithLimit
, searchBugsWithLimit'
, getBug
, getBugAll
, getAttachment
, getAttachments
, getComments
, getHistory
, searchUsers
, getUser
, getUserById
, newBzRequest
, sendBzRequest
, intAsText
, Request
, BugId
, AttachmentId
, CommentId
, UserId
, EventId
, FlagId
, FlagType
, UserEmail
, Field (..)
, User (..)
, Flag (..)
, Bug (..)
, ExternalBug (..)
, ExternalType (..)
, Attachment (..)
, Comment (..)
, History (..)
, HistoryEvent (..)
, Change (..)
, Modification (..)
, fieldName
, BugzillaException (..)
) where
import Control.Exception (throw, try)
import Control.Monad.IO.Class (liftIO)
import Data.Aeson (FromJSON)
import qualified Data.Text as T
import Network.Connection (TLSSettings(..))
import Network.HTTP.Conduit (mkManagerSettings, newManager)
import Web.Bugzilla.RedHat.Internal.Network
import Web.Bugzilla.RedHat.Internal.Search
import Web.Bugzilla.RedHat.Internal.Types
newBugzillaContext :: BugzillaServer -> IO BugzillaContext
newBugzillaContext :: BugzillaServer -> IO BugzillaContext
newBugzillaContext BugzillaServer
server = do
let settings :: ManagerSettings
settings = TLSSettings -> Maybe SockSettings -> ManagerSettings
mkManagerSettings (Bool -> Bool -> Bool -> TLSSettings
TLSSettingsSimple Bool
True Bool
False Bool
False) Maybe SockSettings
forall a. Maybe a
Nothing
Manager
manager <- IO Manager -> IO Manager
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Manager -> IO Manager) -> IO Manager -> IO Manager
forall a b. (a -> b) -> a -> b
$ ManagerSettings -> IO Manager
newManager ManagerSettings
settings
BugzillaContext -> IO BugzillaContext
forall (m :: * -> *) a. Monad m => a -> m a
return (BugzillaContext -> IO BugzillaContext)
-> BugzillaContext -> IO BugzillaContext
forall a b. (a -> b) -> a -> b
$ BugzillaServer -> Manager -> BugzillaContext
BugzillaContext BugzillaServer
server Manager
manager
loginSession :: BugzillaContext -> UserEmail -> T.Text -> IO (Maybe BugzillaSession)
loginSession :: BugzillaContext
-> BugzillaServer -> BugzillaServer -> IO (Maybe BugzillaSession)
loginSession BugzillaContext
ctx BugzillaServer
user BugzillaServer
password = do
let loginQuery :: [(BugzillaServer, Maybe BugzillaServer)]
loginQuery = [(BugzillaServer
"login", BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just BugzillaServer
user),
(BugzillaServer
"password", BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just BugzillaServer
password)]
session :: BugzillaSession
session = BugzillaContext -> BugzillaSession
anonymousSession BugzillaContext
ctx
req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"login"] [(BugzillaServer, Maybe BugzillaServer)]
loginQuery
Either BugzillaException BugzillaToken
eToken <- IO BugzillaToken -> IO (Either BugzillaException BugzillaToken)
forall e a. Exception e => IO a -> IO (Either e a)
try (IO BugzillaToken -> IO (Either BugzillaException BugzillaToken))
-> IO BugzillaToken -> IO (Either BugzillaException BugzillaToken)
forall a b. (a -> b) -> a -> b
$ BugzillaSession -> Request -> IO BugzillaToken
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
Maybe BugzillaSession -> IO (Maybe BugzillaSession)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe BugzillaSession -> IO (Maybe BugzillaSession))
-> Maybe BugzillaSession -> IO (Maybe BugzillaSession)
forall a b. (a -> b) -> a -> b
$ case Either BugzillaException BugzillaToken
eToken of
Left (BugzillaAPIError Int
300 String
_) -> Maybe BugzillaSession
forall a. Maybe a
Nothing
Left BugzillaException
e -> BugzillaException -> Maybe BugzillaSession
forall a e. Exception e => e -> a
throw BugzillaException
e
Right BugzillaToken
token -> BugzillaSession -> Maybe BugzillaSession
forall a. a -> Maybe a
Just (BugzillaSession -> Maybe BugzillaSession)
-> BugzillaSession -> Maybe BugzillaSession
forall a b. (a -> b) -> a -> b
$ BugzillaContext -> BugzillaToken -> BugzillaSession
LoginSession BugzillaContext
ctx BugzillaToken
token
apikeySession :: BugzillaContext -> BugzillaApikey -> BugzillaSession
apikeySession :: BugzillaContext -> BugzillaApikey -> BugzillaSession
apikeySession = BugzillaContext -> BugzillaApikey -> BugzillaSession
ApikeySession
anonymousSession :: BugzillaContext -> BugzillaSession
anonymousSession :: BugzillaContext -> BugzillaSession
anonymousSession = BugzillaContext -> BugzillaSession
AnonymousSession
intAsText :: Int -> T.Text
intAsText :: Int -> BugzillaServer
intAsText = String -> BugzillaServer
T.pack (String -> BugzillaServer)
-> (Int -> String) -> Int -> BugzillaServer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show
searchBugs :: BugzillaSession -> SearchExpression -> IO [Bug]
searchBugs :: BugzillaSession -> SearchExpression -> IO [Bug]
searchBugs BugzillaSession
session SearchExpression
search = do
BugList [Bug]
bugs <- BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO BugList
forall a.
FromJSON a =>
BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO a
doSearchBugs BugzillaSession
session SearchExpression
search Maybe BugzillaServer
forall a. Maybe a
Nothing Maybe (Int, Int)
forall a. Maybe a
Nothing
[Bug] -> IO [Bug]
forall (m :: * -> *) a. Monad m => a -> m a
return [Bug]
bugs
searchBugsAll :: BugzillaSession -> SearchExpression -> IO [Bug]
searchBugsAll :: BugzillaSession -> SearchExpression -> IO [Bug]
searchBugsAll BugzillaSession
session SearchExpression
search = do
BugList [Bug]
bugs <- BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO BugList
forall a.
FromJSON a =>
BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO a
doSearchBugs BugzillaSession
session SearchExpression
search (BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just BugzillaServer
"_all") Maybe (Int, Int)
forall a. Maybe a
Nothing
[Bug] -> IO [Bug]
forall (m :: * -> *) a. Monad m => a -> m a
return [Bug]
bugs
searchBugs' :: BugzillaSession -> SearchExpression -> IO [BugId]
searchBugs' :: BugzillaSession -> SearchExpression -> IO [Int]
searchBugs' BugzillaSession
session SearchExpression
search = do
BugIdList [Int]
bugs <- BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO BugIdList
forall a.
FromJSON a =>
BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO a
doSearchBugs BugzillaSession
session SearchExpression
search (BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just BugzillaServer
"id") Maybe (Int, Int)
forall a. Maybe a
Nothing
[Int] -> IO [Int]
forall (m :: * -> *) a. Monad m => a -> m a
return [Int]
bugs
doSearchBugs :: FromJSON a => BugzillaSession -> SearchExpression -> Maybe T.Text -> Maybe (Int, Int) -> IO a
doSearchBugs :: BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO a
doSearchBugs BugzillaSession
session SearchExpression
search Maybe BugzillaServer
includeField Maybe (Int, Int)
limits = do
let fieldsQuery :: [(BugzillaServer, Maybe BugzillaServer)]
fieldsQuery = case Maybe BugzillaServer
includeField of
Maybe BugzillaServer
Nothing -> []
Just BugzillaServer
field -> [(BugzillaServer
"include_fields", BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just BugzillaServer
field)]
limitQuery :: [(BugzillaServer, Maybe BugzillaServer)]
limitQuery = case Maybe (Int, Int)
limits of
Maybe (Int, Int)
Nothing -> []
Just (Int
limit, Int
offset) -> [(BugzillaServer
"limit", BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just (BugzillaServer -> Maybe BugzillaServer)
-> BugzillaServer -> Maybe BugzillaServer
forall a b. (a -> b) -> a -> b
$ Int -> BugzillaServer
intAsText Int
limit),
(BugzillaServer
"offset", BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just (BugzillaServer -> Maybe BugzillaServer)
-> BugzillaServer -> Maybe BugzillaServer
forall a b. (a -> b) -> a -> b
$ Int -> BugzillaServer
intAsText Int
offset)]
searchQuery :: [(BugzillaServer, Maybe BugzillaServer)]
searchQuery = SearchExpression -> [(BugzillaServer, Maybe BugzillaServer)]
evalSearchExpr SearchExpression
search
req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"bug"] ([(BugzillaServer, Maybe BugzillaServer)]
limitQuery [(BugzillaServer, Maybe BugzillaServer)]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> [(BugzillaServer, Maybe BugzillaServer)]
forall a. [a] -> [a] -> [a]
++ [(BugzillaServer, Maybe BugzillaServer)]
fieldsQuery [(BugzillaServer, Maybe BugzillaServer)]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> [(BugzillaServer, Maybe BugzillaServer)]
forall a. [a] -> [a] -> [a]
++ [(BugzillaServer, Maybe BugzillaServer)]
searchQuery)
BugzillaSession -> Request -> IO a
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
searchBugsWithLimit :: BugzillaSession
-> Int
-> Int
-> SearchExpression
-> IO [Bug]
searchBugsWithLimit :: BugzillaSession -> Int -> Int -> SearchExpression -> IO [Bug]
searchBugsWithLimit BugzillaSession
session Int
limit Int
offset SearchExpression
search = do
BugList [Bug]
bugs <- BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO BugList
forall a.
FromJSON a =>
BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO a
doSearchBugs BugzillaSession
session SearchExpression
search Maybe BugzillaServer
forall a. Maybe a
Nothing ((Int, Int) -> Maybe (Int, Int)
forall a. a -> Maybe a
Just (Int
limit, Int
offset))
[Bug] -> IO [Bug]
forall (m :: * -> *) a. Monad m => a -> m a
return [Bug]
bugs
searchBugsAllWithLimit :: BugzillaSession
-> Int
-> Int
-> SearchExpression
-> IO [Bug]
searchBugsAllWithLimit :: BugzillaSession -> Int -> Int -> SearchExpression -> IO [Bug]
searchBugsAllWithLimit BugzillaSession
session Int
limit Int
offset SearchExpression
search = do
BugList [Bug]
bugs <- BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO BugList
forall a.
FromJSON a =>
BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO a
doSearchBugs BugzillaSession
session SearchExpression
search (BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just BugzillaServer
"_all") ((Int, Int) -> Maybe (Int, Int)
forall a. a -> Maybe a
Just (Int
limit, Int
offset))
[Bug] -> IO [Bug]
forall (m :: * -> *) a. Monad m => a -> m a
return [Bug]
bugs
searchBugsWithLimit' :: BugzillaSession
-> Int
-> Int
-> SearchExpression
-> IO [BugId]
searchBugsWithLimit' :: BugzillaSession -> Int -> Int -> SearchExpression -> IO [Int]
searchBugsWithLimit' BugzillaSession
session Int
limit Int
offset SearchExpression
search = do
BugIdList [Int]
bugs <- BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO BugIdList
forall a.
FromJSON a =>
BugzillaSession
-> SearchExpression
-> Maybe BugzillaServer
-> Maybe (Int, Int)
-> IO a
doSearchBugs BugzillaSession
session SearchExpression
search (BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just BugzillaServer
"id") ((Int, Int) -> Maybe (Int, Int)
forall a. a -> Maybe a
Just (Int
limit, Int
offset))
[Int] -> IO [Int]
forall (m :: * -> *) a. Monad m => a -> m a
return [Int]
bugs
getBug :: BugzillaSession -> BugId -> IO (Maybe Bug)
getBug :: BugzillaSession -> Int -> IO (Maybe Bug)
getBug BugzillaSession
session Int
bid = BugzillaSession -> Int -> [BugzillaServer] -> IO (Maybe Bug)
getBugIncludeFields BugzillaSession
session Int
bid []
getBugAll :: BugzillaSession -> BugId -> IO (Maybe Bug)
getBugAll :: BugzillaSession -> Int -> IO (Maybe Bug)
getBugAll BugzillaSession
session Int
bid = BugzillaSession -> Int -> [BugzillaServer] -> IO (Maybe Bug)
getBugIncludeFields BugzillaSession
session Int
bid [BugzillaServer
"_all"]
getBugIncludeFields :: BugzillaSession -> BugId -> [T.Text] -> IO (Maybe Bug)
getBugIncludeFields :: BugzillaSession -> Int -> [BugzillaServer] -> IO (Maybe Bug)
getBugIncludeFields BugzillaSession
session Int
bid [BugzillaServer]
includeFields = do
let req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"bug", Int -> BugzillaServer
intAsText Int
bid] [(BugzillaServer, Maybe BugzillaServer)]
query
(BugList [Bug]
bugs) <- BugzillaSession -> Request -> IO BugList
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
case [Bug]
bugs of
[Bug
bug] -> Maybe Bug -> IO (Maybe Bug)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Bug -> IO (Maybe Bug)) -> Maybe Bug -> IO (Maybe Bug)
forall a b. (a -> b) -> a -> b
$ Bug -> Maybe Bug
forall a. a -> Maybe a
Just Bug
bug
[] -> Maybe Bug -> IO (Maybe Bug)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Bug
forall a. Maybe a
Nothing
[Bug]
_ -> BugzillaException -> IO (Maybe Bug)
forall a e. Exception e => e -> a
throw (BugzillaException -> IO (Maybe Bug))
-> BugzillaException -> IO (Maybe Bug)
forall a b. (a -> b) -> a -> b
$ String -> BugzillaException
BugzillaUnexpectedValue
String
"Request for a single bug returned multiple bugs"
where
query :: [(BugzillaServer, Maybe BugzillaServer)]
query = (BugzillaServer -> (BugzillaServer, Maybe BugzillaServer))
-> [BugzillaServer] -> [(BugzillaServer, Maybe BugzillaServer)]
forall a b. (a -> b) -> [a] -> [b]
map (\BugzillaServer
f -> (BugzillaServer
"include_fields", BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just BugzillaServer
f)) [BugzillaServer]
includeFields
getAttachment :: BugzillaSession -> AttachmentId -> IO (Maybe Attachment)
getAttachment :: BugzillaSession -> Int -> IO (Maybe Attachment)
getAttachment BugzillaSession
session Int
aid = do
let req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"bug", BugzillaServer
"attachment", Int -> BugzillaServer
intAsText Int
aid] []
(AttachmentList [Attachment]
as) <- BugzillaSession -> Request -> IO AttachmentList
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
case [Attachment]
as of
[Attachment
a] -> Maybe Attachment -> IO (Maybe Attachment)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Attachment -> IO (Maybe Attachment))
-> Maybe Attachment -> IO (Maybe Attachment)
forall a b. (a -> b) -> a -> b
$ Attachment -> Maybe Attachment
forall a. a -> Maybe a
Just Attachment
a
[] -> Maybe Attachment -> IO (Maybe Attachment)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Attachment
forall a. Maybe a
Nothing
[Attachment]
_ -> BugzillaException -> IO (Maybe Attachment)
forall a e. Exception e => e -> a
throw (BugzillaException -> IO (Maybe Attachment))
-> BugzillaException -> IO (Maybe Attachment)
forall a b. (a -> b) -> a -> b
$ String -> BugzillaException
BugzillaUnexpectedValue
String
"Request for a single attachment returned multiple attachments"
getAttachments :: BugzillaSession -> BugId -> IO [Attachment]
getAttachments :: BugzillaSession -> Int -> IO [Attachment]
getAttachments BugzillaSession
session Int
bid = do
let req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"bug", Int -> BugzillaServer
intAsText Int
bid, BugzillaServer
"attachment"] []
(AttachmentList [Attachment]
as) <- BugzillaSession -> Request -> IO AttachmentList
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
[Attachment] -> IO [Attachment]
forall (m :: * -> *) a. Monad m => a -> m a
return [Attachment]
as
getComments :: BugzillaSession -> BugId -> IO [Comment]
BugzillaSession
session Int
bid = do
let req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"bug", Int -> BugzillaServer
intAsText Int
bid, BugzillaServer
"comment"] []
(CommentList [Comment]
as) <- BugzillaSession -> Request -> IO CommentList
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
[Comment] -> IO [Comment]
forall (m :: * -> *) a. Monad m => a -> m a
return [Comment]
as
getHistory :: BugzillaSession -> BugId -> IO History
getHistory :: BugzillaSession -> Int -> IO History
getHistory BugzillaSession
session Int
bid = do
let req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"bug", Int -> BugzillaServer
intAsText Int
bid, BugzillaServer
"history"] []
BugzillaSession -> Request -> IO History
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
searchUsers :: BugzillaSession -> T.Text -> IO [User]
searchUsers :: BugzillaSession -> BugzillaServer -> IO [User]
searchUsers BugzillaSession
session BugzillaServer
text = do
let req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"user"] [(BugzillaServer
"match", BugzillaServer -> Maybe BugzillaServer
forall a. a -> Maybe a
Just BugzillaServer
text)]
(UserList [User]
users) <- BugzillaSession -> Request -> IO UserList
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
[User] -> IO [User]
forall (m :: * -> *) a. Monad m => a -> m a
return [User]
users
getUser :: BugzillaSession -> UserEmail -> IO (Maybe User)
getUser :: BugzillaSession -> BugzillaServer -> IO (Maybe User)
getUser BugzillaSession
session BugzillaServer
user = do
let req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"user", BugzillaServer
user] []
(UserList [User]
users) <- BugzillaSession -> Request -> IO UserList
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
case [User]
users of
[User
u] -> Maybe User -> IO (Maybe User)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe User -> IO (Maybe User)) -> Maybe User -> IO (Maybe User)
forall a b. (a -> b) -> a -> b
$ User -> Maybe User
forall a. a -> Maybe a
Just User
u
[] -> Maybe User -> IO (Maybe User)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe User
forall a. Maybe a
Nothing
[User]
_ -> BugzillaException -> IO (Maybe User)
forall a e. Exception e => e -> a
throw (BugzillaException -> IO (Maybe User))
-> BugzillaException -> IO (Maybe User)
forall a b. (a -> b) -> a -> b
$ String -> BugzillaException
BugzillaUnexpectedValue
String
"Request for a single user returned multiple users"
getUserById :: BugzillaSession -> UserId -> IO (Maybe User)
getUserById :: BugzillaSession -> Int -> IO (Maybe User)
getUserById BugzillaSession
session Int
uid = do
let req :: Request
req = BugzillaSession
-> [BugzillaServer]
-> [(BugzillaServer, Maybe BugzillaServer)]
-> Request
newBzRequest BugzillaSession
session [BugzillaServer
"user", Int -> BugzillaServer
intAsText Int
uid] []
(UserList [User]
users) <- BugzillaSession -> Request -> IO UserList
forall a. FromJSON a => BugzillaSession -> Request -> IO a
sendBzRequest BugzillaSession
session Request
req
case [User]
users of
[User
u] -> Maybe User -> IO (Maybe User)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe User -> IO (Maybe User)) -> Maybe User -> IO (Maybe User)
forall a b. (a -> b) -> a -> b
$ User -> Maybe User
forall a. a -> Maybe a
Just User
u
[] -> Maybe User -> IO (Maybe User)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe User
forall a. Maybe a
Nothing
[User]
_ -> BugzillaException -> IO (Maybe User)
forall a e. Exception e => e -> a
throw (BugzillaException -> IO (Maybe User))
-> BugzillaException -> IO (Maybe User)
forall a b. (a -> b) -> a -> b
$ String -> BugzillaException
BugzillaUnexpectedValue
String
"Request for a single user returned multiple users"