| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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) bugsThere's a somewhat more in-depth demo program included with the source code to this package.
Synopsis
- newBugzillaContext :: BugzillaServer -> IO BugzillaContext
- loginSession :: BugzillaContext -> UserEmail -> Text -> IO (Maybe BugzillaSession)
- anonymousSession :: BugzillaContext -> BugzillaSession
- type BugzillaServer = Text
- data BugzillaContext
- data BugzillaSession
- newtype BugzillaToken = BugzillaToken Text
- searchBugs :: BugzillaSession -> SearchExpression -> IO [Bug]
- searchBugs' :: BugzillaSession -> SearchExpression -> IO [BugId]
- searchBugsWithLimit :: BugzillaSession -> Int -> Int -> SearchExpression -> IO [Bug]
- searchBugsWithLimit' :: BugzillaSession -> Int -> Int -> SearchExpression -> IO [BugId]
- getBug :: BugzillaSession -> BugId -> IO (Maybe Bug)
- getAttachment :: BugzillaSession -> AttachmentId -> IO (Maybe Attachment)
- getAttachments :: BugzillaSession -> BugId -> IO [Attachment]
- getComments :: BugzillaSession -> BugId -> IO [Comment]
- getHistory :: BugzillaSession -> BugId -> IO History
- searchUsers :: BugzillaSession -> Text -> IO [User]
- getUser :: BugzillaSession -> UserEmail -> IO (Maybe User)
- getUserById :: BugzillaSession -> UserId -> IO (Maybe User)
- newBzRequest :: BugzillaSession -> [Text] -> QueryText -> Request
- sendBzRequest :: FromJSON a => BugzillaSession -> Request -> IO a
- intAsText :: Int -> Text
- type BugId = Int
- type AttachmentId = Int
- type CommentId = Int
- type UserId = Int
- type EventId = Int
- type FlagId = Int
- type FlagType = Int
- type UserEmail = Text
- data Field a where
- 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
- data User = User {}
- data Flag = Flag {}
- data Bug = Bug {
- bugId :: !BugId
- bugAlias :: Maybe [Text]
- bugAssignedTo :: UserEmail
- bugAssignedToDetail :: User
- bugBlocks :: [BugId]
- bugCc :: [UserEmail]
- bugCcDetail :: [User]
- bugClassification :: Text
- bugComponent :: [Text]
- bugCreationTime :: UTCTime
- bugCreator :: UserEmail
- bugCreatorDetail :: User
- bugDependsOn :: [BugId]
- bugDupeOf :: Maybe BugId
- bugFlags :: Maybe [Flag]
- bugGroups :: [Text]
- bugIsCcAccessible :: Bool
- bugIsConfirmed :: Bool
- bugIsCreatorAccessible :: Bool
- bugIsOpen :: Bool
- bugKeywords :: [Text]
- bugLastChangeTime :: UTCTime
- bugOpSys :: Text
- bugPlatform :: Text
- bugPriority :: Text
- bugProduct :: Text
- bugQaContact :: UserEmail
- bugResolution :: Text
- bugSeeAlso :: [Text]
- bugSeverity :: Text
- bugStatus :: Text
- bugSummary :: Text
- bugTargetMilestone :: Text
- bugUrl :: Text
- bugVersion :: [Text]
- bugWhiteboard :: Text
- bugCustomFields :: HashMap Text Text
- data Attachment = Attachment {
- attachmentId :: !AttachmentId
- attachmentBugId :: !BugId
- attachmentFileName :: Text
- attachmentSummary :: Text
- attachmentCreator :: UserEmail
- attachmentIsPrivate :: Bool
- attachmentIsObsolete :: Bool
- attachmentIsPatch :: Bool
- attachmentFlags :: [Flag]
- attachmentCreationTime :: UTCTime
- attachmentLastChangeTime :: UTCTime
- attachmentContentType :: Text
- attachmentSize :: !Int
- attachmentData :: Text
- data Comment = Comment {}
- data History = History {
- historyBugId :: !BugId
- historyEvents :: [HistoryEvent]
- data HistoryEvent = HistoryEvent {}
- data Change
- = TextFieldChange (Field Text) (Modification Text)
- | ListFieldChange (Field [Text]) (Modification [Text])
- | IntFieldChange (Field Int) (Modification Int)
- | TimeFieldChange (Field UTCTime) (Modification UTCTime)
- | BoolFieldChange (Field Bool) (Modification Bool)
- data (Eq a, Show a) => Modification a = Modification {
- modRemoved :: Maybe a
- modAdded :: Maybe a
- modAttachmentId :: Maybe AttachmentId
- fieldName :: Field a -> Text
- data BugzillaException
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.
type BugzillaServer = Text Source #
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.
newtype BugzillaToken Source #
Constructors
| BugzillaToken Text |
Instances
| FromJSON BugzillaToken Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Network Methods parseJSON :: Value -> Parser BugzillaToken # parseJSONList :: Value -> Parser [BugzillaToken] # | |
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.
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.
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.
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.
getUserById :: BugzillaSession -> UserId -> IO (Maybe User) Source #
Get a user by user ID.
newBzRequest :: BugzillaSession -> [Text] -> QueryText -> Request Source #
sendBzRequest :: FromJSON a => BugzillaSession -> Request -> IO a Source #
type AttachmentId = Int 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
A Bugzilla user.
Constructors
| User | |
Flags, which may be set on an attachment or on a bug directly.
Constructors
| Flag | |
Fields
| |
A Bugzilla bug.
Constructors
| Bug | |
Fields
| |
data Attachment Source #
An attachment to a bug.
Constructors
Instances
| Eq Attachment Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Types | |
| Show Attachment Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Types Methods showsPrec :: Int -> Attachment -> ShowS # show :: Attachment -> String # showList :: [Attachment] -> ShowS # | |
| FromJSON Attachment Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Types | |
A bug comment. To display these the way Bugzilla does, you'll
need to call getUser and use the userRealName for each user.
Constructors
| Comment | |
Fields
| |
History information for a bug.
Constructors
| History | |
Fields
| |
data HistoryEvent Source #
An event in a bug's history.
Constructors
| HistoryEvent | |
Fields
| |
Instances
| Eq HistoryEvent Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Types | |
| Show HistoryEvent Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Types Methods showsPrec :: Int -> HistoryEvent -> ShowS # show :: HistoryEvent -> String # showList :: [HistoryEvent] -> ShowS # | |
| FromJSON HistoryEvent Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Types | |
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.
Constructors
data (Eq a, Show a) => Modification a Source #
A description of how a field changed during a HistoryEvent.
Constructors
| Modification | |
Fields
| |
Instances
| (Eq a, Show a) => Eq (Modification a) Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Types Methods (==) :: Modification a -> Modification a -> Bool # (/=) :: Modification a -> Modification a -> Bool # | |
| (Eq a, Show a) => Show (Modification a) Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Types Methods showsPrec :: Int -> Modification a -> ShowS # show :: Modification a -> String # showList :: [Modification a] -> ShowS # | |
data BugzillaException Source #
Constructors
| BugzillaJSONParseError String | |
| BugzillaAPIError Int String | |
| BugzillaUnexpectedValue String |
Instances
| Show BugzillaException Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Network Methods showsPrec :: Int -> BugzillaException -> ShowS # show :: BugzillaException -> String # showList :: [BugzillaException] -> ShowS # | |
| Exception BugzillaException Source # | |
Defined in Web.Bugzilla.RedHat.Internal.Network Methods toException :: BugzillaException -> SomeException # | |