-----------------------------------------------------------------------------
-- |
-- License     :  BSD-3-Clause
-- Maintainer  :  Oleg Grenrus <oleg.grenrus@iki.fi>
--
module GitHub.Data.Activities where

import GitHub.Data.Id          (Id, mkId)
import GitHub.Data.Repos       (Repo, RepoRef)
import GitHub.Data.URL         (URL)
import GitHub.Internal.Prelude

import Prelude ()

import qualified Data.Text as T

data RepoStarred = RepoStarred
    { RepoStarred -> UTCTime
repoStarredStarredAt :: !UTCTime
    , RepoStarred -> Repo
repoStarredRepo      :: !Repo
    }
  deriving (Int -> RepoStarred -> ShowS
[RepoStarred] -> ShowS
RepoStarred -> String
(Int -> RepoStarred -> ShowS)
-> (RepoStarred -> String)
-> ([RepoStarred] -> ShowS)
-> Show RepoStarred
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepoStarred] -> ShowS
$cshowList :: [RepoStarred] -> ShowS
show :: RepoStarred -> String
$cshow :: RepoStarred -> String
showsPrec :: Int -> RepoStarred -> ShowS
$cshowsPrec :: Int -> RepoStarred -> ShowS
Show, Typeable RepoStarred
DataType
Constr
Typeable RepoStarred
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> RepoStarred -> c RepoStarred)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RepoStarred)
-> (RepoStarred -> Constr)
-> (RepoStarred -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c RepoStarred))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c RepoStarred))
-> ((forall b. Data b => b -> b) -> RepoStarred -> RepoStarred)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> RepoStarred -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> RepoStarred -> r)
-> (forall u. (forall d. Data d => d -> u) -> RepoStarred -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> RepoStarred -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred)
-> Data RepoStarred
RepoStarred -> DataType
RepoStarred -> Constr
(forall b. Data b => b -> b) -> RepoStarred -> RepoStarred
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoStarred -> c RepoStarred
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoStarred
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> RepoStarred -> u
forall u. (forall d. Data d => d -> u) -> RepoStarred -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoStarred -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoStarred -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoStarred
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoStarred -> c RepoStarred
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoStarred)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepoStarred)
$cRepoStarred :: Constr
$tRepoStarred :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred
gmapMp :: (forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred
gmapM :: (forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoStarred -> m RepoStarred
gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoStarred -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RepoStarred -> u
gmapQ :: (forall d. Data d => d -> u) -> RepoStarred -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RepoStarred -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoStarred -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoStarred -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoStarred -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoStarred -> r
gmapT :: (forall b. Data b => b -> b) -> RepoStarred -> RepoStarred
$cgmapT :: (forall b. Data b => b -> b) -> RepoStarred -> RepoStarred
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepoStarred)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepoStarred)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RepoStarred)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoStarred)
dataTypeOf :: RepoStarred -> DataType
$cdataTypeOf :: RepoStarred -> DataType
toConstr :: RepoStarred -> Constr
$ctoConstr :: RepoStarred -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoStarred
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoStarred
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoStarred -> c RepoStarred
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoStarred -> c RepoStarred
$cp1Data :: Typeable RepoStarred
Data, Typeable, RepoStarred -> RepoStarred -> Bool
(RepoStarred -> RepoStarred -> Bool)
-> (RepoStarred -> RepoStarred -> Bool) -> Eq RepoStarred
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoStarred -> RepoStarred -> Bool
$c/= :: RepoStarred -> RepoStarred -> Bool
== :: RepoStarred -> RepoStarred -> Bool
$c== :: RepoStarred -> RepoStarred -> Bool
Eq, Eq RepoStarred
Eq RepoStarred
-> (RepoStarred -> RepoStarred -> Ordering)
-> (RepoStarred -> RepoStarred -> Bool)
-> (RepoStarred -> RepoStarred -> Bool)
-> (RepoStarred -> RepoStarred -> Bool)
-> (RepoStarred -> RepoStarred -> Bool)
-> (RepoStarred -> RepoStarred -> RepoStarred)
-> (RepoStarred -> RepoStarred -> RepoStarred)
-> Ord RepoStarred
RepoStarred -> RepoStarred -> Bool
RepoStarred -> RepoStarred -> Ordering
RepoStarred -> RepoStarred -> RepoStarred
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 :: RepoStarred -> RepoStarred -> RepoStarred
$cmin :: RepoStarred -> RepoStarred -> RepoStarred
max :: RepoStarred -> RepoStarred -> RepoStarred
$cmax :: RepoStarred -> RepoStarred -> RepoStarred
>= :: RepoStarred -> RepoStarred -> Bool
$c>= :: RepoStarred -> RepoStarred -> Bool
> :: RepoStarred -> RepoStarred -> Bool
$c> :: RepoStarred -> RepoStarred -> Bool
<= :: RepoStarred -> RepoStarred -> Bool
$c<= :: RepoStarred -> RepoStarred -> Bool
< :: RepoStarred -> RepoStarred -> Bool
$c< :: RepoStarred -> RepoStarred -> Bool
compare :: RepoStarred -> RepoStarred -> Ordering
$ccompare :: RepoStarred -> RepoStarred -> Ordering
$cp1Ord :: Eq RepoStarred
Ord, (forall x. RepoStarred -> Rep RepoStarred x)
-> (forall x. Rep RepoStarred x -> RepoStarred)
-> Generic RepoStarred
forall x. Rep RepoStarred x -> RepoStarred
forall x. RepoStarred -> Rep RepoStarred x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RepoStarred x -> RepoStarred
$cfrom :: forall x. RepoStarred -> Rep RepoStarred x
Generic)

instance NFData RepoStarred where rnf :: RepoStarred -> ()
rnf = RepoStarred -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary RepoStarred

-- JSON Instances
instance FromJSON RepoStarred where
    parseJSON :: Value -> Parser RepoStarred
parseJSON = String
-> (Object -> Parser RepoStarred) -> Value -> Parser RepoStarred
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RepoStarred" ((Object -> Parser RepoStarred) -> Value -> Parser RepoStarred)
-> (Object -> Parser RepoStarred) -> Value -> Parser RepoStarred
forall a b. (a -> b) -> a -> b
$ \Object
o -> UTCTime -> Repo -> RepoStarred
RepoStarred
        (UTCTime -> Repo -> RepoStarred)
-> Parser UTCTime -> Parser (Repo -> RepoStarred)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser UTCTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"starred_at"
        Parser (Repo -> RepoStarred) -> Parser Repo -> Parser RepoStarred
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Repo
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"repo"

data Subject = Subject
    { Subject -> Text
subjectTitle :: !Text
    , Subject -> URL
subjectURL :: !URL
    , Subject -> Maybe URL
subjectLatestCommentURL :: !(Maybe URL)
    -- https://developer.github.com/v3/activity/notifications/ doesn't indicate
    -- what the possible values for this field are.
    -- TODO: Make an ADT for this.
    , Subject -> Text
subjectType :: !Text
    }
  deriving (Int -> Subject -> ShowS
[Subject] -> ShowS
Subject -> String
(Int -> Subject -> ShowS)
-> (Subject -> String) -> ([Subject] -> ShowS) -> Show Subject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Subject] -> ShowS
$cshowList :: [Subject] -> ShowS
show :: Subject -> String
$cshow :: Subject -> String
showsPrec :: Int -> Subject -> ShowS
$cshowsPrec :: Int -> Subject -> ShowS
Show, Typeable Subject
DataType
Constr
Typeable Subject
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Subject -> c Subject)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Subject)
-> (Subject -> Constr)
-> (Subject -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Subject))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Subject))
-> ((forall b. Data b => b -> b) -> Subject -> Subject)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Subject -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Subject -> r)
-> (forall u. (forall d. Data d => d -> u) -> Subject -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Subject -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Subject -> m Subject)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Subject -> m Subject)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Subject -> m Subject)
-> Data Subject
Subject -> DataType
Subject -> Constr
(forall b. Data b => b -> b) -> Subject -> Subject
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Subject -> c Subject
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Subject
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Subject -> u
forall u. (forall d. Data d => d -> u) -> Subject -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Subject -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Subject -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Subject -> m Subject
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Subject -> m Subject
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Subject
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Subject -> c Subject
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Subject)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Subject)
$cSubject :: Constr
$tSubject :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Subject -> m Subject
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Subject -> m Subject
gmapMp :: (forall d. Data d => d -> m d) -> Subject -> m Subject
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Subject -> m Subject
gmapM :: (forall d. Data d => d -> m d) -> Subject -> m Subject
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Subject -> m Subject
gmapQi :: Int -> (forall d. Data d => d -> u) -> Subject -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Subject -> u
gmapQ :: (forall d. Data d => d -> u) -> Subject -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Subject -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Subject -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Subject -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Subject -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Subject -> r
gmapT :: (forall b. Data b => b -> b) -> Subject -> Subject
$cgmapT :: (forall b. Data b => b -> b) -> Subject -> Subject
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Subject)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Subject)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Subject)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Subject)
dataTypeOf :: Subject -> DataType
$cdataTypeOf :: Subject -> DataType
toConstr :: Subject -> Constr
$ctoConstr :: Subject -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Subject
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Subject
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Subject -> c Subject
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Subject -> c Subject
$cp1Data :: Typeable Subject
Data, Typeable, Subject -> Subject -> Bool
(Subject -> Subject -> Bool)
-> (Subject -> Subject -> Bool) -> Eq Subject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subject -> Subject -> Bool
$c/= :: Subject -> Subject -> Bool
== :: Subject -> Subject -> Bool
$c== :: Subject -> Subject -> Bool
Eq, Eq Subject
Eq Subject
-> (Subject -> Subject -> Ordering)
-> (Subject -> Subject -> Bool)
-> (Subject -> Subject -> Bool)
-> (Subject -> Subject -> Bool)
-> (Subject -> Subject -> Bool)
-> (Subject -> Subject -> Subject)
-> (Subject -> Subject -> Subject)
-> Ord Subject
Subject -> Subject -> Bool
Subject -> Subject -> Ordering
Subject -> Subject -> Subject
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 :: Subject -> Subject -> Subject
$cmin :: Subject -> Subject -> Subject
max :: Subject -> Subject -> Subject
$cmax :: Subject -> Subject -> Subject
>= :: Subject -> Subject -> Bool
$c>= :: Subject -> Subject -> Bool
> :: Subject -> Subject -> Bool
$c> :: Subject -> Subject -> Bool
<= :: Subject -> Subject -> Bool
$c<= :: Subject -> Subject -> Bool
< :: Subject -> Subject -> Bool
$c< :: Subject -> Subject -> Bool
compare :: Subject -> Subject -> Ordering
$ccompare :: Subject -> Subject -> Ordering
$cp1Ord :: Eq Subject
Ord, (forall x. Subject -> Rep Subject x)
-> (forall x. Rep Subject x -> Subject) -> Generic Subject
forall x. Rep Subject x -> Subject
forall x. Subject -> Rep Subject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Subject x -> Subject
$cfrom :: forall x. Subject -> Rep Subject x
Generic)

instance NFData Subject where rnf :: Subject -> ()
rnf = Subject -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Subject

instance FromJSON Subject where
    parseJSON :: Value -> Parser Subject
parseJSON = String -> (Object -> Parser Subject) -> Value -> Parser Subject
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Subject" ((Object -> Parser Subject) -> Value -> Parser Subject)
-> (Object -> Parser Subject) -> Value -> Parser Subject
forall a b. (a -> b) -> a -> b
$ \Object
o -> Text -> URL -> Maybe URL -> Text -> Subject
Subject
        (Text -> URL -> Maybe URL -> Text -> Subject)
-> Parser Text -> Parser (URL -> Maybe URL -> Text -> Subject)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"title"
        Parser (URL -> Maybe URL -> Text -> Subject)
-> Parser URL -> Parser (Maybe URL -> Text -> Subject)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser URL
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
        Parser (Maybe URL -> Text -> Subject)
-> Parser (Maybe URL) -> Parser (Text -> Subject)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe URL)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"latest_comment_url"
        Parser (Text -> Subject) -> Parser Text -> Parser Subject
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"

data NotificationReason
    = AssignReason
    | AuthorReason
    | CommentReason
    | InvitationReason
    | ManualReason
    | MentionReason
    | ReviewRequestedReason
    | StateChangeReason
    | SubscribedReason
    | TeamMentionReason
  deriving (Int -> NotificationReason -> ShowS
[NotificationReason] -> ShowS
NotificationReason -> String
(Int -> NotificationReason -> ShowS)
-> (NotificationReason -> String)
-> ([NotificationReason] -> ShowS)
-> Show NotificationReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotificationReason] -> ShowS
$cshowList :: [NotificationReason] -> ShowS
show :: NotificationReason -> String
$cshow :: NotificationReason -> String
showsPrec :: Int -> NotificationReason -> ShowS
$cshowsPrec :: Int -> NotificationReason -> ShowS
Show, Typeable NotificationReason
DataType
Constr
Typeable NotificationReason
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> NotificationReason
    -> c NotificationReason)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c NotificationReason)
-> (NotificationReason -> Constr)
-> (NotificationReason -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c NotificationReason))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c NotificationReason))
-> ((forall b. Data b => b -> b)
    -> NotificationReason -> NotificationReason)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> NotificationReason -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> NotificationReason -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> NotificationReason -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> NotificationReason -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> NotificationReason -> m NotificationReason)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> NotificationReason -> m NotificationReason)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> NotificationReason -> m NotificationReason)
-> Data NotificationReason
NotificationReason -> DataType
NotificationReason -> Constr
(forall b. Data b => b -> b)
-> NotificationReason -> NotificationReason
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NotificationReason
-> c NotificationReason
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NotificationReason
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> NotificationReason -> u
forall u. (forall d. Data d => d -> u) -> NotificationReason -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NotificationReason -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NotificationReason -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NotificationReason -> m NotificationReason
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NotificationReason -> m NotificationReason
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NotificationReason
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NotificationReason
-> c NotificationReason
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NotificationReason)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NotificationReason)
$cTeamMentionReason :: Constr
$cSubscribedReason :: Constr
$cStateChangeReason :: Constr
$cReviewRequestedReason :: Constr
$cMentionReason :: Constr
$cManualReason :: Constr
$cInvitationReason :: Constr
$cCommentReason :: Constr
$cAuthorReason :: Constr
$cAssignReason :: Constr
$tNotificationReason :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> NotificationReason -> m NotificationReason
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NotificationReason -> m NotificationReason
gmapMp :: (forall d. Data d => d -> m d)
-> NotificationReason -> m NotificationReason
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NotificationReason -> m NotificationReason
gmapM :: (forall d. Data d => d -> m d)
-> NotificationReason -> m NotificationReason
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NotificationReason -> m NotificationReason
gmapQi :: Int -> (forall d. Data d => d -> u) -> NotificationReason -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> NotificationReason -> u
gmapQ :: (forall d. Data d => d -> u) -> NotificationReason -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NotificationReason -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NotificationReason -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NotificationReason -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NotificationReason -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NotificationReason -> r
gmapT :: (forall b. Data b => b -> b)
-> NotificationReason -> NotificationReason
$cgmapT :: (forall b. Data b => b -> b)
-> NotificationReason -> NotificationReason
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NotificationReason)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NotificationReason)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c NotificationReason)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NotificationReason)
dataTypeOf :: NotificationReason -> DataType
$cdataTypeOf :: NotificationReason -> DataType
toConstr :: NotificationReason -> Constr
$ctoConstr :: NotificationReason -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NotificationReason
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NotificationReason
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NotificationReason
-> c NotificationReason
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NotificationReason
-> c NotificationReason
$cp1Data :: Typeable NotificationReason
Data, Int -> NotificationReason
NotificationReason -> Int
NotificationReason -> [NotificationReason]
NotificationReason -> NotificationReason
NotificationReason -> NotificationReason -> [NotificationReason]
NotificationReason
-> NotificationReason -> NotificationReason -> [NotificationReason]
(NotificationReason -> NotificationReason)
-> (NotificationReason -> NotificationReason)
-> (Int -> NotificationReason)
-> (NotificationReason -> Int)
-> (NotificationReason -> [NotificationReason])
-> (NotificationReason
    -> NotificationReason -> [NotificationReason])
-> (NotificationReason
    -> NotificationReason -> [NotificationReason])
-> (NotificationReason
    -> NotificationReason
    -> NotificationReason
    -> [NotificationReason])
-> Enum NotificationReason
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: NotificationReason
-> NotificationReason -> NotificationReason -> [NotificationReason]
$cenumFromThenTo :: NotificationReason
-> NotificationReason -> NotificationReason -> [NotificationReason]
enumFromTo :: NotificationReason -> NotificationReason -> [NotificationReason]
$cenumFromTo :: NotificationReason -> NotificationReason -> [NotificationReason]
enumFromThen :: NotificationReason -> NotificationReason -> [NotificationReason]
$cenumFromThen :: NotificationReason -> NotificationReason -> [NotificationReason]
enumFrom :: NotificationReason -> [NotificationReason]
$cenumFrom :: NotificationReason -> [NotificationReason]
fromEnum :: NotificationReason -> Int
$cfromEnum :: NotificationReason -> Int
toEnum :: Int -> NotificationReason
$ctoEnum :: Int -> NotificationReason
pred :: NotificationReason -> NotificationReason
$cpred :: NotificationReason -> NotificationReason
succ :: NotificationReason -> NotificationReason
$csucc :: NotificationReason -> NotificationReason
Enum, NotificationReason
NotificationReason
-> NotificationReason -> Bounded NotificationReason
forall a. a -> a -> Bounded a
maxBound :: NotificationReason
$cmaxBound :: NotificationReason
minBound :: NotificationReason
$cminBound :: NotificationReason
Bounded, Typeable, NotificationReason -> NotificationReason -> Bool
(NotificationReason -> NotificationReason -> Bool)
-> (NotificationReason -> NotificationReason -> Bool)
-> Eq NotificationReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotificationReason -> NotificationReason -> Bool
$c/= :: NotificationReason -> NotificationReason -> Bool
== :: NotificationReason -> NotificationReason -> Bool
$c== :: NotificationReason -> NotificationReason -> Bool
Eq, Eq NotificationReason
Eq NotificationReason
-> (NotificationReason -> NotificationReason -> Ordering)
-> (NotificationReason -> NotificationReason -> Bool)
-> (NotificationReason -> NotificationReason -> Bool)
-> (NotificationReason -> NotificationReason -> Bool)
-> (NotificationReason -> NotificationReason -> Bool)
-> (NotificationReason -> NotificationReason -> NotificationReason)
-> (NotificationReason -> NotificationReason -> NotificationReason)
-> Ord NotificationReason
NotificationReason -> NotificationReason -> Bool
NotificationReason -> NotificationReason -> Ordering
NotificationReason -> NotificationReason -> NotificationReason
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 :: NotificationReason -> NotificationReason -> NotificationReason
$cmin :: NotificationReason -> NotificationReason -> NotificationReason
max :: NotificationReason -> NotificationReason -> NotificationReason
$cmax :: NotificationReason -> NotificationReason -> NotificationReason
>= :: NotificationReason -> NotificationReason -> Bool
$c>= :: NotificationReason -> NotificationReason -> Bool
> :: NotificationReason -> NotificationReason -> Bool
$c> :: NotificationReason -> NotificationReason -> Bool
<= :: NotificationReason -> NotificationReason -> Bool
$c<= :: NotificationReason -> NotificationReason -> Bool
< :: NotificationReason -> NotificationReason -> Bool
$c< :: NotificationReason -> NotificationReason -> Bool
compare :: NotificationReason -> NotificationReason -> Ordering
$ccompare :: NotificationReason -> NotificationReason -> Ordering
$cp1Ord :: Eq NotificationReason
Ord, (forall x. NotificationReason -> Rep NotificationReason x)
-> (forall x. Rep NotificationReason x -> NotificationReason)
-> Generic NotificationReason
forall x. Rep NotificationReason x -> NotificationReason
forall x. NotificationReason -> Rep NotificationReason x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NotificationReason x -> NotificationReason
$cfrom :: forall x. NotificationReason -> Rep NotificationReason x
Generic)

instance NFData NotificationReason where rnf :: NotificationReason -> ()
rnf = NotificationReason -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary NotificationReason

instance FromJSON NotificationReason where
    parseJSON :: Value -> Parser NotificationReason
parseJSON = String
-> (Text -> Parser NotificationReason)
-> Value
-> Parser NotificationReason
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"NotificationReason" ((Text -> Parser NotificationReason)
 -> Value -> Parser NotificationReason)
-> (Text -> Parser NotificationReason)
-> Value
-> Parser NotificationReason
forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text -> Text
T.toLower Text
t of
        Text
"assign"           -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
AssignReason
        Text
"author"           -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
AuthorReason
        Text
"comment"          -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
CommentReason
        Text
"invitation"       -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
InvitationReason
        Text
"manual"           -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
ManualReason
        Text
"mention"          -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
MentionReason
        Text
"review_requested" -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
ReviewRequestedReason
        Text
"state_change"     -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
StateChangeReason
        Text
"subscribed"       -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
SubscribedReason
        Text
"team_mention"     -> NotificationReason -> Parser NotificationReason
forall (f :: * -> *) a. Applicative f => a -> f a
pure NotificationReason
TeamMentionReason
        Text
_                  -> String -> Parser NotificationReason
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser NotificationReason)
-> String -> Parser NotificationReason
forall a b. (a -> b) -> a -> b
$ String
"Unknown NotificationReason " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t

data Notification = Notification
    -- XXX: The notification id field type IS in fact string. Not sure why gh
    -- chose to do this when all the other ids are Numbers...
    { Notification -> Id Notification
notificationId :: !(Id Notification)
    , Notification -> RepoRef
notificationRepo :: !RepoRef
    , Notification -> Subject
notificationSubject :: !Subject
    , Notification -> NotificationReason
notificationReason :: !NotificationReason
    , Notification -> Bool
notificationUnread :: !Bool
    , Notification -> Maybe UTCTime
notificationUpdatedAt :: !(Maybe UTCTime)
    , Notification -> Maybe UTCTime
notificationLastReadAt :: !(Maybe UTCTime)
    , Notification -> URL
notificationUrl :: !URL
    }
  deriving (Int -> Notification -> ShowS
[Notification] -> ShowS
Notification -> String
(Int -> Notification -> ShowS)
-> (Notification -> String)
-> ([Notification] -> ShowS)
-> Show Notification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Notification] -> ShowS
$cshowList :: [Notification] -> ShowS
show :: Notification -> String
$cshow :: Notification -> String
showsPrec :: Int -> Notification -> ShowS
$cshowsPrec :: Int -> Notification -> ShowS
Show, Typeable Notification
DataType
Constr
Typeable Notification
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Notification -> c Notification)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Notification)
-> (Notification -> Constr)
-> (Notification -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Notification))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c Notification))
-> ((forall b. Data b => b -> b) -> Notification -> Notification)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Notification -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Notification -> r)
-> (forall u. (forall d. Data d => d -> u) -> Notification -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Notification -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Notification -> m Notification)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Notification -> m Notification)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Notification -> m Notification)
-> Data Notification
Notification -> DataType
Notification -> Constr
(forall b. Data b => b -> b) -> Notification -> Notification
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Notification -> c Notification
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Notification
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Notification -> u
forall u. (forall d. Data d => d -> u) -> Notification -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Notification -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Notification -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Notification -> m Notification
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Notification -> m Notification
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Notification
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Notification -> c Notification
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Notification)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Notification)
$cNotification :: Constr
$tNotification :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Notification -> m Notification
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Notification -> m Notification
gmapMp :: (forall d. Data d => d -> m d) -> Notification -> m Notification
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Notification -> m Notification
gmapM :: (forall d. Data d => d -> m d) -> Notification -> m Notification
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Notification -> m Notification
gmapQi :: Int -> (forall d. Data d => d -> u) -> Notification -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Notification -> u
gmapQ :: (forall d. Data d => d -> u) -> Notification -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Notification -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Notification -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Notification -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Notification -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Notification -> r
gmapT :: (forall b. Data b => b -> b) -> Notification -> Notification
$cgmapT :: (forall b. Data b => b -> b) -> Notification -> Notification
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Notification)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Notification)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Notification)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Notification)
dataTypeOf :: Notification -> DataType
$cdataTypeOf :: Notification -> DataType
toConstr :: Notification -> Constr
$ctoConstr :: Notification -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Notification
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Notification
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Notification -> c Notification
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Notification -> c Notification
$cp1Data :: Typeable Notification
Data, Typeable, Notification -> Notification -> Bool
(Notification -> Notification -> Bool)
-> (Notification -> Notification -> Bool) -> Eq Notification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Notification -> Notification -> Bool
$c/= :: Notification -> Notification -> Bool
== :: Notification -> Notification -> Bool
$c== :: Notification -> Notification -> Bool
Eq, Eq Notification
Eq Notification
-> (Notification -> Notification -> Ordering)
-> (Notification -> Notification -> Bool)
-> (Notification -> Notification -> Bool)
-> (Notification -> Notification -> Bool)
-> (Notification -> Notification -> Bool)
-> (Notification -> Notification -> Notification)
-> (Notification -> Notification -> Notification)
-> Ord Notification
Notification -> Notification -> Bool
Notification -> Notification -> Ordering
Notification -> Notification -> Notification
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 :: Notification -> Notification -> Notification
$cmin :: Notification -> Notification -> Notification
max :: Notification -> Notification -> Notification
$cmax :: Notification -> Notification -> Notification
>= :: Notification -> Notification -> Bool
$c>= :: Notification -> Notification -> Bool
> :: Notification -> Notification -> Bool
$c> :: Notification -> Notification -> Bool
<= :: Notification -> Notification -> Bool
$c<= :: Notification -> Notification -> Bool
< :: Notification -> Notification -> Bool
$c< :: Notification -> Notification -> Bool
compare :: Notification -> Notification -> Ordering
$ccompare :: Notification -> Notification -> Ordering
$cp1Ord :: Eq Notification
Ord, (forall x. Notification -> Rep Notification x)
-> (forall x. Rep Notification x -> Notification)
-> Generic Notification
forall x. Rep Notification x -> Notification
forall x. Notification -> Rep Notification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Notification x -> Notification
$cfrom :: forall x. Notification -> Rep Notification x
Generic)

instance NFData Notification where rnf :: Notification -> ()
rnf = Notification -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Notification

instance FromJSON Notification where
    parseJSON :: Value -> Parser Notification
parseJSON = String
-> (Object -> Parser Notification) -> Value -> Parser Notification
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Notification" ((Object -> Parser Notification) -> Value -> Parser Notification)
-> (Object -> Parser Notification) -> Value -> Parser Notification
forall a b. (a -> b) -> a -> b
$ \Object
o -> Id Notification
-> RepoRef
-> Subject
-> NotificationReason
-> Bool
-> Maybe UTCTime
-> Maybe UTCTime
-> URL
-> Notification
Notification
        (Id Notification
 -> RepoRef
 -> Subject
 -> NotificationReason
 -> Bool
 -> Maybe UTCTime
 -> Maybe UTCTime
 -> URL
 -> Notification)
-> Parser (Id Notification)
-> Parser
     (RepoRef
      -> Subject
      -> NotificationReason
      -> Bool
      -> Maybe UTCTime
      -> Maybe UTCTime
      -> URL
      -> Notification)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Any Notification -> Int -> Id Notification
forall (proxy :: * -> *) entity. proxy entity -> Int -> Id entity
mkId Any Notification
forall a. HasCallStack => a
undefined (Int -> Id Notification)
-> (String -> Int) -> String -> Id Notification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Int
forall a. Read a => String -> a
read (String -> Id Notification)
-> Parser String -> Parser (Id Notification)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id")
        Parser
  (RepoRef
   -> Subject
   -> NotificationReason
   -> Bool
   -> Maybe UTCTime
   -> Maybe UTCTime
   -> URL
   -> Notification)
-> Parser RepoRef
-> Parser
     (Subject
      -> NotificationReason
      -> Bool
      -> Maybe UTCTime
      -> Maybe UTCTime
      -> URL
      -> Notification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser RepoRef
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"repository"
        Parser
  (Subject
   -> NotificationReason
   -> Bool
   -> Maybe UTCTime
   -> Maybe UTCTime
   -> URL
   -> Notification)
-> Parser Subject
-> Parser
     (NotificationReason
      -> Bool -> Maybe UTCTime -> Maybe UTCTime -> URL -> Notification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Subject
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"subject"
        Parser
  (NotificationReason
   -> Bool -> Maybe UTCTime -> Maybe UTCTime -> URL -> Notification)
-> Parser NotificationReason
-> Parser
     (Bool -> Maybe UTCTime -> Maybe UTCTime -> URL -> Notification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser NotificationReason
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"reason"
        Parser
  (Bool -> Maybe UTCTime -> Maybe UTCTime -> URL -> Notification)
-> Parser Bool
-> Parser (Maybe UTCTime -> Maybe UTCTime -> URL -> Notification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"unread"
        Parser (Maybe UTCTime -> Maybe UTCTime -> URL -> Notification)
-> Parser (Maybe UTCTime)
-> Parser (Maybe UTCTime -> URL -> Notification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe UTCTime)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"updated_at"
        Parser (Maybe UTCTime -> URL -> Notification)
-> Parser (Maybe UTCTime) -> Parser (URL -> Notification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe UTCTime)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"last_read_at"
        Parser (URL -> Notification) -> Parser URL -> Parser Notification
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser URL
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"