{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}

module Web.Bugzilla.RedHat.Internal.Types
( BugId
, AttachmentId
, CommentId
, UserId
, EventId
, FlagId
, FlagType
, UserEmail
, Field (..)
, User (..)
, UserList (..)
, Flag (..)
, 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
import qualified Data.HashMap.Strict as H
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 CommentId    = Int
type UserId       = Int
type EventId      = Int
type FlagId       = Int
type FlagType     = Int
type UserEmail    = T.Text

-- | A field which you can search by using 'Web.Bugzilla.searchBugs' or track
--   changes to using 'Web.Bugzilla.getHistory'. To get a human-readable name for
--   a field, use 'fieldName'.
data Field a where
  AliasField                    :: Field [T.Text]         -- Alias
  AssignedToField               :: Field UserEmail        -- Assignee
  AttachmentCreatorField        :: Field UserEmail        -- Attachment creator
  AttachmentDataField           :: Field T.Text           -- Attachment data
  AttachmentDescriptionField    :: Field T.Text           -- Attachment description
  AttachmentFilenameField       :: Field T.Text           -- Attachment filename
  AttachmentIsObsoleteField     :: Field Bool             -- Attachment is obsolete
  AttachmentIsPatchField        :: Field Bool             -- Attachment is patch
  AttachmentIsPrivateField      :: Field Bool             -- Attachment is private
  AttachmentMimetypeField       :: Field T.Text           -- Attachment mime type
  BlocksField                   :: Field Int              -- Blocks
  BugIdField                    :: Field Int              -- Bug ID
  CcField                       :: Field UserEmail        -- CC
  CcListAccessibleField         :: Field Bool             -- CC list accessible
  ClassificationField           :: Field T.Text           -- Classification
  CommentField                  :: Field T.Text           -- Comment
  CommentIsPrivateField         :: Field T.Text           -- Comment is private
  CommentTagsField              :: Field T.Text           -- Comment Tags
  CommenterField                :: Field UserEmail        -- Commenter
  ComponentField                :: Field [T.Text]         -- Component
  ContentField                  :: Field T.Text           -- Content
  CreationDateField             :: Field UTCTime          -- Creation date
  DaysElapsedField              :: Field Int              -- Days since bug changed
  DependsOnField                :: Field Int              -- Depends on
  EverConfirmedField            :: Field Bool             -- Ever confirmed
  FlagRequesteeField            :: Field UserEmail        -- Flag Requestee
  FlagSetterField               :: Field UserEmail        -- Flag Setter
  FlagsField                    :: Field T.Text           -- Flags
  GroupField                    :: Field T.Text           -- Group
  KeywordsField                 :: Field [T.Text]         -- Keywords
  ChangedField                  :: Field UTCTime          -- Changed
  CommentCountField             :: Field Int              -- Number of Comments
  OperatingSystemField          :: Field T.Text           -- OS
  HardwareField                 :: Field T.Text           -- Hardware
  PriorityField                 :: Field T.Text           -- Priority
  ProductField                  :: Field T.Text           -- Product
  QaContactField                :: Field UserEmail        -- QA Contact
  ReporterField                 :: Field UserEmail        -- Reporter
  ReporterAccessibleField       :: Field Bool             -- Reporter accessible
  ResolutionField               :: Field T.Text           -- Resolution
  RestrictCommentsField         :: Field Bool             -- Restrict Comments
  SeeAlsoField                  :: Field T.Text           -- See Also
  SeverityField                 :: Field T.Text           -- Severity
  StatusField                   :: Field T.Text           -- Status
  WhiteboardField               :: Field T.Text           -- Whiteboard
  SummaryField                  :: Field T.Text           -- Summary
  TagsField                     :: Field T.Text           -- Tags
  TargetMilestoneField          :: Field T.Text           -- Target Milestone
  TimeSinceAssigneeTouchedField :: Field Int              -- Time Since Assignee Touched
  BugURLField                   :: Field T.Text           -- URL
  VersionField                  :: Field T.Text           -- Version
  VotesField                    :: Field T.Text           -- Votes
  CustomField                   :: T.Text -> Field T.Text -- (Custom fields)

instance Eq (Field a) where
  (CustomField a :: Text
a) == :: Field a -> Field a -> Bool
== (CustomField b :: Text
b) = Text
a Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
b
  (CustomField _) == _               = Bool
False
  _ == (CustomField _)               = Bool
False
  a :: Field a
a == b :: 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 AliasField                    = "AliasField"
  show AssignedToField               = "AssignedToField"
  show AttachmentCreatorField        = "AttachmentCreatorField"
  show AttachmentDataField           = "AttachmentDataField"
  show AttachmentDescriptionField    = "AttachmentDescriptionField"
  show AttachmentFilenameField       = "AttachmentFilenameField"
  show AttachmentIsObsoleteField     = "AttachmentIsObsoleteField"
  show AttachmentIsPatchField        = "AttachmentIsPatchField"
  show AttachmentIsPrivateField      = "AttachmentIsPrivateField"
  show AttachmentMimetypeField       = "AttachmentMimetypeField"
  show BlocksField                   = "BlocksField"
  show BugIdField                    = "BugIdField"
  show CcField                       = "CcField"
  show CcListAccessibleField         = "CcListAccessibleField"
  show ClassificationField           = "ClassificationField"
  show CommentField                  = "CommentField"
  show CommentIsPrivateField         = "CommentIsPrivateField"
  show CommentTagsField              = "CommentTagsField"
  show CommenterField                = "CommenterField"
  show ComponentField                = "ComponentField"
  show ContentField                  = "ContentField"
  show CreationDateField             = "CreationDateField"
  show DaysElapsedField              = "DaysElapsedField"
  show DependsOnField                = "DependsOnField"
  show EverConfirmedField            = "EverConfirmedField"
  show FlagRequesteeField            = "FlagRequesteeField"
  show FlagSetterField               = "FlagSetterField"
  show FlagsField                    = "FlagsField"
  show GroupField                    = "GroupField"
  show KeywordsField                 = "KeywordsField"
  show ChangedField                  = "ChangedField"
  show CommentCountField             = "CommentCountField"
  show OperatingSystemField          = "OperatingSystemField"
  show HardwareField                 = "HardwareField"
  show PriorityField                 = "PriorityField"
  show ProductField                  = "ProductField"
  show QaContactField                = "QaContactField"
  show ReporterField                 = "ReporterField"
  show ReporterAccessibleField       = "ReporterAccessibleField"
  show ResolutionField               = "ResolutionField"
  show RestrictCommentsField         = "RestrictCommentsField"
  show SeeAlsoField                  = "SeeAlsoField"
  show SeverityField                 = "SeverityField"
  show StatusField                   = "StatusField"
  show WhiteboardField               = "WhiteboardField"
  show SummaryField                  = "SummaryField"
  show TagsField                     = "TagsField"
  show TargetMilestoneField          = "TargetMilestoneField"
  show TimeSinceAssigneeTouchedField = "TimeSinceAssigneeTouchedField"
  show BugURLField                   = "BugURLField"
  show VersionField                  = "VersionField"
  show VotesField                    = "VotesField"
  show (CustomField name :: Text
name)            = "CustomField " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
name

-- | Provides a human-readable name for a 'Field'.
fieldName :: Field a -> T.Text
fieldName :: Field a -> Text
fieldName AliasField                    = "Alias"
fieldName AssignedToField               = "Assigned to"
fieldName AttachmentCreatorField        = "Attachment creator"
fieldName AttachmentDataField           = "Attachment data"
fieldName AttachmentDescriptionField    = "Attachment description"
fieldName AttachmentFilenameField       = "Attachment filename"
fieldName AttachmentIsObsoleteField     = "Attachment is obsolete"
fieldName AttachmentIsPatchField        = "Attachment is patch"
fieldName AttachmentIsPrivateField      = "Attachment is private"
fieldName AttachmentMimetypeField       = "Attachment MIME type"
fieldName BlocksField                   = "Blocks"
fieldName BugIdField                    = "BugId"
fieldName CcField                       = "CC"
fieldName CcListAccessibleField         = "CC list is accessible"
fieldName ClassificationField           = "Classification"
fieldName CommentField                  = "Comment"
fieldName CommentIsPrivateField         = "Comment is private"
fieldName CommentTagsField              = "Comment tags"
fieldName CommenterField                = "Commenter"
fieldName ComponentField                = "Component"
fieldName ContentField                  = "Content"
fieldName CreationDateField             = "Creation date"
fieldName DaysElapsedField              = "Days elapsed"
fieldName DependsOnField                = "Depends on"
fieldName EverConfirmedField            = "Ever confirmed"
fieldName FlagRequesteeField            = "Flag requestee"
fieldName FlagSetterField               = "Flag setter"
fieldName FlagsField                    = "Flags"
fieldName GroupField                    = "Group"
fieldName KeywordsField                 = "Keywords"
fieldName ChangedField                  = "Changed"
fieldName CommentCountField             = "Comment count"
fieldName OperatingSystemField          = "Operating system"
fieldName HardwareField                 = "Hardware"
fieldName PriorityField                 = "Priority"
fieldName ProductField                  = "Product"
fieldName QaContactField                = "QA contact"
fieldName ReporterField                 = "Reporter"
fieldName ReporterAccessibleField       = "Reporter accessible"
fieldName ResolutionField               = "Resolution"
fieldName RestrictCommentsField         = "Restrict comments"
fieldName SeeAlsoField                  = "See also"
fieldName SeverityField                 = "Severity"
fieldName StatusField                   = "Status"
fieldName WhiteboardField               = "Whiteboard"
fieldName SummaryField                  = "Summary"
fieldName TagsField                     = "Tags"
fieldName TargetMilestoneField          = "Target milestone"
fieldName TimeSinceAssigneeTouchedField = "Time since assignee touched"
fieldName BugURLField                   = "Bug URL"
fieldName VersionField                  = "Version"
fieldName VotesField                    = "Votes"
fieldName (CustomField name :: Text
name)            = [Text] -> Text
T.concat ["Custom field \"", String -> Text
T.pack (Text -> String
forall a. Show a => a -> String
show Text
name), "\""]

searchFieldName :: Field a -> T.Text
searchFieldName :: Field a -> Text
searchFieldName AliasField                    = "alias"
searchFieldName AssignedToField               = "assigned_to"
searchFieldName AttachmentCreatorField        = "attachments.submitter"
searchFieldName AttachmentDataField           = "attach_data.thedata"
searchFieldName AttachmentDescriptionField    = "attachments.description"
searchFieldName AttachmentFilenameField       = "attachments.filename"
searchFieldName AttachmentIsObsoleteField     = "attachments.isobsolete"
searchFieldName AttachmentIsPatchField        = "attachments.ispatch"
searchFieldName AttachmentIsPrivateField      = "attachments.isprivate"
searchFieldName AttachmentMimetypeField       = "attachments.mimetype"
searchFieldName BlocksField                   = "blocked"
searchFieldName BugIdField                    = "bug_id"
searchFieldName CcField                       = "cc"
searchFieldName CcListAccessibleField         = "cclist_accessible"
searchFieldName ClassificationField           = "classification"
searchFieldName CommentField                  = "longdesc"
searchFieldName CommentIsPrivateField         = "longdescs.isprivate"
searchFieldName CommentTagsField              = "comment_tag"
searchFieldName CommenterField                = "commenter"
searchFieldName ComponentField                = "component"
searchFieldName ContentField                  = "content"
searchFieldName CreationDateField             = "creation_ts"
searchFieldName DaysElapsedField              = "days_elapsed"
searchFieldName DependsOnField                = "dependson"
searchFieldName EverConfirmedField            = "everconfirmed"
searchFieldName FlagRequesteeField            = "requestees.login_name"
searchFieldName FlagSetterField               = "setters.login_name"
searchFieldName FlagsField                    = "flagtypes.name"
searchFieldName GroupField                    = "bug_group"
searchFieldName KeywordsField                 = "keywords"
searchFieldName ChangedField                  = "delta_ts"
searchFieldName CommentCountField             = "longdescs.count"
searchFieldName OperatingSystemField          = "op_sys"
searchFieldName HardwareField                 = "rep_platform"
searchFieldName PriorityField                 = "priority"
searchFieldName ProductField                  = "product"
searchFieldName QaContactField                = "qa_contact"
searchFieldName ReporterField                 = "reporter"
searchFieldName ReporterAccessibleField       = "reporter_accessible"
searchFieldName ResolutionField               = "resolution"
searchFieldName RestrictCommentsField         = "restrict_comments"
searchFieldName SeeAlsoField                  = "see_also"
searchFieldName SeverityField                 = "bug_severity"
searchFieldName StatusField                   = "bug_status"
searchFieldName WhiteboardField               = "status_whiteboard"
searchFieldName SummaryField                  = "short_desc"
searchFieldName TagsField                     = "tag"
searchFieldName TargetMilestoneField          = "target_milestone"
searchFieldName TimeSinceAssigneeTouchedField = "owner_idle_time"
searchFieldName BugURLField                   = "bug_file_loc"
searchFieldName VersionField                  = "version"
searchFieldName VotesField                    = "votes"
searchFieldName (CustomField name :: Text
name)            = Text
name

-- | A Bugzilla user.
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 v :: 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
.: "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)
.:? "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
.: "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
.: "real_name"
  parseJSON _ = 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 v :: 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
.: "users"
  parseJSON _          = Parser UserList
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- | Flags, which may be set on an attachment or on a bug directly.
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 v :: 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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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)
.:? "requestee"
  parseJSON _ = Parser Flag
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- | A Bugzilla bug.
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]
bugSeeAlso             :: [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        :: H.HashMap T.Text T.Text
  } 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 v :: 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]
-> Text
-> HashMap Text Text
-> 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]
 -> Text
 -> HashMap Text Text
 -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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)
.:? "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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
.: "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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)
.:? "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]
   -> Text
   -> HashMap Text Text
   -> 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]
      -> Text
      -> HashMap Text Text
      -> 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)
.:? "flags"
          Parser
  ([Text]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> [Text]
   -> UTCTime
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser [Text]
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> [Text]
      -> UTCTime
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "groups"
          Parser
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> [Text]
   -> UTCTime
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> [Text]
      -> UTCTime
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "is_cc_accessible"
          Parser
  (Bool
   -> Bool
   -> Bool
   -> [Text]
   -> UTCTime
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> [Text]
      -> UTCTime
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "is_confirmed"
          Parser
  (Bool
   -> Bool
   -> [Text]
   -> UTCTime
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Bool
-> Parser
     (Bool
      -> [Text]
      -> UTCTime
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "is_creator_accessible"
          Parser
  (Bool
   -> [Text]
   -> UTCTime
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Bool
-> Parser
     ([Text]
      -> UTCTime
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "is_open"
          Parser
  ([Text]
   -> UTCTime
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser [Text]
-> Parser
     (UTCTime
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "keywords"
          Parser
  (UTCTime
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser UTCTime
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "last_change_time"
          Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "op_sys"
          Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "platform"
          Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "priority"
          Parser
  (Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "product"
          Parser
  (Text
   -> Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Text
-> Parser
     (Text
      -> [Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "qa_contact"
          Parser
  (Text
   -> [Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Text
-> Parser
     ([Text]
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "resolution"
          Parser
  ([Text]
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser [Text]
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "see_also"
          Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> HashMap Text Text
      -> 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
.: "severity"
          Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> HashMap Text Text
   -> Bug)
-> Parser Text
-> Parser
     (Text
      -> Text -> Text -> [Text] -> Text -> HashMap Text Text -> 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
.: "status"
          Parser
  (Text
   -> Text -> Text -> [Text] -> Text -> HashMap Text Text -> Bug)
-> Parser Text
-> Parser
     (Text -> Text -> [Text] -> Text -> HashMap Text Text -> 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
.: "summary"
          Parser (Text -> Text -> [Text] -> Text -> HashMap Text Text -> Bug)
-> Parser Text
-> Parser (Text -> [Text] -> Text -> HashMap Text Text -> 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
.: "target_milestone"
          Parser (Text -> [Text] -> Text -> HashMap Text Text -> Bug)
-> Parser Text
-> Parser ([Text] -> Text -> HashMap Text Text -> 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
.: "url"
          Parser ([Text] -> Text -> HashMap Text Text -> Bug)
-> Parser [Text] -> Parser (Text -> HashMap Text Text -> 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
.: "version"
          Parser (Text -> HashMap Text Text -> Bug)
-> Parser Text -> Parser (HashMap Text Text -> 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
.: "whiteboard"
          Parser (HashMap Text Text -> Bug)
-> Parser (HashMap Text Text) -> Parser 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)
  parseJSON _ = Parser Bug
forall (m :: * -> *) a. MonadPlus m => m a
mzero

customFields :: Object -> H.HashMap T.Text T.Text
customFields :: Object -> HashMap Text Text
customFields = (Value -> Text) -> Object -> HashMap Text Text
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
H.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
H.filterWithKey Text -> Value -> Bool
forall p. Text -> p -> Bool
filterCustomFields
  where
    stringifyCustomFields :: Value -> T.Text
    stringifyCustomFields :: Value -> Text
stringifyCustomFields (String t :: Text
t) = Text
t
    stringifyCustomFields v :: 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 k :: Text
k _ = "cf_" Text -> Text -> Bool
`T.isPrefixOf` Text
k

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 v :: 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
.: "bugs"
  parseJSON _          = 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 v :: Object
v) = do
    [Object]
bugs <- Object
v Object -> Text -> Parser [Object]
forall a. FromJSON a => Object -> Text -> Parser a
.: "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
.: "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 _          = Parser BugIdList
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- | An attachment to a bug.
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 v :: 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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "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
.: "data"
  parseJSON _ = Parser Attachment
forall (m :: * -> *) a. MonadPlus m => m a
mzero

fromNumericBool :: Int -> Bool
fromNumericBool :: Int -> Bool
fromNumericBool 0 = Bool
False
fromNumericBool _ = 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 v :: Object
v) = do
    Value
attachmentsVal <- Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: "attachments"
    Value
bugsVal <- Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: "bugs"
    case (Value
attachmentsVal, Value
bugsVal) of
      (Object (Object -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
H.toList -> [(_, as :: Value
as)]), _) -> [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
      (_, Object (Object -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
H.toList -> [(_, as :: 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
      _                                   -> Parser AttachmentList
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  parseJSON _ = Parser AttachmentList
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- | A bug comment. To display these the way Bugzilla does, you'll
-- need to call 'getUser' and use the 'userRealName' for each user.
data Comment = Comment
  { Comment -> Int
commentId           :: !CommentId
  , Comment -> Int
commentBugId        :: !BugId
  , Comment -> Maybe Int
commentAttachmentId :: Maybe AttachmentId
  , Comment -> Int
commentCount        :: !Int
  , Comment -> Text
commentText         :: T.Text
  , Comment -> Text
commentCreator      :: UserEmail
  , Comment -> UTCTime
commentCreationTime :: UTCTime
  , Comment -> Bool
commentIsPrivate    :: 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 v :: 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
.: "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
.: "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
.: "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
.: "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"
            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
.: "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
.: "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
.: "is_private"
  parseJSON _ = Parser Comment
forall (m :: * -> *) a. MonadPlus m => m a
mzero

newtype CommentList = CommentList [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 v :: Object
v) = do
    Value
bugsVal <- Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: "bugs"
    case Value
bugsVal of
      Object (Object -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
H.toList -> [(_, cs :: Value
cs)]) ->
        do Value
comments <- String -> (Object -> Parser Value) -> Value -> Parser Value
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject "comments" (Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: "comments") Value
cs
           String
-> (Array -> Parser CommentList) -> Value -> Parser CommentList
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray "comment list" (\a :: 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
      _ -> Parser CommentList
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  parseJSON _ = Parser CommentList
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- Note that we make the (possibly unwise) assumption that Bugzilla
-- returns the comments in order. If it turns out that's not true, we
-- can always sort by their 'id' to ensure correct results.
addCount :: V.Vector Value -> Value
addCount :: Array -> Value
addCount vs :: 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 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' c :: Int
c (Object v :: 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
H.insert "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' _ v :: Value
v          = Value
v

-- | History information for a bug.
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 v :: Object
v) = do
    Value
bugsVal <- Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: "bugs"
    case Value
bugsVal of
      Array (Array -> [Value]
forall a. Vector a -> [a]
V.toList -> [history :: Value
history]) ->
        String -> (Object -> Parser History) -> Value -> Parser History
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject "history"
                   (\h :: 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
.: "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
      _ -> Parser History
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  parseJSON _ = Parser History
forall (m :: * -> *) a. MonadPlus m => m a
mzero

parseHistoryEvents :: Object -> Parser [HistoryEvent]
parseHistoryEvents :: Object -> Parser [HistoryEvent]
parseHistoryEvents h :: Object
h = do
  Value
events <- Object
h Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: "history"
  String
-> (Array -> Parser [HistoryEvent])
-> Value
-> Parser [HistoryEvent]
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray "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

-- | An event in a bug's history.
data HistoryEvent = HistoryEvent
  { HistoryEvent -> Int
historyEventId      :: EventId   -- ^ A sequential event id.
  , HistoryEvent -> UTCTime
historyEventTime    :: UTCTime   -- ^ When the event occurred.
  , HistoryEvent -> Text
historyEventUser    :: UserEmail -- ^ Which user was responsible.
  , HistoryEvent -> [Change]
historyEventChanges :: [Change]  -- ^ All the changes which are
                                     --   part of this event.
  } 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 v :: 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
.: "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
.: "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
.: "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
.: "changes"
  parseJSON _ = Parser HistoryEvent
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- | A single change which is part of an event. Different constructors
--   are used according to the type of the field. The 'Modification'
--   describes the value of the field before and after the change.
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 v :: Object
v) = do
    Text
changedField <- Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: "field_name"
    case Text
changedField of
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      "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
      name :: 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 _ = Parser Change
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- | A description of how a field changed during a 'HistoryEvent'.
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 v :: 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
.: "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
.: "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)
.:? "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 v :: Text
v | Text
v Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== "" = 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 _       -> Parser (Maybe Int)
forall (m :: * -> *) a. MonadPlus m => m a
mzero
                          Right (i :: Int
i, _) -> 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 v :: Text
v | Text
v Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== "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
== "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 v :: 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
v