bugzilla-redhat-0.3.1: A Haskell interface to the Bugzilla native REST API
Safe HaskellNone
LanguageHaskell2010

Web.Bugzilla.RedHat

Description

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:

  ctx <- newBugzillaContext "bugzilla.example.org"
  let session = anonymousSession ctx
      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 somewhat more in-depth demo program included with the source code to this package.

Synopsis

Connecting to Bugzilla

newBugzillaContext :: BugzillaServer -> IO BugzillaContext Source #

Creates a new BugzillaContext, suitable for connecting to the provided server. You should try to reuse BugzillaContexts whenever possible, because creating them is expensive.

loginSession :: BugzillaContext -> UserEmail -> Text -> IO (Maybe BugzillaSession) Source #

Attempts to create a logged-in BugzillaSession using the provided username and password. Returns Nothing if login fails.

anonymousSession :: BugzillaContext -> BugzillaSession Source #

Creates an anonymous BugzillaSession. Note that some content will be hidden by Bugzilla when you make queries in this state.

data BugzillaContext Source #

Holds information about a BugzillaServer and manages outgoing connections. You can use newBugzillaContext or withBugzillaContext to create one.

data BugzillaSession Source #

A session for Bugzilla queries. Use anonymousSession and loginSession, as appropriate, to create one.

Querying Bugzilla

searchBugs :: BugzillaSession -> SearchExpression -> IO [Bug] Source #

Searches Bugzilla and returns a list of Bugs. The SearchExpression can be constructed conveniently using the operators in Web.Bugzilla.Search.

searchBugs' :: BugzillaSession -> SearchExpression -> IO [BugId] Source #

Like searchBugs, but returns a list of BugIds. 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.

searchBugsWithLimit Source #

Arguments

:: BugzillaSession 
-> Int

The maximum number of results to return.

-> Int

The offset from the first result to start from.

-> SearchExpression 
-> IO [Bug] 

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' Source #

Arguments

:: BugzillaSession 
-> Int

The maximum number of results to return.

-> Int

The offset from the first result to start from.

-> SearchExpression 
-> IO [BugId] 

Like searchBugsWithLimit, but returns a list of BugIds. See searchBugs' for more discussion.

getBug :: BugzillaSession -> BugId -> IO (Maybe Bug) Source #

Retrieve a bug by bug number.

getAttachment :: BugzillaSession -> AttachmentId -> IO (Maybe Attachment) Source #

Retrieve a bug by attachment number.

getAttachments :: BugzillaSession -> BugId -> IO [Attachment] Source #

Get all attachments for a bug.

getComments :: BugzillaSession -> BugId -> IO [Comment] Source #

Get all comments for a bug.

getHistory :: BugzillaSession -> BugId -> IO History Source #

Get the history for a bug.

searchUsers :: BugzillaSession -> Text -> IO [User] Source #

Search user names and emails using a substring search.

getUser :: BugzillaSession -> UserEmail -> IO (Maybe User) Source #

Get a user by email.

getUserById :: BugzillaSession -> UserId -> IO (Maybe User) Source #

Get a user by user ID.

type BugId = Int Source #

data Field a where Source #

A field which you can search by using searchBugs or track changes to using getHistory. To get a human-readable name for a field, use fieldName.

Constructors

AliasField :: Field [Text] 
AssignedToField :: Field UserEmail 
AttachmentCreatorField :: Field UserEmail 
AttachmentDataField :: Field Text 
AttachmentDescriptionField :: Field Text 
AttachmentFilenameField :: Field Text 
AttachmentIsObsoleteField :: Field Bool 
AttachmentIsPatchField :: Field Bool 
AttachmentIsPrivateField :: Field Bool 
AttachmentMimetypeField :: Field Text 
BlocksField :: Field Int 
BugIdField :: Field Int 
CcField :: Field UserEmail 
CcListAccessibleField :: Field Bool 
ClassificationField :: Field Text 
CommentField :: Field Text 
CommentIsPrivateField :: Field Text 
CommentTagsField :: Field Text 
CommenterField :: Field UserEmail 
ComponentField :: Field [Text] 
ContentField :: Field Text 
CreationDateField :: Field UTCTime 
DaysElapsedField :: Field Int 
DependsOnField :: Field Int 
EverConfirmedField :: Field Bool 
FlagRequesteeField :: Field UserEmail 
FlagSetterField :: Field UserEmail 
FlagsField :: Field Text 
GroupField :: Field Text 
KeywordsField :: Field [Text] 
ChangedField :: Field UTCTime 
CommentCountField :: Field Int 
OperatingSystemField :: Field Text 
HardwareField :: Field Text 
PriorityField :: Field Text 
ProductField :: Field Text 
QaContactField :: Field UserEmail 
ReporterField :: Field UserEmail 
ReporterAccessibleField :: Field Bool 
ResolutionField :: Field Text 
RestrictCommentsField :: Field Bool 
SeeAlsoField :: Field Text 
SeverityField :: Field Text 
StatusField :: Field Text 
WhiteboardField :: Field Text 
SummaryField :: Field Text 
TagsField :: Field Text 
TargetMilestoneField :: Field Text 
TimeSinceAssigneeTouchedField :: Field Int 
BugURLField :: Field Text 
VersionField :: Field Text 
VotesField :: Field Text 
CustomField :: Text -> Field Text 

Instances

Instances details
Eq (Field a) Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

(==) :: Field a -> Field a -> Bool #

(/=) :: Field a -> Field a -> Bool #

Show (Field a) Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

showsPrec :: Int -> Field a -> ShowS #

show :: Field a -> String #

showList :: [Field a] -> ShowS #

data User Source #

A Bugzilla user.

Constructors

User 

Instances

Instances details
Eq User Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

(==) :: User -> User -> Bool #

(/=) :: User -> User -> Bool #

Ord User Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

compare :: User -> User -> Ordering #

(<) :: User -> User -> Bool #

(<=) :: User -> User -> Bool #

(>) :: User -> User -> Bool #

(>=) :: User -> User -> Bool #

max :: User -> User -> User #

min :: User -> User -> User #

Show User Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

FromJSON User Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

data Flag Source #

Flags, which may be set on an attachment or on a bug directly.

Instances

Instances details
Eq Flag Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

(==) :: Flag -> Flag -> Bool #

(/=) :: Flag -> Flag -> Bool #

Ord Flag Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

compare :: Flag -> Flag -> Ordering #

(<) :: Flag -> Flag -> Bool #

(<=) :: Flag -> Flag -> Bool #

(>) :: Flag -> Flag -> Bool #

(>=) :: Flag -> Flag -> Bool #

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

Show Flag Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

FromJSON Flag Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

data Comment Source #

A bug comment. To display these the way Bugzilla does, you'll need to call getUser and use the userRealName for each user.

Instances

Instances details
Eq Comment Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

(==) :: Comment -> Comment -> Bool #

(/=) :: Comment -> Comment -> Bool #

Show Comment Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

FromJSON Comment Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

data History Source #

History information for a bug.

Constructors

History 

Instances

Instances details
Eq History Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

(==) :: History -> History -> Bool #

(/=) :: History -> History -> Bool #

Show History Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

FromJSON History Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

data HistoryEvent Source #

An event in a bug's history.

Constructors

HistoryEvent 

Fields

data Change Source #

A single change which is part of an event. Different constructors are used according to the type of the field. The Modification describes the value of the field before and after the change.

Instances

Instances details
Eq Change Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

Methods

(==) :: Change -> Change -> Bool #

(/=) :: Change -> Change -> Bool #

Show Change Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

FromJSON Change Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

data (Eq a, Show a) => Modification a Source #

A description of how a field changed during a HistoryEvent.

Instances

Instances details
(Eq a, Show a) => Eq (Modification a) Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

(Eq a, Show a) => Show (Modification a) Source # 
Instance details

Defined in Web.Bugzilla.RedHat.Internal.Types

fieldName :: Field a -> Text Source #

Provides a human-readable name for a Field.