{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Web.RedHatBugzilla.Internal.Types
( BugId
, AttachmentId
, CommentId
, UserId
, EventId
, FlagId
, FlagType
, UserEmail
, Field (..)
, User (..)
, UserList (..)
, Flag (..)
, ExternalType (..)
, ExternalBug (..)
, Bug (..)
, BugList (..)
, BugIdList (..)
, Attachment (..)
, AttachmentList (..)
, Comment (..)
, CommentList (..)
, History (..)
, HistoryEvent (..)
, Change (..)
, Modification (..)
, fieldName
, searchFieldName
) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative (pure, (<$>), (<*>))
#endif
import Control.Monad (mzero)
import Data.Aeson
#if MIN_VERSION_aeson(1,0,0)
import Data.Aeson.Text
#else
import Data.Aeson.Encode
#endif
import Data.Aeson.Types
#if MIN_VERSION_aeson(2,0,0)
import Data.Aeson.Key
import qualified Data.Aeson.KeyMap as M
#else
import qualified Data.HashMap.Strict as M
#endif
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TLB
import qualified Data.Text.Read as TR
import qualified Data.Vector as V
import Data.Time.Clock (UTCTime(..))
type BugId = Int
type AttachmentId = Int
type = Int
type UserId = Int
type EventId = Int
type FlagId = Int
type FlagType = Int
type UserEmail = T.Text
data Field a where
AliasField :: Field [T.Text]
AssignedToField :: Field UserEmail
AttachmentCreatorField :: Field UserEmail
AttachmentDataField :: Field T.Text
AttachmentDescriptionField :: Field T.Text
AttachmentFilenameField :: Field T.Text
AttachmentIsObsoleteField :: Field Bool
AttachmentIsPatchField :: Field Bool
AttachmentIsPrivateField :: Field Bool
AttachmentMimetypeField :: Field T.Text
BlocksField :: Field Int
BugIdField :: Field Int
CcField :: Field UserEmail
CcListAccessibleField :: Field Bool
ClassificationField :: Field T.Text
:: Field T.Text
:: Field T.Text
:: Field T.Text
:: Field UserEmail
ComponentField :: Field [T.Text]
ContentField :: Field T.Text
CreationDateField :: Field UTCTime
DaysElapsedField :: Field Int
DependsOnField :: Field Int
EverConfirmedField :: Field Bool
FlagRequesteeField :: Field UserEmail
FlagSetterField :: Field UserEmail
FlagsField :: Field T.Text
GroupField :: Field T.Text
KeywordsField :: Field [T.Text]
ChangedField :: Field UTCTime
:: Field Int
OperatingSystemField :: Field T.Text
HardwareField :: Field T.Text
PriorityField :: Field T.Text
ProductField :: Field T.Text
QaContactField :: Field UserEmail
ReporterField :: Field UserEmail
ReporterAccessibleField :: Field Bool
ResolutionField :: Field T.Text
:: Field Bool
SeeAlsoField :: Field T.Text
SeverityField :: Field T.Text
StatusField :: Field T.Text
WhiteboardField :: Field T.Text
SummaryField :: Field T.Text
TagsField :: Field T.Text
TargetMilestoneField :: Field T.Text
TimeSinceAssigneeTouchedField :: Field Int
BugURLField :: Field T.Text
VersionField :: Field T.Text
VotesField :: Field T.Text
CustomField :: T.Text -> Field T.Text
instance Eq (Field a) where
(CustomField Text
a) == :: Field a -> Field a -> Bool
== (CustomField Text
b) = Text
a Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
b
(CustomField Text
_) == Field a
_ = Bool
False
Field a
_ == (CustomField Text
_) = Bool
False
Field a
a == Field a
b = Field a -> Text
forall a. Field a -> Text
searchFieldName Field a
a Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Field a -> Text
forall a. Field a -> Text
searchFieldName Field a
b
instance Show (Field a) where
show :: Field a -> String
show Field a
AliasField = String
"AliasField"
show Field a
AssignedToField = String
"AssignedToField"
show Field a
AttachmentCreatorField = String
"AttachmentCreatorField"
show Field a
AttachmentDataField = String
"AttachmentDataField"
show Field a
AttachmentDescriptionField = String
"AttachmentDescriptionField"
show Field a
AttachmentFilenameField = String
"AttachmentFilenameField"
show Field a
AttachmentIsObsoleteField = String
"AttachmentIsObsoleteField"
show Field a
AttachmentIsPatchField = String
"AttachmentIsPatchField"
show Field a
AttachmentIsPrivateField = String
"AttachmentIsPrivateField"
show Field a
AttachmentMimetypeField = String
"AttachmentMimetypeField"
show Field a
BlocksField = String
"BlocksField"
show Field a
BugIdField = String
"BugIdField"
show Field a
CcField = String
"CcField"
show Field a
CcListAccessibleField = String
"CcListAccessibleField"
show Field a
ClassificationField = String
"ClassificationField"
show Field a
CommentField = String
"CommentField"
show Field a
CommentIsPrivateField = String
"CommentIsPrivateField"
show Field a
CommentTagsField = String
"CommentTagsField"
show Field a
CommenterField = String
"CommenterField"
show Field a
ComponentField = String
"ComponentField"
show Field a
ContentField = String
"ContentField"
show Field a
CreationDateField = String
"CreationDateField"
show Field a
DaysElapsedField = String
"DaysElapsedField"
show Field a
DependsOnField = String
"DependsOnField"
show Field a
EverConfirmedField = String
"EverConfirmedField"
show Field a
FlagRequesteeField = String
"FlagRequesteeField"
show Field a
FlagSetterField = String
"FlagSetterField"
show Field a
FlagsField = String
"FlagsField"
show Field a
GroupField = String
"GroupField"
show Field a
KeywordsField = String
"KeywordsField"
show Field a
ChangedField = String
"ChangedField"
show Field a
CommentCountField = String
"CommentCountField"
show Field a
OperatingSystemField = String
"OperatingSystemField"
show Field a
HardwareField = String
"HardwareField"
show Field a
PriorityField = String
"PriorityField"
show Field a
ProductField = String
"ProductField"
show Field a
QaContactField = String
"QaContactField"
show Field a
ReporterField = String
"ReporterField"
show Field a
ReporterAccessibleField = String
"ReporterAccessibleField"
show Field a
ResolutionField = String
"ResolutionField"
show Field a
RestrictCommentsField = String
"RestrictCommentsField"
show Field a
SeeAlsoField = String
"SeeAlsoField"
show Field a
SeverityField = String
"SeverityField"
show Field a
StatusField = String
"StatusField"
show Field a
WhiteboardField = String
"WhiteboardField"
show Field a
SummaryField = String
"SummaryField"
show Field a
TagsField = String
"TagsField"
show Field a
TargetMilestoneField = String
"TargetMilestoneField"
show Field a
TimeSinceAssigneeTouchedField = String
"TimeSinceAssigneeTouchedField"
show Field a
BugURLField = String
"BugURLField"
show Field a
VersionField = String
"VersionField"
show Field a
VotesField = String
"VotesField"
show (CustomField Text
name) = String
"CustomField " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
name
fieldName :: Field a -> T.Text
fieldName :: Field a -> Text
fieldName Field a
AliasField = Text
"Alias"
fieldName Field a
AssignedToField = Text
"Assigned to"
fieldName Field a
AttachmentCreatorField = Text
"Attachment creator"
fieldName Field a
AttachmentDataField = Text
"Attachment data"
fieldName Field a
AttachmentDescriptionField = Text
"Attachment description"
fieldName Field a
AttachmentFilenameField = Text
"Attachment filename"
fieldName Field a
AttachmentIsObsoleteField = Text
"Attachment is obsolete"
fieldName Field a
AttachmentIsPatchField = Text
"Attachment is patch"
fieldName Field a
AttachmentIsPrivateField = Text
"Attachment is private"
fieldName Field a
AttachmentMimetypeField = Text
"Attachment MIME type"
fieldName Field a
BlocksField = Text
"Blocks"
fieldName Field a
BugIdField = Text
"BugId"
fieldName Field a
CcField = Text
"CC"
fieldName Field a
CcListAccessibleField = Text
"CC list is accessible"
fieldName Field a
ClassificationField = Text
"Classification"
fieldName Field a
CommentField = Text
"Comment"
fieldName Field a
CommentIsPrivateField = Text
"Comment is private"
fieldName Field a
CommentTagsField = Text
"Comment tags"
fieldName Field a
CommenterField = Text
"Commenter"
fieldName Field a
ComponentField = Text
"Component"
fieldName Field a
ContentField = Text
"Content"
fieldName Field a
CreationDateField = Text
"Creation date"
fieldName Field a
DaysElapsedField = Text
"Days elapsed"
fieldName Field a
DependsOnField = Text
"Depends on"
fieldName Field a
EverConfirmedField = Text
"Ever confirmed"
fieldName Field a
FlagRequesteeField = Text
"Flag requestee"
fieldName Field a
FlagSetterField = Text
"Flag setter"
fieldName Field a
FlagsField = Text
"Flags"
fieldName Field a
GroupField = Text
"Group"
fieldName Field a
KeywordsField = Text
"Keywords"
fieldName Field a
ChangedField = Text
"Changed"
fieldName Field a
CommentCountField = Text
"Comment count"
fieldName Field a
OperatingSystemField = Text
"Operating system"
fieldName Field a
HardwareField = Text
"Hardware"
fieldName Field a
PriorityField = Text
"Priority"
fieldName Field a
ProductField = Text
"Product"
fieldName Field a
QaContactField = Text
"QA contact"
fieldName Field a
ReporterField = Text
"Reporter"
fieldName Field a
ReporterAccessibleField = Text
"Reporter accessible"
fieldName Field a
ResolutionField = Text
"Resolution"
fieldName Field a
RestrictCommentsField = Text
"Restrict comments"
fieldName Field a
SeeAlsoField = Text
"See also"
fieldName Field a
SeverityField = Text
"Severity"
fieldName Field a
StatusField = Text
"Status"
fieldName Field a
WhiteboardField = Text
"Whiteboard"
fieldName Field a
SummaryField = Text
"Summary"
fieldName Field a
TagsField = Text
"Tags"
fieldName Field a
TargetMilestoneField = Text
"Target milestone"
fieldName Field a
TimeSinceAssigneeTouchedField = Text
"Time since assignee touched"
fieldName Field a
BugURLField = Text
"Bug URL"
fieldName Field a
VersionField = Text
"Version"
fieldName Field a
VotesField = Text
"Votes"
fieldName (CustomField Text
name) = [Text] -> Text
T.concat [Text
"Custom field \"", String -> Text
T.pack (Text -> String
forall a. Show a => a -> String
show Text
name), Text
"\""]
searchFieldName :: Field a -> T.Text
searchFieldName :: Field a -> Text
searchFieldName Field a
AliasField = Text
"alias"
searchFieldName Field a
AssignedToField = Text
"assigned_to"
searchFieldName Field a
AttachmentCreatorField = Text
"attachments.submitter"
searchFieldName Field a
AttachmentDataField = Text
"attach_data.thedata"
searchFieldName Field a
AttachmentDescriptionField = Text
"attachments.description"
searchFieldName Field a
AttachmentFilenameField = Text
"attachments.filename"
searchFieldName Field a
AttachmentIsObsoleteField = Text
"attachments.isobsolete"
searchFieldName Field a
AttachmentIsPatchField = Text
"attachments.ispatch"
searchFieldName Field a
AttachmentIsPrivateField = Text
"attachments.isprivate"
searchFieldName Field a
AttachmentMimetypeField = Text
"attachments.mimetype"
searchFieldName Field a
BlocksField = Text
"blocked"
searchFieldName Field a
BugIdField = Text
"bug_id"
searchFieldName Field a
CcField = Text
"cc"
searchFieldName Field a
CcListAccessibleField = Text
"cclist_accessible"
searchFieldName Field a
ClassificationField = Text
"classification"
searchFieldName Field a
CommentField = Text
"longdesc"
searchFieldName Field a
CommentIsPrivateField = Text
"longdescs.isprivate"
searchFieldName Field a
CommentTagsField = Text
"comment_tag"
searchFieldName Field a
CommenterField = Text
"commenter"
searchFieldName Field a
ComponentField = Text
"component"
searchFieldName Field a
ContentField = Text
"content"
searchFieldName Field a
CreationDateField = Text
"creation_ts"
searchFieldName Field a
DaysElapsedField = Text
"days_elapsed"
searchFieldName Field a
DependsOnField = Text
"dependson"
searchFieldName Field a
EverConfirmedField = Text
"everconfirmed"
searchFieldName Field a
FlagRequesteeField = Text
"requestees.login_name"
searchFieldName Field a
FlagSetterField = Text
"setters.login_name"
searchFieldName Field a
FlagsField = Text
"flagtypes.name"
searchFieldName Field a
GroupField = Text
"bug_group"
searchFieldName Field a
KeywordsField = Text
"keywords"
searchFieldName Field a
ChangedField = Text
"delta_ts"
searchFieldName Field a
CommentCountField = Text
"longdescs.count"
searchFieldName Field a
OperatingSystemField = Text
"op_sys"
searchFieldName Field a
HardwareField = Text
"rep_platform"
searchFieldName Field a
PriorityField = Text
"priority"
searchFieldName Field a
ProductField = Text
"product"
searchFieldName Field a
QaContactField = Text
"qa_contact"
searchFieldName Field a
ReporterField = Text
"reporter"
searchFieldName Field a
ReporterAccessibleField = Text
"reporter_accessible"
searchFieldName Field a
ResolutionField = Text
"resolution"
searchFieldName Field a
RestrictCommentsField = Text
"restrict_comments"
searchFieldName Field a
SeeAlsoField = Text
"see_also"
searchFieldName Field a
SeverityField = Text
"bug_severity"
searchFieldName Field a
StatusField = Text
"bug_status"
searchFieldName Field a
WhiteboardField = Text
"status_whiteboard"
searchFieldName Field a
SummaryField = Text
"short_desc"
searchFieldName Field a
TagsField = Text
"tag"
searchFieldName Field a
TargetMilestoneField = Text
"target_milestone"
searchFieldName Field a
TimeSinceAssigneeTouchedField = Text
"owner_idle_time"
searchFieldName Field a
BugURLField = Text
"bug_file_loc"
searchFieldName Field a
VersionField = Text
"version"
searchFieldName Field a
VotesField = Text
"votes"
searchFieldName (CustomField Text
name) = Text
name
data User = User
{ User -> Int
userId :: !UserId
, User -> Maybe Text
userEmail :: Maybe UserEmail
, User -> Text
userName :: T.Text
, User -> Text
userRealName :: T.Text
} deriving (User -> User -> Bool
(User -> User -> Bool) -> (User -> User -> Bool) -> Eq User
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: User -> User -> Bool
$c/= :: User -> User -> Bool
== :: User -> User -> Bool
$c== :: User -> User -> Bool
Eq, Eq User
Eq User
-> (User -> User -> Ordering)
-> (User -> User -> Bool)
-> (User -> User -> Bool)
-> (User -> User -> Bool)
-> (User -> User -> Bool)
-> (User -> User -> User)
-> (User -> User -> User)
-> Ord User
User -> User -> Bool
User -> User -> Ordering
User -> User -> User
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: User -> User -> User
$cmin :: User -> User -> User
max :: User -> User -> User
$cmax :: User -> User -> User
>= :: User -> User -> Bool
$c>= :: User -> User -> Bool
> :: User -> User -> Bool
$c> :: User -> User -> Bool
<= :: User -> User -> Bool
$c<= :: User -> User -> Bool
< :: User -> User -> Bool
$c< :: User -> User -> Bool
compare :: User -> User -> Ordering
$ccompare :: User -> User -> Ordering
$cp1Ord :: Eq User
Ord, Int -> User -> ShowS
[User] -> ShowS
User -> String
(Int -> User -> ShowS)
-> (User -> String) -> ([User] -> ShowS) -> Show User
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [User] -> ShowS
$cshowList :: [User] -> ShowS
show :: User -> String
$cshow :: User -> String
showsPrec :: Int -> User -> ShowS
$cshowsPrec :: Int -> User -> ShowS
Show)
instance FromJSON User where
parseJSON :: Value -> Parser User
parseJSON (Object Object
v) =
Int -> Maybe Text -> Text -> Text -> User
User (Int -> Maybe Text -> Text -> Text -> User)
-> Parser Int -> Parser (Maybe Text -> Text -> Text -> User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Parser (Maybe Text -> Text -> Text -> User)
-> Parser (Maybe Text) -> Parser (Text -> Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"email"
Parser (Text -> Text -> User)
-> Parser Text -> Parser (Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"name"
Parser (Text -> User) -> Parser Text -> Parser User
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"real_name"
parseJSON Value
_ = Parser User
forall (m :: * -> *) a. MonadPlus m => m a
mzero
newtype UserList = UserList [User]
deriving (UserList -> UserList -> Bool
(UserList -> UserList -> Bool)
-> (UserList -> UserList -> Bool) -> Eq UserList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserList -> UserList -> Bool
$c/= :: UserList -> UserList -> Bool
== :: UserList -> UserList -> Bool
$c== :: UserList -> UserList -> Bool
Eq, Int -> UserList -> ShowS
[UserList] -> ShowS
UserList -> String
(Int -> UserList -> ShowS)
-> (UserList -> String) -> ([UserList] -> ShowS) -> Show UserList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserList] -> ShowS
$cshowList :: [UserList] -> ShowS
show :: UserList -> String
$cshow :: UserList -> String
showsPrec :: Int -> UserList -> ShowS
$cshowsPrec :: Int -> UserList -> ShowS
Show)
instance FromJSON UserList where
parseJSON :: Value -> Parser UserList
parseJSON (Object Object
v) = [User] -> UserList
UserList ([User] -> UserList) -> Parser [User] -> Parser UserList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser [User]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"users"
parseJSON Value
_ = Parser UserList
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data Flag = Flag
{ Flag -> Int
flagId :: !FlagId
, Flag -> Int
flagTypeId :: !FlagType
, Flag -> Text
flagName :: T.Text
, Flag -> Text
flagSetter :: UserEmail
, Flag -> Text
flagStatus :: T.Text
, Flag -> UTCTime
flagCreationDate :: UTCTime
, Flag -> UTCTime
flagModificationDate :: UTCTime
, Flag -> Maybe Text
flagRequestee :: Maybe UserEmail
} deriving (Flag -> Flag -> Bool
(Flag -> Flag -> Bool) -> (Flag -> Flag -> Bool) -> Eq Flag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Flag -> Flag -> Bool
$c/= :: Flag -> Flag -> Bool
== :: Flag -> Flag -> Bool
$c== :: Flag -> Flag -> Bool
Eq, Eq Flag
Eq Flag
-> (Flag -> Flag -> Ordering)
-> (Flag -> Flag -> Bool)
-> (Flag -> Flag -> Bool)
-> (Flag -> Flag -> Bool)
-> (Flag -> Flag -> Bool)
-> (Flag -> Flag -> Flag)
-> (Flag -> Flag -> Flag)
-> Ord Flag
Flag -> Flag -> Bool
Flag -> Flag -> Ordering
Flag -> Flag -> Flag
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Flag -> Flag -> Flag
$cmin :: Flag -> Flag -> Flag
max :: Flag -> Flag -> Flag
$cmax :: Flag -> Flag -> Flag
>= :: Flag -> Flag -> Bool
$c>= :: Flag -> Flag -> Bool
> :: Flag -> Flag -> Bool
$c> :: Flag -> Flag -> Bool
<= :: Flag -> Flag -> Bool
$c<= :: Flag -> Flag -> Bool
< :: Flag -> Flag -> Bool
$c< :: Flag -> Flag -> Bool
compare :: Flag -> Flag -> Ordering
$ccompare :: Flag -> Flag -> Ordering
$cp1Ord :: Eq Flag
Ord, Int -> Flag -> ShowS
[Flag] -> ShowS
Flag -> String
(Int -> Flag -> ShowS)
-> (Flag -> String) -> ([Flag] -> ShowS) -> Show Flag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Flag] -> ShowS
$cshowList :: [Flag] -> ShowS
show :: Flag -> String
$cshow :: Flag -> String
showsPrec :: Int -> Flag -> ShowS
$cshowsPrec :: Int -> Flag -> ShowS
Show)
instance FromJSON Flag where
parseJSON :: Value -> Parser Flag
parseJSON (Object Object
v) =
Int
-> Int
-> Text
-> Text
-> Text
-> UTCTime
-> UTCTime
-> Maybe Text
-> Flag
Flag (Int
-> Int
-> Text
-> Text
-> Text
-> UTCTime
-> UTCTime
-> Maybe Text
-> Flag)
-> Parser Int
-> Parser
(Int
-> Text
-> Text
-> Text
-> UTCTime
-> UTCTime
-> Maybe Text
-> Flag)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Parser
(Int
-> Text
-> Text
-> Text
-> UTCTime
-> UTCTime
-> Maybe Text
-> Flag)
-> Parser Int
-> Parser
(Text -> Text -> Text -> UTCTime -> UTCTime -> Maybe Text -> Flag)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"type_id"
Parser
(Text -> Text -> Text -> UTCTime -> UTCTime -> Maybe Text -> Flag)
-> Parser Text
-> Parser
(Text -> Text -> UTCTime -> UTCTime -> Maybe Text -> Flag)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"name"
Parser (Text -> Text -> UTCTime -> UTCTime -> Maybe Text -> Flag)
-> Parser Text
-> Parser (Text -> UTCTime -> UTCTime -> Maybe Text -> Flag)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"setter"
Parser (Text -> UTCTime -> UTCTime -> Maybe Text -> Flag)
-> Parser Text -> Parser (UTCTime -> UTCTime -> Maybe Text -> Flag)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"status"
Parser (UTCTime -> UTCTime -> Maybe Text -> Flag)
-> Parser UTCTime -> Parser (UTCTime -> Maybe Text -> Flag)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser UTCTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"creation_date"
Parser (UTCTime -> Maybe Text -> Flag)
-> Parser UTCTime -> Parser (Maybe Text -> Flag)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser UTCTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"modification_date"
Parser (Maybe Text -> Flag) -> Parser (Maybe Text) -> Parser Flag
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"requestee"
parseJSON Value
_ = Parser Flag
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data ExternalType = ExternalType
{ ExternalType -> Text
externalTypeDescription :: T.Text
, ExternalType -> Text
externalTypeUrl :: T.Text
, ExternalType -> Int
externalTypeId :: Int
, ExternalType -> Text
externalTypeType :: T.Text
, ExternalType -> Text
externalTypeFullUrl :: T.Text
} deriving (ExternalType -> ExternalType -> Bool
(ExternalType -> ExternalType -> Bool)
-> (ExternalType -> ExternalType -> Bool) -> Eq ExternalType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExternalType -> ExternalType -> Bool
$c/= :: ExternalType -> ExternalType -> Bool
== :: ExternalType -> ExternalType -> Bool
$c== :: ExternalType -> ExternalType -> Bool
Eq, Eq ExternalType
Eq ExternalType
-> (ExternalType -> ExternalType -> Ordering)
-> (ExternalType -> ExternalType -> Bool)
-> (ExternalType -> ExternalType -> Bool)
-> (ExternalType -> ExternalType -> Bool)
-> (ExternalType -> ExternalType -> Bool)
-> (ExternalType -> ExternalType -> ExternalType)
-> (ExternalType -> ExternalType -> ExternalType)
-> Ord ExternalType
ExternalType -> ExternalType -> Bool
ExternalType -> ExternalType -> Ordering
ExternalType -> ExternalType -> ExternalType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExternalType -> ExternalType -> ExternalType
$cmin :: ExternalType -> ExternalType -> ExternalType
max :: ExternalType -> ExternalType -> ExternalType
$cmax :: ExternalType -> ExternalType -> ExternalType
>= :: ExternalType -> ExternalType -> Bool
$c>= :: ExternalType -> ExternalType -> Bool
> :: ExternalType -> ExternalType -> Bool
$c> :: ExternalType -> ExternalType -> Bool
<= :: ExternalType -> ExternalType -> Bool
$c<= :: ExternalType -> ExternalType -> Bool
< :: ExternalType -> ExternalType -> Bool
$c< :: ExternalType -> ExternalType -> Bool
compare :: ExternalType -> ExternalType -> Ordering
$ccompare :: ExternalType -> ExternalType -> Ordering
$cp1Ord :: Eq ExternalType
Ord, Int -> ExternalType -> ShowS
[ExternalType] -> ShowS
ExternalType -> String
(Int -> ExternalType -> ShowS)
-> (ExternalType -> String)
-> ([ExternalType] -> ShowS)
-> Show ExternalType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExternalType] -> ShowS
$cshowList :: [ExternalType] -> ShowS
show :: ExternalType -> String
$cshow :: ExternalType -> String
showsPrec :: Int -> ExternalType -> ShowS
$cshowsPrec :: Int -> ExternalType -> ShowS
Show)
instance FromJSON ExternalType where
parseJSON :: Value -> Parser ExternalType
parseJSON (Object Object
v) =
Text -> Text -> Int -> Text -> Text -> ExternalType
ExternalType (Text -> Text -> Int -> Text -> Text -> ExternalType)
-> Parser Text
-> Parser (Text -> Int -> Text -> Text -> ExternalType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"description"
Parser (Text -> Int -> Text -> Text -> ExternalType)
-> Parser Text -> Parser (Int -> Text -> Text -> ExternalType)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"url"
Parser (Int -> Text -> Text -> ExternalType)
-> Parser Int -> Parser (Text -> Text -> ExternalType)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Parser (Text -> Text -> ExternalType)
-> Parser Text -> Parser (Text -> ExternalType)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"type"
Parser (Text -> ExternalType) -> Parser Text -> Parser ExternalType
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"full_url"
parseJSON Value
_ = Parser ExternalType
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data ExternalBug = ExternalBug
{ ExternalBug -> Text
externalDescription :: T.Text
, ExternalBug -> Int
externalBzId :: Int
, ExternalBug -> Text
externalPriority :: T.Text
, ExternalBug -> Text
externalBugId :: T.Text
, ExternalBug -> Text
externalStatus :: T.Text
, ExternalBug -> Int
externalId :: Int
, ExternalBug -> ExternalType
externalType :: ExternalType
} deriving (ExternalBug -> ExternalBug -> Bool
(ExternalBug -> ExternalBug -> Bool)
-> (ExternalBug -> ExternalBug -> Bool) -> Eq ExternalBug
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExternalBug -> ExternalBug -> Bool
$c/= :: ExternalBug -> ExternalBug -> Bool
== :: ExternalBug -> ExternalBug -> Bool
$c== :: ExternalBug -> ExternalBug -> Bool
Eq, Eq ExternalBug
Eq ExternalBug
-> (ExternalBug -> ExternalBug -> Ordering)
-> (ExternalBug -> ExternalBug -> Bool)
-> (ExternalBug -> ExternalBug -> Bool)
-> (ExternalBug -> ExternalBug -> Bool)
-> (ExternalBug -> ExternalBug -> Bool)
-> (ExternalBug -> ExternalBug -> ExternalBug)
-> (ExternalBug -> ExternalBug -> ExternalBug)
-> Ord ExternalBug
ExternalBug -> ExternalBug -> Bool
ExternalBug -> ExternalBug -> Ordering
ExternalBug -> ExternalBug -> ExternalBug
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExternalBug -> ExternalBug -> ExternalBug
$cmin :: ExternalBug -> ExternalBug -> ExternalBug
max :: ExternalBug -> ExternalBug -> ExternalBug
$cmax :: ExternalBug -> ExternalBug -> ExternalBug
>= :: ExternalBug -> ExternalBug -> Bool
$c>= :: ExternalBug -> ExternalBug -> Bool
> :: ExternalBug -> ExternalBug -> Bool
$c> :: ExternalBug -> ExternalBug -> Bool
<= :: ExternalBug -> ExternalBug -> Bool
$c<= :: ExternalBug -> ExternalBug -> Bool
< :: ExternalBug -> ExternalBug -> Bool
$c< :: ExternalBug -> ExternalBug -> Bool
compare :: ExternalBug -> ExternalBug -> Ordering
$ccompare :: ExternalBug -> ExternalBug -> Ordering
$cp1Ord :: Eq ExternalBug
Ord, Int -> ExternalBug -> ShowS
[ExternalBug] -> ShowS
ExternalBug -> String
(Int -> ExternalBug -> ShowS)
-> (ExternalBug -> String)
-> ([ExternalBug] -> ShowS)
-> Show ExternalBug
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExternalBug] -> ShowS
$cshowList :: [ExternalBug] -> ShowS
show :: ExternalBug -> String
$cshow :: ExternalBug -> String
showsPrec :: Int -> ExternalBug -> ShowS
$cshowsPrec :: Int -> ExternalBug -> ShowS
Show)
instance FromJSON ExternalBug where
parseJSON :: Value -> Parser ExternalBug
parseJSON (Object Object
v) =
Text
-> Int
-> Text
-> Text
-> Text
-> Int
-> ExternalType
-> ExternalBug
ExternalBug (Text
-> Int
-> Text
-> Text
-> Text
-> Int
-> ExternalType
-> ExternalBug)
-> Parser Text
-> Parser
(Int -> Text -> Text -> Text -> Int -> ExternalType -> ExternalBug)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ext_description"
Parser
(Int -> Text -> Text -> Text -> Int -> ExternalType -> ExternalBug)
-> Parser Int
-> Parser
(Text -> Text -> Text -> Int -> ExternalType -> ExternalBug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ext_bz_id"
Parser (Text -> Text -> Text -> Int -> ExternalType -> ExternalBug)
-> Parser Text
-> Parser (Text -> Text -> Int -> ExternalType -> ExternalBug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ext_priority"
Parser (Text -> Text -> Int -> ExternalType -> ExternalBug)
-> Parser Text
-> Parser (Text -> Int -> ExternalType -> ExternalBug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ext_bz_bug_id"
Parser (Text -> Int -> ExternalType -> ExternalBug)
-> Parser Text -> Parser (Int -> ExternalType -> ExternalBug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"ext_status"
Parser (Int -> ExternalType -> ExternalBug)
-> Parser Int -> Parser (ExternalType -> ExternalBug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Parser (ExternalType -> ExternalBug)
-> Parser ExternalType -> Parser ExternalBug
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser ExternalType
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"type"
parseJSON Value
_ = Parser ExternalBug
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data Bug = Bug
{ Bug -> Int
bugId :: !BugId
, Bug -> Maybe [Text]
bugAlias :: Maybe [T.Text]
, Bug -> Text
bugAssignedTo :: UserEmail
, Bug -> User
bugAssignedToDetail :: User
, Bug -> [Int]
bugBlocks :: [BugId]
, Bug -> [Text]
bugCc :: [UserEmail]
, Bug -> [User]
bugCcDetail :: [User]
, Bug -> Text
bugClassification :: T.Text
, Bug -> [Text]
bugComponent :: [T.Text]
, Bug -> UTCTime
bugCreationTime :: UTCTime
, Bug -> Text
bugCreator :: UserEmail
, Bug -> User
bugCreatorDetail :: User
, Bug -> [Int]
bugDependsOn :: [BugId]
, Bug -> Maybe Int
bugDupeOf :: Maybe BugId
, Bug -> Maybe [Flag]
bugFlags :: Maybe [Flag]
, Bug -> [Text]
bugGroups :: [T.Text]
, Bug -> Bool
bugIsCcAccessible :: Bool
, Bug -> Bool
bugIsConfirmed :: Bool
, Bug -> Bool
bugIsCreatorAccessible :: Bool
, Bug -> Bool
bugIsOpen :: Bool
, Bug -> [Text]
bugKeywords :: [T.Text]
, Bug -> UTCTime
bugLastChangeTime :: UTCTime
, Bug -> Text
bugOpSys :: T.Text
, Bug -> Text
bugPlatform :: T.Text
, Bug -> Text
bugPriority :: T.Text
, Bug -> Text
bugProduct :: T.Text
, Bug -> Text
bugQaContact :: UserEmail
, Bug -> Text
bugResolution :: T.Text
, Bug -> Text
bugSeverity :: T.Text
, Bug -> Text
bugStatus :: T.Text
, Bug -> Text
bugSummary :: T.Text
, Bug -> Text
bugTargetMilestone :: T.Text
, Bug -> Text
bugUrl :: T.Text
, Bug -> [Text]
bugVersion :: [T.Text]
, Bug -> Text
bugWhiteboard :: T.Text
, Bug -> HashMap Text Text
bugCustomFields ::
#if MIN_VERSION_aeson(2,0,0)
M.KeyMap T.Text
#else
M.HashMap T.Text T.Text
#endif
, Bug -> Maybe [ExternalBug]
bugExternalBugs :: Maybe [ExternalBug]
} deriving (Bug -> Bug -> Bool
(Bug -> Bug -> Bool) -> (Bug -> Bug -> Bool) -> Eq Bug
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bug -> Bug -> Bool
$c/= :: Bug -> Bug -> Bool
== :: Bug -> Bug -> Bool
$c== :: Bug -> Bug -> Bool
Eq, Int -> Bug -> ShowS
[Bug] -> ShowS
Bug -> String
(Int -> Bug -> ShowS)
-> (Bug -> String) -> ([Bug] -> ShowS) -> Show Bug
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bug] -> ShowS
$cshowList :: [Bug] -> ShowS
show :: Bug -> String
$cshow :: Bug -> String
showsPrec :: Int -> Bug -> ShowS
$cshowsPrec :: Int -> Bug -> ShowS
Show)
instance FromJSON Bug where
parseJSON :: Value -> Parser Bug
parseJSON (Object Object
v) =
Int
-> Maybe [Text]
-> Text
-> User
-> [Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug
Bug (Int
-> Maybe [Text]
-> Text
-> User
-> [Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Int
-> Parser
(Maybe [Text]
-> Text
-> User
-> [Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Parser
(Maybe [Text]
-> Text
-> User
-> [Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser (Maybe [Text])
-> Parser
(Text
-> User
-> [Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"alias"
Parser
(Text
-> User
-> [Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(User
-> [Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"assigned_to"
Parser
(User
-> [Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser User
-> Parser
([Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser User
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"assigned_to_detail"
Parser
([Int]
-> [Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser [Int]
-> Parser
([Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Int]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"blocks"
Parser
([Text]
-> [User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser [Text]
-> Parser
([User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"cc"
Parser
([User]
-> Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser [User]
-> Parser
(Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [User]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"cc_detail"
Parser
(Text
-> [Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
([Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"classification"
Parser
([Text]
-> UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser [Text]
-> Parser
(UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"component"
Parser
(UTCTime
-> Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser UTCTime
-> Parser
(Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser UTCTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"creation_time"
Parser
(Text
-> User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"creator"
Parser
(User
-> [Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser User
-> Parser
([Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser User
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"creator_detail"
Parser
([Int]
-> Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser [Int]
-> Parser
(Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Int]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"depends_on"
Parser
(Maybe Int
-> Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser (Maybe Int)
-> Parser
(Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"dupe_of"
Parser
(Maybe [Flag]
-> [Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser (Maybe [Flag])
-> Parser
([Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe [Flag])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"flags"
Parser
([Text]
-> Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser [Text]
-> Parser
(Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"groups"
Parser
(Bool
-> Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Bool
-> Parser
(Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_cc_accessible"
Parser
(Bool
-> Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Bool
-> Parser
(Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_confirmed"
Parser
(Bool
-> Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Bool
-> Parser
(Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_creator_accessible"
Parser
(Bool
-> [Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Bool
-> Parser
([Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_open"
Parser
([Text]
-> UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser [Text]
-> Parser
(UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"keywords"
Parser
(UTCTime
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser UTCTime
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser UTCTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"last_change_time"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"op_sys"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"platform"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"priority"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"product"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"qa_contact"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"resolution"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"severity"
Parser
(Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"status"
Parser
(Text
-> Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"summary"
Parser
(Text
-> Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
(Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"target_milestone"
Parser
(Text
-> [Text]
-> Text
-> HashMap Text Text
-> Maybe [ExternalBug]
-> Bug)
-> Parser Text
-> Parser
([Text] -> Text -> HashMap Text Text -> Maybe [ExternalBug] -> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"url"
Parser
([Text] -> Text -> HashMap Text Text -> Maybe [ExternalBug] -> Bug)
-> Parser [Text]
-> Parser (Text -> HashMap Text Text -> Maybe [ExternalBug] -> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"version"
Parser (Text -> HashMap Text Text -> Maybe [ExternalBug] -> Bug)
-> Parser Text
-> Parser (HashMap Text Text -> Maybe [ExternalBug] -> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"whiteboard"
Parser (HashMap Text Text -> Maybe [ExternalBug] -> Bug)
-> Parser (HashMap Text Text)
-> Parser (Maybe [ExternalBug] -> Bug)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> HashMap Text Text -> Parser (HashMap Text Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Object -> HashMap Text Text
customFields Object
v)
Parser (Maybe [ExternalBug] -> Bug)
-> Parser (Maybe [ExternalBug]) -> Parser Bug
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe [ExternalBug])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"external_bugs"
parseJSON Value
_ = Parser Bug
forall (m :: * -> *) a. MonadPlus m => m a
mzero
customFields :: Object ->
#if MIN_VERSION_aeson(2,0,0)
M.KeyMap T.Text
#else
M.HashMap T.Text T.Text
#endif
customFields :: Object -> HashMap Text Text
customFields = (Value -> Text) -> Object -> HashMap Text Text
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
M.map Value -> Text
stringifyCustomFields
(Object -> HashMap Text Text)
-> (Object -> Object) -> Object -> HashMap Text Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Value -> Bool) -> Object -> Object
forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v
M.filterWithKey Text -> Value -> Bool
forall p. Text -> p -> Bool
filterCustomFields
where
stringifyCustomFields :: Value -> T.Text
stringifyCustomFields :: Value -> Text
stringifyCustomFields (String Text
t) = Text
t
stringifyCustomFields Value
v = [Text] -> Text
T.concat
([Text] -> Text) -> (Value -> [Text]) -> Value -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
TL.toChunks
(Text -> [Text]) -> (Value -> Text) -> Value -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
TLB.toLazyText
(Builder -> Text) -> (Value -> Builder) -> Value -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Builder
forall a. ToJSON a => a -> Builder
encodeToTextBuilder
(Value -> Builder) -> (Value -> Value) -> Value -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Value
forall a. ToJSON a => a -> Value
toJSON
(Value -> Text) -> Value -> Text
forall a b. (a -> b) -> a -> b
$ Value
v
filterCustomFields :: Text -> p -> Bool
filterCustomFields Text
k p
_ = Text
"cf_" Text -> Text -> Bool
`T.isPrefixOf` Text -> Text
forall a. a -> a
toText Text
k
#if !MIN_VERSION_aeson(2,0,0)
where toText :: a -> a
toText = a -> a
forall a. a -> a
id
#endif
newtype BugList = BugList [Bug]
deriving (BugList -> BugList -> Bool
(BugList -> BugList -> Bool)
-> (BugList -> BugList -> Bool) -> Eq BugList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BugList -> BugList -> Bool
$c/= :: BugList -> BugList -> Bool
== :: BugList -> BugList -> Bool
$c== :: BugList -> BugList -> Bool
Eq, Int -> BugList -> ShowS
[BugList] -> ShowS
BugList -> String
(Int -> BugList -> ShowS)
-> (BugList -> String) -> ([BugList] -> ShowS) -> Show BugList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BugList] -> ShowS
$cshowList :: [BugList] -> ShowS
show :: BugList -> String
$cshow :: BugList -> String
showsPrec :: Int -> BugList -> ShowS
$cshowsPrec :: Int -> BugList -> ShowS
Show)
instance FromJSON BugList where
parseJSON :: Value -> Parser BugList
parseJSON (Object Object
v) = [Bug] -> BugList
BugList ([Bug] -> BugList) -> Parser [Bug] -> Parser BugList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser [Bug]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"bugs"
parseJSON Value
_ = Parser BugList
forall (m :: * -> *) a. MonadPlus m => m a
mzero
newtype BugIdList = BugIdList [BugId]
deriving (BugIdList -> BugIdList -> Bool
(BugIdList -> BugIdList -> Bool)
-> (BugIdList -> BugIdList -> Bool) -> Eq BugIdList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BugIdList -> BugIdList -> Bool
$c/= :: BugIdList -> BugIdList -> Bool
== :: BugIdList -> BugIdList -> Bool
$c== :: BugIdList -> BugIdList -> Bool
Eq, Int -> BugIdList -> ShowS
[BugIdList] -> ShowS
BugIdList -> String
(Int -> BugIdList -> ShowS)
-> (BugIdList -> String)
-> ([BugIdList] -> ShowS)
-> Show BugIdList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BugIdList] -> ShowS
$cshowList :: [BugIdList] -> ShowS
show :: BugIdList -> String
$cshow :: BugIdList -> String
showsPrec :: Int -> BugIdList -> ShowS
$cshowsPrec :: Int -> BugIdList -> ShowS
Show)
instance FromJSON BugIdList where
parseJSON :: Value -> Parser BugIdList
parseJSON (Object Object
v) = do
[Object]
bugs <- Object
v Object -> Text -> Parser [Object]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"bugs"
[Int]
bugIds <- (Object -> Parser Int) -> [Object] -> Parser [Int]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id") [Object]
bugs
BugIdList -> Parser BugIdList
forall (m :: * -> *) a. Monad m => a -> m a
return (BugIdList -> Parser BugIdList) -> BugIdList -> Parser BugIdList
forall a b. (a -> b) -> a -> b
$ [Int] -> BugIdList
BugIdList [Int]
bugIds
parseJSON Value
_ = Parser BugIdList
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data Attachment = Attachment
{ Attachment -> Int
attachmentId :: !AttachmentId
, Attachment -> Int
attachmentBugId :: !BugId
, Attachment -> Text
attachmentFileName :: T.Text
, Attachment -> Text
attachmentSummary :: T.Text
, Attachment -> Text
attachmentCreator :: UserEmail
, Attachment -> Bool
attachmentIsPrivate :: Bool
, Attachment -> Bool
attachmentIsObsolete :: Bool
, Attachment -> Bool
attachmentIsPatch :: Bool
, Attachment -> [Flag]
attachmentFlags :: [Flag]
, Attachment -> UTCTime
attachmentCreationTime :: UTCTime
, Attachment -> UTCTime
attachmentLastChangeTime :: UTCTime
, Attachment -> Text
attachmentContentType :: T.Text
, Attachment -> Int
attachmentSize :: !Int
, Attachment -> Text
attachmentData :: T.Text
} deriving (Attachment -> Attachment -> Bool
(Attachment -> Attachment -> Bool)
-> (Attachment -> Attachment -> Bool) -> Eq Attachment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Attachment -> Attachment -> Bool
$c/= :: Attachment -> Attachment -> Bool
== :: Attachment -> Attachment -> Bool
$c== :: Attachment -> Attachment -> Bool
Eq, Int -> Attachment -> ShowS
[Attachment] -> ShowS
Attachment -> String
(Int -> Attachment -> ShowS)
-> (Attachment -> String)
-> ([Attachment] -> ShowS)
-> Show Attachment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Attachment] -> ShowS
$cshowList :: [Attachment] -> ShowS
show :: Attachment -> String
$cshow :: Attachment -> String
showsPrec :: Int -> Attachment -> ShowS
$cshowsPrec :: Int -> Attachment -> ShowS
Show)
instance FromJSON Attachment where
parseJSON :: Value -> Parser Attachment
parseJSON (Object Object
v) =
Int
-> Int
-> Text
-> Text
-> Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment
Attachment (Int
-> Int
-> Text
-> Text
-> Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
-> Parser Int
-> Parser
(Int
-> Text
-> Text
-> Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Parser
(Int
-> Text
-> Text
-> Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
-> Parser Int
-> Parser
(Text
-> Text
-> Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"bug_id"
Parser
(Text
-> Text
-> Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
-> Parser Text
-> Parser
(Text
-> Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"file_name"
Parser
(Text
-> Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
-> Parser Text
-> Parser
(Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"summary"
Parser
(Text
-> Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
-> Parser Text
-> Parser
(Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"creator"
Parser
(Bool
-> Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
-> Parser Bool
-> Parser
(Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Int -> Bool
fromNumericBool (Int -> Bool) -> Parser Int -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_private")
Parser
(Bool
-> Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
-> Parser Bool
-> Parser
(Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Int -> Bool
fromNumericBool (Int -> Bool) -> Parser Int -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_obsolete")
Parser
(Bool
-> [Flag]
-> UTCTime
-> UTCTime
-> Text
-> Int
-> Text
-> Attachment)
-> Parser Bool
-> Parser
([Flag] -> UTCTime -> UTCTime -> Text -> Int -> Text -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Int -> Bool
fromNumericBool (Int -> Bool) -> Parser Int -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_patch")
Parser
([Flag] -> UTCTime -> UTCTime -> Text -> Int -> Text -> Attachment)
-> Parser [Flag]
-> Parser (UTCTime -> UTCTime -> Text -> Int -> Text -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Flag]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"flags"
Parser (UTCTime -> UTCTime -> Text -> Int -> Text -> Attachment)
-> Parser UTCTime
-> Parser (UTCTime -> Text -> Int -> Text -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser UTCTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"creation_time"
Parser (UTCTime -> Text -> Int -> Text -> Attachment)
-> Parser UTCTime -> Parser (Text -> Int -> Text -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser UTCTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"last_change_time"
Parser (Text -> Int -> Text -> Attachment)
-> Parser Text -> Parser (Int -> Text -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"content_type"
Parser (Int -> Text -> Attachment)
-> Parser Int -> Parser (Text -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"size"
Parser (Text -> Attachment) -> Parser Text -> Parser Attachment
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"data"
parseJSON Value
_ = Parser Attachment
forall (m :: * -> *) a. MonadPlus m => m a
mzero
fromNumericBool :: Int -> Bool
fromNumericBool :: Int -> Bool
fromNumericBool Int
0 = Bool
False
fromNumericBool Int
_ = Bool
True
newtype AttachmentList = AttachmentList [Attachment]
deriving (AttachmentList -> AttachmentList -> Bool
(AttachmentList -> AttachmentList -> Bool)
-> (AttachmentList -> AttachmentList -> Bool) -> Eq AttachmentList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachmentList -> AttachmentList -> Bool
$c/= :: AttachmentList -> AttachmentList -> Bool
== :: AttachmentList -> AttachmentList -> Bool
$c== :: AttachmentList -> AttachmentList -> Bool
Eq, Int -> AttachmentList -> ShowS
[AttachmentList] -> ShowS
AttachmentList -> String
(Int -> AttachmentList -> ShowS)
-> (AttachmentList -> String)
-> ([AttachmentList] -> ShowS)
-> Show AttachmentList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachmentList] -> ShowS
$cshowList :: [AttachmentList] -> ShowS
show :: AttachmentList -> String
$cshow :: AttachmentList -> String
showsPrec :: Int -> AttachmentList -> ShowS
$cshowsPrec :: Int -> AttachmentList -> ShowS
Show)
instance FromJSON AttachmentList where
parseJSON :: Value -> Parser AttachmentList
parseJSON (Object Object
v) = do
Value
attachmentsVal <- Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"attachments"
Value
bugsVal <- Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"bugs"
case (Value
attachmentsVal, Value
bugsVal) of
(Object (Object -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
M.toList -> [(Text
_, Value
as)]), Value
_) -> [Attachment] -> AttachmentList
AttachmentList ([Attachment] -> AttachmentList)
-> (Attachment -> [Attachment]) -> Attachment -> AttachmentList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Attachment -> [Attachment] -> [Attachment]
forall a. a -> [a] -> [a]
:[]) (Attachment -> AttachmentList)
-> Parser Attachment -> Parser AttachmentList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Attachment
forall a. FromJSON a => Value -> Parser a
parseJSON Value
as
(Value
_, Object (Object -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
M.toList -> [(Text
_, Value
as)])) -> [Attachment] -> AttachmentList
AttachmentList ([Attachment] -> AttachmentList)
-> Parser [Attachment] -> Parser AttachmentList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [Attachment]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
as
(Value, Value)
_ -> Parser AttachmentList
forall (m :: * -> *) a. MonadPlus m => m a
mzero
parseJSON Value
_ = Parser AttachmentList
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data =
{ :: !CommentId
, :: !BugId
, :: Maybe AttachmentId
, :: !Int
, :: T.Text
, :: UserEmail
, :: UTCTime
, :: Bool
} deriving (Comment -> Comment -> Bool
(Comment -> Comment -> Bool)
-> (Comment -> Comment -> Bool) -> Eq Comment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Comment -> Comment -> Bool
$c/= :: Comment -> Comment -> Bool
== :: Comment -> Comment -> Bool
$c== :: Comment -> Comment -> Bool
Eq, Int -> Comment -> ShowS
[Comment] -> ShowS
Comment -> String
(Int -> Comment -> ShowS)
-> (Comment -> String) -> ([Comment] -> ShowS) -> Show Comment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Comment] -> ShowS
$cshowList :: [Comment] -> ShowS
show :: Comment -> String
$cshow :: Comment -> String
showsPrec :: Int -> Comment -> ShowS
$cshowsPrec :: Int -> Comment -> ShowS
Show)
instance FromJSON Comment where
parseJSON :: Value -> Parser Comment
parseJSON (Object Object
v) =
Int
-> Int
-> Maybe Int
-> Int
-> Text
-> Text
-> UTCTime
-> Bool
-> Comment
Comment (Int
-> Int
-> Maybe Int
-> Int
-> Text
-> Text
-> UTCTime
-> Bool
-> Comment)
-> Parser Int
-> Parser
(Int
-> Maybe Int -> Int -> Text -> Text -> UTCTime -> Bool -> Comment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Parser
(Int
-> Maybe Int -> Int -> Text -> Text -> UTCTime -> Bool -> Comment)
-> Parser Int
-> Parser
(Maybe Int -> Int -> Text -> Text -> UTCTime -> Bool -> Comment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"bug_id"
Parser
(Maybe Int -> Int -> Text -> Text -> UTCTime -> Bool -> Comment)
-> Parser (Maybe Int)
-> Parser (Int -> Text -> Text -> UTCTime -> Bool -> Comment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"attachment_id"
Parser (Int -> Text -> Text -> UTCTime -> Bool -> Comment)
-> Parser Int
-> Parser (Text -> Text -> UTCTime -> Bool -> Comment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"count"
Parser (Text -> Text -> UTCTime -> Bool -> Comment)
-> Parser Text -> Parser (Text -> UTCTime -> Bool -> Comment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"text"
Parser (Text -> UTCTime -> Bool -> Comment)
-> Parser Text -> Parser (UTCTime -> Bool -> Comment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"creator"
Parser (UTCTime -> Bool -> Comment)
-> Parser UTCTime -> Parser (Bool -> Comment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser UTCTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"creation_time"
Parser (Bool -> Comment) -> Parser Bool -> Parser Comment
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_private"
parseJSON Value
_ = Parser Comment
forall (m :: * -> *) a. MonadPlus m => m a
mzero
newtype = [Comment]
deriving (CommentList -> CommentList -> Bool
(CommentList -> CommentList -> Bool)
-> (CommentList -> CommentList -> Bool) -> Eq CommentList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommentList -> CommentList -> Bool
$c/= :: CommentList -> CommentList -> Bool
== :: CommentList -> CommentList -> Bool
$c== :: CommentList -> CommentList -> Bool
Eq, Int -> CommentList -> ShowS
[CommentList] -> ShowS
CommentList -> String
(Int -> CommentList -> ShowS)
-> (CommentList -> String)
-> ([CommentList] -> ShowS)
-> Show CommentList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommentList] -> ShowS
$cshowList :: [CommentList] -> ShowS
show :: CommentList -> String
$cshow :: CommentList -> String
showsPrec :: Int -> CommentList -> ShowS
$cshowsPrec :: Int -> CommentList -> ShowS
Show)
instance FromJSON CommentList where
parseJSON :: Value -> Parser CommentList
parseJSON (Object Object
v) = do
Value
bugsVal <- Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"bugs"
case Value
bugsVal of
Object (Object -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
M.toList -> [(Text
_, Value
cs)]) ->
do Value
comments <- String -> (Object -> Parser Value) -> Value -> Parser Value
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"comments" (Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"comments") Value
cs
String
-> (Array -> Parser CommentList) -> Value -> Parser CommentList
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray String
"comment list" (\Array
a -> [Comment] -> CommentList
CommentList ([Comment] -> CommentList)
-> Parser [Comment] -> Parser CommentList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [Comment]
forall a. FromJSON a => Value -> Parser a
parseJSON (Array -> Value
addCount Array
a)) Value
comments
Value
_ -> Parser CommentList
forall (m :: * -> *) a. MonadPlus m => m a
mzero
parseJSON Value
_ = Parser CommentList
forall (m :: * -> *) a. MonadPlus m => m a
mzero
addCount :: V.Vector Value -> Value
addCount :: Array -> Value
addCount Array
vs = Array -> Value
Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ (Int -> Value -> Value) -> Vector Int -> Array -> Array
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith Int -> Value -> Value
addCount' (Int -> Int -> Vector Int
forall a. Num a => a -> Int -> Vector a
V.enumFromN Int
0 (Int -> Vector Int) -> Int -> Vector Int
forall a b. (a -> b) -> a -> b
$ Array -> Int
forall a. Vector a -> Int
V.length Array
vs) Array
vs
where
addCount' :: Int -> Value -> Value
addCount' :: Int -> Value -> Value
addCount' Int
c (Object Object
v) = Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Value -> Object -> Object
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
M.insert Text
"count" (Scientific -> Value
Number (Scientific -> Value) -> Scientific -> Value
forall a b. (a -> b) -> a -> b
$ Int -> Scientific
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
c) Object
v
addCount' Int
_ Value
v = Value
v
data History = History
{ History -> Int
historyBugId :: !BugId
, History -> [HistoryEvent]
historyEvents :: [HistoryEvent]
} deriving (History -> History -> Bool
(History -> History -> Bool)
-> (History -> History -> Bool) -> Eq History
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: History -> History -> Bool
$c/= :: History -> History -> Bool
== :: History -> History -> Bool
$c== :: History -> History -> Bool
Eq, Int -> History -> ShowS
[History] -> ShowS
History -> String
(Int -> History -> ShowS)
-> (History -> String) -> ([History] -> ShowS) -> Show History
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [History] -> ShowS
$cshowList :: [History] -> ShowS
show :: History -> String
$cshow :: History -> String
showsPrec :: Int -> History -> ShowS
$cshowsPrec :: Int -> History -> ShowS
Show)
instance FromJSON History where
parseJSON :: Value -> Parser History
parseJSON (Object Object
v) = do
Value
bugsVal <- Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"bugs"
case Value
bugsVal of
Array (Array -> [Value]
forall a. Vector a -> [a]
V.toList -> [Value
history]) ->
String -> (Object -> Parser History) -> Value -> Parser History
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"history"
(\Object
h -> Int -> [HistoryEvent] -> History
History (Int -> [HistoryEvent] -> History)
-> Parser Int -> Parser ([HistoryEvent] -> History)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
h Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Parser ([HistoryEvent] -> History)
-> Parser [HistoryEvent] -> Parser History
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object -> Parser [HistoryEvent]
parseHistoryEvents Object
h)
Value
history
Value
_ -> Parser History
forall (m :: * -> *) a. MonadPlus m => m a
mzero
parseJSON Value
_ = Parser History
forall (m :: * -> *) a. MonadPlus m => m a
mzero
parseHistoryEvents :: Object -> Parser [HistoryEvent]
parseHistoryEvents :: Object -> Parser [HistoryEvent]
parseHistoryEvents Object
h = do
Value
events <- Object
h Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"history"
String
-> (Array -> Parser [HistoryEvent])
-> Value
-> Parser [HistoryEvent]
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray String
"event list" (Value -> Parser [HistoryEvent]
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser [HistoryEvent])
-> (Array -> Value) -> Array -> Parser [HistoryEvent]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> Value
addCount) Value
events
data HistoryEvent = HistoryEvent
{ HistoryEvent -> Int
historyEventId :: EventId
, HistoryEvent -> UTCTime
historyEventTime :: UTCTime
, HistoryEvent -> Text
historyEventUser :: UserEmail
, HistoryEvent -> [Change]
historyEventChanges :: [Change]
} deriving (HistoryEvent -> HistoryEvent -> Bool
(HistoryEvent -> HistoryEvent -> Bool)
-> (HistoryEvent -> HistoryEvent -> Bool) -> Eq HistoryEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HistoryEvent -> HistoryEvent -> Bool
$c/= :: HistoryEvent -> HistoryEvent -> Bool
== :: HistoryEvent -> HistoryEvent -> Bool
$c== :: HistoryEvent -> HistoryEvent -> Bool
Eq, Int -> HistoryEvent -> ShowS
[HistoryEvent] -> ShowS
HistoryEvent -> String
(Int -> HistoryEvent -> ShowS)
-> (HistoryEvent -> String)
-> ([HistoryEvent] -> ShowS)
-> Show HistoryEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HistoryEvent] -> ShowS
$cshowList :: [HistoryEvent] -> ShowS
show :: HistoryEvent -> String
$cshow :: HistoryEvent -> String
showsPrec :: Int -> HistoryEvent -> ShowS
$cshowsPrec :: Int -> HistoryEvent -> ShowS
Show)
instance FromJSON HistoryEvent where
parseJSON :: Value -> Parser HistoryEvent
parseJSON (Object Object
v) =
Int -> UTCTime -> Text -> [Change] -> HistoryEvent
HistoryEvent (Int -> UTCTime -> Text -> [Change] -> HistoryEvent)
-> Parser Int
-> Parser (UTCTime -> Text -> [Change] -> HistoryEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"count"
Parser (UTCTime -> Text -> [Change] -> HistoryEvent)
-> Parser UTCTime -> Parser (Text -> [Change] -> HistoryEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser UTCTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"when"
Parser (Text -> [Change] -> HistoryEvent)
-> Parser Text -> Parser ([Change] -> HistoryEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"who"
Parser ([Change] -> HistoryEvent)
-> Parser [Change] -> Parser HistoryEvent
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Change]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"changes"
parseJSON Value
_ = Parser HistoryEvent
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data Change
= TextFieldChange (Field T.Text) (Modification T.Text)
| ListFieldChange (Field [T.Text]) (Modification [T.Text])
| IntFieldChange (Field Int) (Modification Int)
| TimeFieldChange (Field UTCTime) (Modification UTCTime)
| BoolFieldChange (Field Bool) (Modification Bool)
deriving (Change -> Change -> Bool
(Change -> Change -> Bool)
-> (Change -> Change -> Bool) -> Eq Change
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Change -> Change -> Bool
$c/= :: Change -> Change -> Bool
== :: Change -> Change -> Bool
$c== :: Change -> Change -> Bool
Eq, Int -> Change -> ShowS
[Change] -> ShowS
Change -> String
(Int -> Change -> ShowS)
-> (Change -> String) -> ([Change] -> ShowS) -> Show Change
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Change] -> ShowS
$cshowList :: [Change] -> ShowS
show :: Change -> String
$cshow :: Change -> String
showsPrec :: Int -> Change -> ShowS
$cshowsPrec :: Int -> Change -> ShowS
Show)
instance FromJSON Change where
parseJSON :: Value -> Parser Change
parseJSON (Object Object
v) = do
Text
changedField <- Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"field_name"
case Text
changedField of
Text
"alias" -> Field [Text] -> Modification [Text] -> Change
ListFieldChange Field [Text]
AliasField (Modification [Text] -> Change)
-> Parser (Modification [Text]) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification [Text])
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"assigned_to" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
AssignedToField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"attachments.submitter" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
AttachmentCreatorField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"attach_data.thedata" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
AttachmentDataField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"attachments.description"-> Field Text -> Modification Text -> Change
TextFieldChange Field Text
AttachmentDescriptionField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"attachments.filename" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
AttachmentFilenameField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"attachments.isobsolete" -> Field Bool -> Modification Bool -> Change
BoolFieldChange Field Bool
AttachmentIsObsoleteField (Modification Bool -> Change)
-> Parser (Modification Bool) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Bool)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"attachments.ispatch" -> Field Bool -> Modification Bool -> Change
BoolFieldChange Field Bool
AttachmentIsPatchField (Modification Bool -> Change)
-> Parser (Modification Bool) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Bool)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"attachments.isprivate" -> Field Bool -> Modification Bool -> Change
BoolFieldChange Field Bool
AttachmentIsPrivateField (Modification Bool -> Change)
-> Parser (Modification Bool) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Bool)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"attachments.mimetype" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
AttachmentMimetypeField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"blocks" -> Field Int -> Modification Int -> Change
IntFieldChange Field Int
BlocksField (Modification Int -> Change)
-> Parser (Modification Int) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Int)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"bug_id" -> Field Int -> Modification Int -> Change
IntFieldChange Field Int
BugIdField (Modification Int -> Change)
-> Parser (Modification Int) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Int)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"cc" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
CcField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"is_cc_accessible" -> Field Bool -> Modification Bool -> Change
BoolFieldChange Field Bool
CcListAccessibleField (Modification Bool -> Change)
-> Parser (Modification Bool) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Bool)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"classification" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
ClassificationField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"component" -> Field [Text] -> Modification [Text] -> Change
ListFieldChange Field [Text]
ComponentField (Modification [Text] -> Change)
-> Parser (Modification [Text]) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification [Text])
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"content" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
ContentField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"creation_time" -> Field UTCTime -> Modification UTCTime -> Change
TimeFieldChange Field UTCTime
CreationDateField (Modification UTCTime -> Change)
-> Parser (Modification UTCTime) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification UTCTime)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"days_elapsed" -> Field Int -> Modification Int -> Change
IntFieldChange Field Int
DaysElapsedField (Modification Int -> Change)
-> Parser (Modification Int) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Int)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"depends_on" -> Field Int -> Modification Int -> Change
IntFieldChange Field Int
DependsOnField (Modification Int -> Change)
-> Parser (Modification Int) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Int)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"everconfirmed" -> Field Bool -> Modification Bool -> Change
BoolFieldChange Field Bool
EverConfirmedField (Modification Bool -> Change)
-> Parser (Modification Bool) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Bool)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"flagtypes.name" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
FlagsField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"bug_group" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
GroupField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"keywords" -> Field [Text] -> Modification [Text] -> Change
ListFieldChange Field [Text]
KeywordsField (Modification [Text] -> Change)
-> Parser (Modification [Text]) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification [Text])
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"op_sys" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
OperatingSystemField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"platform" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
HardwareField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"priority" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
PriorityField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"product" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
ProductField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"qa_contact" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
QaContactField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"reporter" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
ReporterField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"reporter_accessible" -> Field Bool -> Modification Bool -> Change
BoolFieldChange Field Bool
ReporterAccessibleField (Modification Bool -> Change)
-> Parser (Modification Bool) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Bool)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"resolution" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
ResolutionField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"restrict_comments" -> Field Bool -> Modification Bool -> Change
BoolFieldChange Field Bool
RestrictCommentsField (Modification Bool -> Change)
-> Parser (Modification Bool) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Bool)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"see_also" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
SeeAlsoField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"severity" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
SeverityField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"status" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
StatusField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"whiteboard" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
WhiteboardField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"summary" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
SummaryField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"tag" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
TagsField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"target_milestone" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
TargetMilestoneField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"url" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
BugURLField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"version" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
VersionField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
"votes" -> Field Text -> Modification Text -> Change
TextFieldChange Field Text
VotesField (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
Text
name -> Field Text -> Modification Text -> Change
TextFieldChange (Text -> Field Text
CustomField Text
name) (Modification Text -> Change)
-> Parser (Modification Text) -> Parser Change
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object -> Parser (Modification Text)
forall a b.
(FromJSON a, Eq b, Show b, ToModification a b) =>
Object -> Parser (Modification b)
parseModification Object
v
parseJSON Value
_ = Parser Change
forall (m :: * -> *) a. MonadPlus m => m a
mzero
data (Eq a, Show a) => Modification a = Modification
{ Modification a -> Maybe a
modRemoved :: Maybe a
, Modification a -> Maybe a
modAdded :: Maybe a
, Modification a -> Maybe Int
modAttachmentId :: Maybe AttachmentId
} deriving (Modification a -> Modification a -> Bool
(Modification a -> Modification a -> Bool)
-> (Modification a -> Modification a -> Bool)
-> Eq (Modification a)
forall a.
(Eq a, Show a) =>
Modification a -> Modification a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Modification a -> Modification a -> Bool
$c/= :: forall a.
(Eq a, Show a) =>
Modification a -> Modification a -> Bool
== :: Modification a -> Modification a -> Bool
$c== :: forall a.
(Eq a, Show a) =>
Modification a -> Modification a -> Bool
Eq, Int -> Modification a -> ShowS
[Modification a] -> ShowS
Modification a -> String
(Int -> Modification a -> ShowS)
-> (Modification a -> String)
-> ([Modification a] -> ShowS)
-> Show (Modification a)
forall a. (Eq a, Show a) => Int -> Modification a -> ShowS
forall a. (Eq a, Show a) => [Modification a] -> ShowS
forall a. (Eq a, Show a) => Modification a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Modification a] -> ShowS
$cshowList :: forall a. (Eq a, Show a) => [Modification a] -> ShowS
show :: Modification a -> String
$cshow :: forall a. (Eq a, Show a) => Modification a -> String
showsPrec :: Int -> Modification a -> ShowS
$cshowsPrec :: forall a. (Eq a, Show a) => Int -> Modification a -> ShowS
Show)
parseModification :: (FromJSON a, Eq b, Show b, ToModification a b) => Object -> Parser (Modification b)
parseModification :: Object -> Parser (Modification b)
parseModification Object
v = Maybe b -> Maybe b -> Maybe Int -> Modification b
forall a. Maybe a -> Maybe a -> Maybe Int -> Modification a
Modification (Maybe b -> Maybe b -> Maybe Int -> Modification b)
-> Parser (Maybe b)
-> Parser (Maybe b -> Maybe Int -> Modification b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> Parser (Maybe b)
forall a b. ToModification a b => a -> Parser (Maybe b)
toMod (a -> Parser (Maybe b)) -> Parser a -> Parser (Maybe b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
v Object -> Text -> Parser a
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"removed")
Parser (Maybe b -> Maybe Int -> Modification b)
-> Parser (Maybe b) -> Parser (Maybe Int -> Modification b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (a -> Parser (Maybe b)
forall a b. ToModification a b => a -> Parser (Maybe b)
toMod (a -> Parser (Maybe b)) -> Parser a -> Parser (Maybe b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
v Object -> Text -> Parser a
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"added")
Parser (Maybe Int -> Modification b)
-> Parser (Maybe Int) -> Parser (Modification b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"attachment_id"
class ToModification a b | b -> a where toMod :: a -> Parser (Maybe b)
instance ToModification T.Text T.Text where toMod :: Text -> Parser (Maybe Text)
toMod = Maybe Text -> Parser (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Text -> Parser (Maybe Text))
-> (Text -> Maybe Text) -> Text -> Parser (Maybe Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text
forall a. a -> Maybe a
Just
instance ToModification UTCTime UTCTime where toMod :: UTCTime -> Parser (Maybe UTCTime)
toMod = Maybe UTCTime -> Parser (Maybe UTCTime)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe UTCTime -> Parser (Maybe UTCTime))
-> (UTCTime -> Maybe UTCTime) -> UTCTime -> Parser (Maybe UTCTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> Maybe UTCTime
forall a. a -> Maybe a
Just
instance ToModification T.Text Int where
toMod :: Text -> Parser (Maybe Int)
toMod Text
v | Text
v Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"" = Maybe Int -> Parser (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing
| Bool
otherwise = case Reader Int
forall a. Integral a => Reader a
TR.decimal Text
v of
Left String
_ -> Parser (Maybe Int)
forall (m :: * -> *) a. MonadPlus m => m a
mzero
Right (Int
i, Text
_) -> Maybe Int -> Parser (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int -> Parser (Maybe Int))
-> Maybe Int -> Parser (Maybe Int)
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Int
forall a. a -> Maybe a
Just Int
i
instance ToModification T.Text Bool where
toMod :: Text -> Parser (Maybe Bool)
toMod Text
v | Text
v Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"0" = Maybe Bool -> Parser (Maybe Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Bool -> Parser (Maybe Bool))
-> Maybe Bool -> Parser (Maybe Bool)
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
| Text
v Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"1" = Maybe Bool -> Parser (Maybe Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Bool -> Parser (Maybe Bool))
-> Maybe Bool -> Parser (Maybe Bool)
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
| Bool
otherwise = Parser (Maybe Bool)
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance ToModification T.Text [T.Text] where
toMod :: Text -> Parser (Maybe [Text])
toMod Text
v = Maybe [Text] -> Parser (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [Text] -> Parser (Maybe [Text]))
-> ([Text] -> Maybe [Text]) -> [Text] -> Parser (Maybe [Text])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just ([Text] -> Parser (Maybe [Text]))
-> [Text] -> Parser (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [Text]
T.splitOn Text
", " Text
v