{-# LANGUAGE OverloadedStrings #-}

-- | This package is designed to provide an easy-to-use, typesafe
--   interface to querying Bugzilla from Haskell.
--
--   A modified version of Web.Bugzilla to support
--   the list fields in Red Hat's modified bugzilla API.
--
--   A very simple program using this package might look like this:
--
-- >   let session = anonymousSession "https://bugzilla.redhat.com"
-- >       user = "me@example.org"
-- >       query = AssignedToField .==. user .&&.
-- >               FlagRequesteeField .==. user .&&.
-- >               (FlagsField `contains` "review" .||. FlagsField `contains` "feedback")
-- >   bugs <- searchBugs session query
-- >   mapM_ (putStrLn . show . bugSummary) bugs
--
--   There's a more in-depth demo program included with the
--   source code to this package.

module Web.RedHatBugzilla
( -- * Connecting to Bugzilla
  apikeySession
, anonymousSession

, BugzillaServer
, BugzillaSession (..)
, BugzillaApiKey (..)

  -- * Querying Bugzilla
, 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)
import Data.Aeson (FromJSON)
import qualified Data.Text as T

import Web.RedHatBugzilla.Internal.Network
import Web.RedHatBugzilla.Internal.Search
import Web.RedHatBugzilla.Internal.Types

-- | Creates a 'BugzillaSession' using the provided api key.
apikeySession :: BugzillaServer -> BugzillaApiKey -> BugzillaSession
apikeySession :: BugzillaServer -> BugzillaApiKey -> BugzillaSession
apikeySession = BugzillaServer -> BugzillaApiKey -> BugzillaSession
ApiKeySession

-- | Creates an anonymous 'BugzillaSession'. Note that some content
--   will be hidden by Bugzilla when you make queries in this state.
anonymousSession :: BugzillaServer -> BugzillaSession
anonymousSession :: BugzillaServer -> BugzillaSession
anonymousSession = BugzillaServer -> 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

-- | Searches Bugzilla and returns a list of 'Bug's. The 'SearchExpression'
-- can be constructed conveniently using the operators in "Web.Bugzilla.Search".
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

-- | Similar to 'searchBugs', but return _all fields.
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

-- | Like 'searchBugs', but returns a list of 'BugId's. You can
-- retrieve the 'Bug' for each 'BugId' using 'getBug'. The combination
-- of 'searchBugs'' and 'getBug' is much less efficient than
-- 'searchBugs'. 'searchBugs'' is suitable for cases where you won't need to call
-- 'getBug' most of the time - for example, polling to determine whether the
-- set of bugs returned by a query has changed.
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)
  Request -> IO a
forall a. FromJSON a => Request -> IO a
sendBzRequest Request
req

-- | Search Bugzilla and returns a limited number of results. You can
--   call this repeatedly and use 'offset' to retrieve the results of
--   a large query incrementally. Note that most Bugzillas won't
--   return all of the results for a very large query by default, but
--   you can request this by calling 'searchBugsWithLimit' with 0 for
--   the limit.
searchBugsWithLimit :: BugzillaSession
                    -> Int  -- ^ The maximum number of results to return.
                    -> Int  -- ^ The offset from the first result to start from.
                    -> 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

-- | Similar to 'searchBugsWithLimit', but return _all fields.
searchBugsAllWithLimit :: BugzillaSession
                       -> Int  -- ^ The maximum number of results to return.
                       -> Int  -- ^ The offset from the first result to start from.
                       -> 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

-- | Like 'searchBugsWithLimit', but returns a list of 'BugId's. See
-- 'searchBugs'' for more discussion.
searchBugsWithLimit' :: BugzillaSession
                     -> Int  -- ^ The maximum number of results to return.
                     -> Int  -- ^ The offset from the first result to start from.
                     -> 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

-- | Retrieve a bug by bug number.
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 []

-- | Retrieve all bug field by bug number
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"]

-- | Retrieve a bug by bug number with fields
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) <- Request -> IO BugList
forall a. FromJSON a => Request -> IO a
sendBzRequest 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

-- | Retrieve a bug by attachment number.
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) <- Request -> IO AttachmentList
forall a. FromJSON a => Request -> IO a
sendBzRequest 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"

-- | Get all attachments for a bug.
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) <- Request -> IO AttachmentList
forall a. FromJSON a => Request -> IO a
sendBzRequest Request
req
  [Attachment] -> IO [Attachment]
forall (m :: * -> *) a. Monad m => a -> m a
return [Attachment]
as

-- | Get all comments for a bug.
getComments :: BugzillaSession -> BugId -> IO [Comment]
getComments :: BugzillaSession -> Int -> IO [Comment]
getComments 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) <- Request -> IO CommentList
forall a. FromJSON a => Request -> IO a
sendBzRequest Request
req
  [Comment] -> IO [Comment]
forall (m :: * -> *) a. Monad m => a -> m a
return [Comment]
as

-- | Get the history for a bug.
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"] []
  Request -> IO History
forall a. FromJSON a => Request -> IO a
sendBzRequest Request
req

-- | Search user names and emails using a substring search.
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) <- Request -> IO UserList
forall a. FromJSON a => Request -> IO a
sendBzRequest Request
req
  [User] -> IO [User]
forall (m :: * -> *) a. Monad m => a -> m a
return [User]
users

-- | Get a user by email.
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) <- Request -> IO UserList
forall a. FromJSON a => Request -> IO a
sendBzRequest 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"

-- | Get a user by user ID.
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) <- Request -> IO UserList
forall a. FromJSON a => Request -> IO a
sendBzRequest 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"