Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 "https://bugzilla.redhat.com" 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
- apikeySession :: BugzillaServer -> BugzillaApiKey -> BugzillaSession
- anonymousSession :: BugzillaServer -> BugzillaSession
- type BugzillaServer = Text
- data BugzillaSession
- newtype BugzillaApiKey = BugzillaApiKey Text
- searchBugs :: BugzillaSession -> SearchExpression -> IO [Bug]
- searchBugsAll :: BugzillaSession -> SearchExpression -> IO [Bug]
- searchBugs' :: BugzillaSession -> SearchExpression -> IO [BugId]
- searchBugsWithLimit :: BugzillaSession -> Int -> Int -> SearchExpression -> IO [Bug]
- searchBugsAllWithLimit :: BugzillaSession -> Int -> Int -> SearchExpression -> IO [Bug]
- searchBugsWithLimit' :: BugzillaSession -> Int -> Int -> SearchExpression -> IO [BugId]
- getBug :: BugzillaSession -> BugId -> IO (Maybe Bug)
- getBugAll :: 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 => Request -> IO a
- intAsText :: Int -> Text
- data Request
- 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 {
- flagId :: !FlagId
- flagTypeId :: !FlagType
- flagName :: Text
- flagSetter :: UserEmail
- flagStatus :: Text
- flagCreationDate :: UTCTime
- flagModificationDate :: UTCTime
- flagRequestee :: Maybe UserEmail
- 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
- bugExternalBugs :: Maybe [ExternalBug]
- data ExternalBug = ExternalBug {
- externalDescription :: Text
- externalBzId :: Int
- externalPriority :: Text
- externalBugId :: Text
- externalStatus :: Text
- externalId :: Int
- externalType :: ExternalType
- data ExternalType = ExternalType {
- externalTypeDescription :: Text
- externalTypeUrl :: Text
- externalTypeId :: Int
- externalTypeType :: Text
- externalTypeFullUrl :: 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 {
- commentId :: !CommentId
- commentBugId :: !BugId
- commentAttachmentId :: Maybe AttachmentId
- commentCount :: !Int
- commentText :: Text
- commentCreator :: UserEmail
- commentCreationTime :: UTCTime
- commentIsPrivate :: Bool
- data History = History {
- historyBugId :: !BugId
- historyEvents :: [HistoryEvent]
- data HistoryEvent = HistoryEvent {
- historyEventId :: EventId
- historyEventTime :: UTCTime
- historyEventUser :: UserEmail
- historyEventChanges :: [Change]
- 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
- = BugzillaJSONParseError String
- | BugzillaAPIError Int String
- | BugzillaUnexpectedValue String
Connecting to Bugzilla
apikeySession :: BugzillaServer -> BugzillaApiKey -> BugzillaSession Source #
Creates a BugzillaSession
using the provided api key.
anonymousSession :: BugzillaServer -> 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 BugzillaSession Source #
A session for Bugzilla queries. Use anonymousSession
and
loginSession
, as appropriate, to create one.
newtype BugzillaApiKey Source #
BugzillaApiKey Text |
Querying Bugzilla
searchBugs :: BugzillaSession -> SearchExpression -> IO [Bug] Source #
Searches Bugzilla and returns a list of Bug
s. The SearchExpression
can be constructed conveniently using the operators in Web.Bugzilla.Search.
searchBugsAll :: BugzillaSession -> SearchExpression -> IO [Bug] Source #
Similar to searchBugs
, but return _all fields.
searchBugs' :: BugzillaSession -> SearchExpression -> IO [BugId] Source #
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.
:: 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.
searchBugsAllWithLimit Source #
:: BugzillaSession | |
-> Int | The maximum number of results to return. |
-> Int | The offset from the first result to start from. |
-> SearchExpression | |
-> IO [Bug] |
Similar to searchBugsWithLimit
, but return _all fields.
:: 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 BugId
s. See
searchBugs'
for more discussion.
getBugAll :: BugzillaSession -> BugId -> IO (Maybe Bug) Source #
Retrieve all bug field 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.
getUserById :: BugzillaSession -> UserId -> IO (Maybe User) Source #
Get a user by user ID.
newBzRequest :: BugzillaSession -> [Text] -> QueryText -> Request Source #
sendBzRequest :: FromJSON a => 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
.
Instances
A Bugzilla user.
Flags, which may be set on an attachment or on a bug directly.
Flag | |
|
A Bugzilla bug.
Bug | |
|
data ExternalBug Source #
An external bug.
ExternalBug | |
|
Instances
Eq ExternalBug Source # | |
Defined in Web.RedHatBugzilla.Internal.Types (==) :: ExternalBug -> ExternalBug -> Bool (/=) :: ExternalBug -> ExternalBug -> Bool | |
Ord ExternalBug Source # | |
Defined in Web.RedHatBugzilla.Internal.Types compare :: ExternalBug -> ExternalBug -> Ordering (<) :: ExternalBug -> ExternalBug -> Bool (<=) :: ExternalBug -> ExternalBug -> Bool (>) :: ExternalBug -> ExternalBug -> Bool (>=) :: ExternalBug -> ExternalBug -> Bool max :: ExternalBug -> ExternalBug -> ExternalBug min :: ExternalBug -> ExternalBug -> ExternalBug | |
Show ExternalBug Source # | |
Defined in Web.RedHatBugzilla.Internal.Types showsPrec :: Int -> ExternalBug -> ShowS show :: ExternalBug -> String showList :: [ExternalBug] -> ShowS | |
FromJSON ExternalBug Source # | |
Defined in Web.RedHatBugzilla.Internal.Types parseJSON :: Value -> Parser ExternalBug parseJSONList :: Value -> Parser [ExternalBug] |
data ExternalType Source #
An external bug type
ExternalType | |
|
Instances
Eq ExternalType Source # | |
Defined in Web.RedHatBugzilla.Internal.Types (==) :: ExternalType -> ExternalType -> Bool (/=) :: ExternalType -> ExternalType -> Bool | |
Ord ExternalType Source # | |
Defined in Web.RedHatBugzilla.Internal.Types compare :: ExternalType -> ExternalType -> Ordering (<) :: ExternalType -> ExternalType -> Bool (<=) :: ExternalType -> ExternalType -> Bool (>) :: ExternalType -> ExternalType -> Bool (>=) :: ExternalType -> ExternalType -> Bool max :: ExternalType -> ExternalType -> ExternalType min :: ExternalType -> ExternalType -> ExternalType | |
Show ExternalType Source # | |
Defined in Web.RedHatBugzilla.Internal.Types showsPrec :: Int -> ExternalType -> ShowS show :: ExternalType -> String showList :: [ExternalType] -> ShowS | |
FromJSON ExternalType Source # | |
Defined in Web.RedHatBugzilla.Internal.Types parseJSON :: Value -> Parser ExternalType parseJSONList :: Value -> Parser [ExternalType] |
data Attachment Source #
An attachment to a bug.
Attachment | |
|
Instances
Eq Attachment Source # | |
Defined in Web.RedHatBugzilla.Internal.Types (==) :: Attachment -> Attachment -> Bool (/=) :: Attachment -> Attachment -> Bool | |
Show Attachment Source # | |
Defined in Web.RedHatBugzilla.Internal.Types showsPrec :: Int -> Attachment -> ShowS show :: Attachment -> String showList :: [Attachment] -> ShowS | |
FromJSON Attachment Source # | |
Defined in Web.RedHatBugzilla.Internal.Types parseJSON :: Value -> Parser Attachment parseJSONList :: Value -> Parser [Attachment] |
A bug comment. To display these the way Bugzilla does, you'll
need to call getUser
and use the userRealName
for each user.
Comment | |
|
History information for a bug.
History | |
|
data HistoryEvent Source #
An event in a bug's history.
HistoryEvent | |
|
Instances
Eq HistoryEvent Source # | |
Defined in Web.RedHatBugzilla.Internal.Types (==) :: HistoryEvent -> HistoryEvent -> Bool (/=) :: HistoryEvent -> HistoryEvent -> Bool | |
Show HistoryEvent Source # | |
Defined in Web.RedHatBugzilla.Internal.Types showsPrec :: Int -> HistoryEvent -> ShowS show :: HistoryEvent -> String showList :: [HistoryEvent] -> ShowS | |
FromJSON HistoryEvent Source # | |
Defined in Web.RedHatBugzilla.Internal.Types parseJSON :: Value -> Parser HistoryEvent parseJSONList :: Value -> Parser [HistoryEvent] |
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.
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 Source #
A description of how a field changed during a HistoryEvent
.
Modification | |
|
Instances
(Eq a, Show a) => Eq (Modification a) Source # | |
Defined in Web.RedHatBugzilla.Internal.Types (==) :: Modification a -> Modification a -> Bool (/=) :: Modification a -> Modification a -> Bool | |
(Eq a, Show a) => Show (Modification a) Source # | |
Defined in Web.RedHatBugzilla.Internal.Types showsPrec :: Int -> Modification a -> ShowS show :: Modification a -> String showList :: [Modification a] -> ShowS |
data BugzillaException Source #
BugzillaJSONParseError String | |
BugzillaAPIError Int String | |
BugzillaUnexpectedValue String |
Instances
Show BugzillaException Source # | |
Defined in Web.RedHatBugzilla.Internal.Network showsPrec :: Int -> BugzillaException -> ShowS show :: BugzillaException -> String showList :: [BugzillaException] -> ShowS | |
Exception BugzillaException Source # | |
Defined in Web.RedHatBugzilla.Internal.Network toException :: BugzillaException -> SomeException fromException :: SomeException -> Maybe BugzillaException displayException :: BugzillaException -> String |