{-# LANGUAGE InstanceSigs #-}
module GitHub.Data.Reactions where
import qualified Data.Text as T
import GitHub.Data.Id (Id)
import GitHub.Data.Definitions (SimpleUser)
import GitHub.Internal.Prelude
import Prelude ()
data Reaction = Reaction
{ Reaction -> Id Reaction
reactionId :: Id Reaction
, Reaction -> Maybe SimpleUser
reactionUser :: !(Maybe SimpleUser)
, Reaction -> ReactionContent
reactionContent :: !ReactionContent
, Reaction -> UTCTime
reactionCreatedAt :: !UTCTime
}
deriving (Int -> Reaction -> ShowS
[Reaction] -> ShowS
Reaction -> String
(Int -> Reaction -> ShowS)
-> (Reaction -> String) -> ([Reaction] -> ShowS) -> Show Reaction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Reaction -> ShowS
showsPrec :: Int -> Reaction -> ShowS
$cshow :: Reaction -> String
show :: Reaction -> String
$cshowList :: [Reaction] -> ShowS
showList :: [Reaction] -> ShowS
Show, Typeable Reaction
Typeable Reaction =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reaction -> c Reaction)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reaction)
-> (Reaction -> Constr)
-> (Reaction -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Reaction))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reaction))
-> ((forall b. Data b => b -> b) -> Reaction -> Reaction)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Reaction -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reaction -> r)
-> (forall u. (forall d. Data d => d -> u) -> Reaction -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Reaction -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction)
-> Data Reaction
Reaction -> Constr
Reaction -> DataType
(forall b. Data b => b -> b) -> Reaction -> Reaction
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) -> Reaction -> u
forall u. (forall d. Data d => d -> u) -> Reaction -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Reaction -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reaction -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reaction
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reaction -> c Reaction
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Reaction)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reaction)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reaction -> c Reaction
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Reaction -> c Reaction
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reaction
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Reaction
$ctoConstr :: Reaction -> Constr
toConstr :: Reaction -> Constr
$cdataTypeOf :: Reaction -> DataType
dataTypeOf :: Reaction -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Reaction)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Reaction)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reaction)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reaction)
$cgmapT :: (forall b. Data b => b -> b) -> Reaction -> Reaction
gmapT :: (forall b. Data b => b -> b) -> Reaction -> Reaction
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Reaction -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Reaction -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reaction -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Reaction -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Reaction -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Reaction -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Reaction -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Reaction -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Reaction -> m Reaction
Data, Typeable, Reaction -> Reaction -> Bool
(Reaction -> Reaction -> Bool)
-> (Reaction -> Reaction -> Bool) -> Eq Reaction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Reaction -> Reaction -> Bool
== :: Reaction -> Reaction -> Bool
$c/= :: Reaction -> Reaction -> Bool
/= :: Reaction -> Reaction -> Bool
Eq, Eq Reaction
Eq Reaction =>
(Reaction -> Reaction -> Ordering)
-> (Reaction -> Reaction -> Bool)
-> (Reaction -> Reaction -> Bool)
-> (Reaction -> Reaction -> Bool)
-> (Reaction -> Reaction -> Bool)
-> (Reaction -> Reaction -> Reaction)
-> (Reaction -> Reaction -> Reaction)
-> Ord Reaction
Reaction -> Reaction -> Bool
Reaction -> Reaction -> Ordering
Reaction -> Reaction -> Reaction
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
$ccompare :: Reaction -> Reaction -> Ordering
compare :: Reaction -> Reaction -> Ordering
$c< :: Reaction -> Reaction -> Bool
< :: Reaction -> Reaction -> Bool
$c<= :: Reaction -> Reaction -> Bool
<= :: Reaction -> Reaction -> Bool
$c> :: Reaction -> Reaction -> Bool
> :: Reaction -> Reaction -> Bool
$c>= :: Reaction -> Reaction -> Bool
>= :: Reaction -> Reaction -> Bool
$cmax :: Reaction -> Reaction -> Reaction
max :: Reaction -> Reaction -> Reaction
$cmin :: Reaction -> Reaction -> Reaction
min :: Reaction -> Reaction -> Reaction
Ord, (forall x. Reaction -> Rep Reaction x)
-> (forall x. Rep Reaction x -> Reaction) -> Generic Reaction
forall x. Rep Reaction x -> Reaction
forall x. Reaction -> Rep Reaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Reaction -> Rep Reaction x
from :: forall x. Reaction -> Rep Reaction x
$cto :: forall x. Rep Reaction x -> Reaction
to :: forall x. Rep Reaction x -> Reaction
Generic)
instance NFData Reaction where rnf :: Reaction -> ()
rnf = Reaction -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Reaction
data NewReaction = NewReaction
{ NewReaction -> ReactionContent
newReactionContent :: !ReactionContent
}
deriving (Int -> NewReaction -> ShowS
[NewReaction] -> ShowS
NewReaction -> String
(Int -> NewReaction -> ShowS)
-> (NewReaction -> String)
-> ([NewReaction] -> ShowS)
-> Show NewReaction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NewReaction -> ShowS
showsPrec :: Int -> NewReaction -> ShowS
$cshow :: NewReaction -> String
show :: NewReaction -> String
$cshowList :: [NewReaction] -> ShowS
showList :: [NewReaction] -> ShowS
Show, Typeable NewReaction
Typeable NewReaction =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewReaction -> c NewReaction)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewReaction)
-> (NewReaction -> Constr)
-> (NewReaction -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewReaction))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewReaction))
-> ((forall b. Data b => b -> b) -> NewReaction -> NewReaction)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewReaction -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewReaction -> r)
-> (forall u. (forall d. Data d => d -> u) -> NewReaction -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> NewReaction -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction)
-> Data NewReaction
NewReaction -> Constr
NewReaction -> DataType
(forall b. Data b => b -> b) -> NewReaction -> NewReaction
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) -> NewReaction -> u
forall u. (forall d. Data d => d -> u) -> NewReaction -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewReaction -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewReaction -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewReaction
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewReaction -> c NewReaction
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewReaction)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewReaction)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewReaction -> c NewReaction
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewReaction -> c NewReaction
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewReaction
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewReaction
$ctoConstr :: NewReaction -> Constr
toConstr :: NewReaction -> Constr
$cdataTypeOf :: NewReaction -> DataType
dataTypeOf :: NewReaction -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewReaction)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewReaction)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewReaction)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewReaction)
$cgmapT :: (forall b. Data b => b -> b) -> NewReaction -> NewReaction
gmapT :: (forall b. Data b => b -> b) -> NewReaction -> NewReaction
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewReaction -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewReaction -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewReaction -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewReaction -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewReaction -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> NewReaction -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewReaction -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewReaction -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewReaction -> m NewReaction
Data, Typeable, NewReaction -> NewReaction -> Bool
(NewReaction -> NewReaction -> Bool)
-> (NewReaction -> NewReaction -> Bool) -> Eq NewReaction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NewReaction -> NewReaction -> Bool
== :: NewReaction -> NewReaction -> Bool
$c/= :: NewReaction -> NewReaction -> Bool
/= :: NewReaction -> NewReaction -> Bool
Eq, Eq NewReaction
Eq NewReaction =>
(NewReaction -> NewReaction -> Ordering)
-> (NewReaction -> NewReaction -> Bool)
-> (NewReaction -> NewReaction -> Bool)
-> (NewReaction -> NewReaction -> Bool)
-> (NewReaction -> NewReaction -> Bool)
-> (NewReaction -> NewReaction -> NewReaction)
-> (NewReaction -> NewReaction -> NewReaction)
-> Ord NewReaction
NewReaction -> NewReaction -> Bool
NewReaction -> NewReaction -> Ordering
NewReaction -> NewReaction -> NewReaction
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
$ccompare :: NewReaction -> NewReaction -> Ordering
compare :: NewReaction -> NewReaction -> Ordering
$c< :: NewReaction -> NewReaction -> Bool
< :: NewReaction -> NewReaction -> Bool
$c<= :: NewReaction -> NewReaction -> Bool
<= :: NewReaction -> NewReaction -> Bool
$c> :: NewReaction -> NewReaction -> Bool
> :: NewReaction -> NewReaction -> Bool
$c>= :: NewReaction -> NewReaction -> Bool
>= :: NewReaction -> NewReaction -> Bool
$cmax :: NewReaction -> NewReaction -> NewReaction
max :: NewReaction -> NewReaction -> NewReaction
$cmin :: NewReaction -> NewReaction -> NewReaction
min :: NewReaction -> NewReaction -> NewReaction
Ord, (forall x. NewReaction -> Rep NewReaction x)
-> (forall x. Rep NewReaction x -> NewReaction)
-> Generic NewReaction
forall x. Rep NewReaction x -> NewReaction
forall x. NewReaction -> Rep NewReaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NewReaction -> Rep NewReaction x
from :: forall x. NewReaction -> Rep NewReaction x
$cto :: forall x. Rep NewReaction x -> NewReaction
to :: forall x. Rep NewReaction x -> NewReaction
Generic)
instance NFData NewReaction where rnf :: NewReaction -> ()
rnf = NewReaction -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary NewReaction
data ReactionContent
= PlusOne
| MinusOne
| Laugh
| Confused
| Heart
| Hooray
| Rocket
| Eyes
deriving (Int -> ReactionContent -> ShowS
[ReactionContent] -> ShowS
ReactionContent -> String
(Int -> ReactionContent -> ShowS)
-> (ReactionContent -> String)
-> ([ReactionContent] -> ShowS)
-> Show ReactionContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReactionContent -> ShowS
showsPrec :: Int -> ReactionContent -> ShowS
$cshow :: ReactionContent -> String
show :: ReactionContent -> String
$cshowList :: [ReactionContent] -> ShowS
showList :: [ReactionContent] -> ShowS
Show, Typeable ReactionContent
Typeable ReactionContent =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReactionContent -> c ReactionContent)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReactionContent)
-> (ReactionContent -> Constr)
-> (ReactionContent -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReactionContent))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReactionContent))
-> ((forall b. Data b => b -> b)
-> ReactionContent -> ReactionContent)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReactionContent -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReactionContent -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ReactionContent -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ReactionContent -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent)
-> Data ReactionContent
ReactionContent -> Constr
ReactionContent -> DataType
(forall b. Data b => b -> b) -> ReactionContent -> ReactionContent
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) -> ReactionContent -> u
forall u. (forall d. Data d => d -> u) -> ReactionContent -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReactionContent -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReactionContent -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReactionContent
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReactionContent -> c ReactionContent
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReactionContent)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReactionContent)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReactionContent -> c ReactionContent
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReactionContent -> c ReactionContent
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReactionContent
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReactionContent
$ctoConstr :: ReactionContent -> Constr
toConstr :: ReactionContent -> Constr
$cdataTypeOf :: ReactionContent -> DataType
dataTypeOf :: ReactionContent -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReactionContent)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReactionContent)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReactionContent)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReactionContent)
$cgmapT :: (forall b. Data b => b -> b) -> ReactionContent -> ReactionContent
gmapT :: (forall b. Data b => b -> b) -> ReactionContent -> ReactionContent
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReactionContent -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReactionContent -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReactionContent -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReactionContent -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ReactionContent -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ReactionContent -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ReactionContent -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ReactionContent -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ReactionContent -> m ReactionContent
Data, Typeable, ReactionContent -> ReactionContent -> Bool
(ReactionContent -> ReactionContent -> Bool)
-> (ReactionContent -> ReactionContent -> Bool)
-> Eq ReactionContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReactionContent -> ReactionContent -> Bool
== :: ReactionContent -> ReactionContent -> Bool
$c/= :: ReactionContent -> ReactionContent -> Bool
/= :: ReactionContent -> ReactionContent -> Bool
Eq, Eq ReactionContent
Eq ReactionContent =>
(ReactionContent -> ReactionContent -> Ordering)
-> (ReactionContent -> ReactionContent -> Bool)
-> (ReactionContent -> ReactionContent -> Bool)
-> (ReactionContent -> ReactionContent -> Bool)
-> (ReactionContent -> ReactionContent -> Bool)
-> (ReactionContent -> ReactionContent -> ReactionContent)
-> (ReactionContent -> ReactionContent -> ReactionContent)
-> Ord ReactionContent
ReactionContent -> ReactionContent -> Bool
ReactionContent -> ReactionContent -> Ordering
ReactionContent -> ReactionContent -> ReactionContent
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
$ccompare :: ReactionContent -> ReactionContent -> Ordering
compare :: ReactionContent -> ReactionContent -> Ordering
$c< :: ReactionContent -> ReactionContent -> Bool
< :: ReactionContent -> ReactionContent -> Bool
$c<= :: ReactionContent -> ReactionContent -> Bool
<= :: ReactionContent -> ReactionContent -> Bool
$c> :: ReactionContent -> ReactionContent -> Bool
> :: ReactionContent -> ReactionContent -> Bool
$c>= :: ReactionContent -> ReactionContent -> Bool
>= :: ReactionContent -> ReactionContent -> Bool
$cmax :: ReactionContent -> ReactionContent -> ReactionContent
max :: ReactionContent -> ReactionContent -> ReactionContent
$cmin :: ReactionContent -> ReactionContent -> ReactionContent
min :: ReactionContent -> ReactionContent -> ReactionContent
Ord, Int -> ReactionContent
ReactionContent -> Int
ReactionContent -> [ReactionContent]
ReactionContent -> ReactionContent
ReactionContent -> ReactionContent -> [ReactionContent]
ReactionContent
-> ReactionContent -> ReactionContent -> [ReactionContent]
(ReactionContent -> ReactionContent)
-> (ReactionContent -> ReactionContent)
-> (Int -> ReactionContent)
-> (ReactionContent -> Int)
-> (ReactionContent -> [ReactionContent])
-> (ReactionContent -> ReactionContent -> [ReactionContent])
-> (ReactionContent -> ReactionContent -> [ReactionContent])
-> (ReactionContent
-> ReactionContent -> ReactionContent -> [ReactionContent])
-> Enum ReactionContent
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ReactionContent -> ReactionContent
succ :: ReactionContent -> ReactionContent
$cpred :: ReactionContent -> ReactionContent
pred :: ReactionContent -> ReactionContent
$ctoEnum :: Int -> ReactionContent
toEnum :: Int -> ReactionContent
$cfromEnum :: ReactionContent -> Int
fromEnum :: ReactionContent -> Int
$cenumFrom :: ReactionContent -> [ReactionContent]
enumFrom :: ReactionContent -> [ReactionContent]
$cenumFromThen :: ReactionContent -> ReactionContent -> [ReactionContent]
enumFromThen :: ReactionContent -> ReactionContent -> [ReactionContent]
$cenumFromTo :: ReactionContent -> ReactionContent -> [ReactionContent]
enumFromTo :: ReactionContent -> ReactionContent -> [ReactionContent]
$cenumFromThenTo :: ReactionContent
-> ReactionContent -> ReactionContent -> [ReactionContent]
enumFromThenTo :: ReactionContent
-> ReactionContent -> ReactionContent -> [ReactionContent]
Enum, ReactionContent
ReactionContent -> ReactionContent -> Bounded ReactionContent
forall a. a -> a -> Bounded a
$cminBound :: ReactionContent
minBound :: ReactionContent
$cmaxBound :: ReactionContent
maxBound :: ReactionContent
Bounded, (forall x. ReactionContent -> Rep ReactionContent x)
-> (forall x. Rep ReactionContent x -> ReactionContent)
-> Generic ReactionContent
forall x. Rep ReactionContent x -> ReactionContent
forall x. ReactionContent -> Rep ReactionContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReactionContent -> Rep ReactionContent x
from :: forall x. ReactionContent -> Rep ReactionContent x
$cto :: forall x. Rep ReactionContent x -> ReactionContent
to :: forall x. Rep ReactionContent x -> ReactionContent
Generic)
instance NFData ReactionContent where rnf :: ReactionContent -> ()
rnf = ReactionContent -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary ReactionContent
instance FromJSON Reaction where
parseJSON :: Value -> Parser Reaction
parseJSON = String -> (Object -> Parser Reaction) -> Value -> Parser Reaction
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Reaction" ((Object -> Parser Reaction) -> Value -> Parser Reaction)
-> (Object -> Parser Reaction) -> Value -> Parser Reaction
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Id Reaction
-> Maybe SimpleUser -> ReactionContent -> UTCTime -> Reaction
Reaction
(Id Reaction
-> Maybe SimpleUser -> ReactionContent -> UTCTime -> Reaction)
-> Parser (Id Reaction)
-> Parser
(Maybe SimpleUser -> ReactionContent -> UTCTime -> Reaction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Id Reaction)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser (Maybe SimpleUser -> ReactionContent -> UTCTime -> Reaction)
-> Parser (Maybe SimpleUser)
-> Parser (ReactionContent -> UTCTime -> Reaction)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe SimpleUser)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"user"
Parser (ReactionContent -> UTCTime -> Reaction)
-> Parser ReactionContent -> Parser (UTCTime -> Reaction)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser ReactionContent
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"content"
Parser (UTCTime -> Reaction) -> Parser UTCTime -> Parser Reaction
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser UTCTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created_at"
instance ToJSON NewReaction where
toJSON :: NewReaction -> Value
toJSON (NewReaction ReactionContent
content) = [Pair] -> Value
object [Key
"content" Key -> ReactionContent -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ReactionContent
content]
instance FromJSON ReactionContent where
parseJSON :: Value -> Parser ReactionContent
parseJSON = String
-> (Text -> Parser ReactionContent)
-> Value
-> Parser ReactionContent
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"ReactionContent" ((Text -> Parser ReactionContent)
-> Value -> Parser ReactionContent)
-> (Text -> Parser ReactionContent)
-> Value
-> Parser ReactionContent
forall a b. (a -> b) -> a -> b
$ \case
Text
"+1" -> ReactionContent -> Parser ReactionContent
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReactionContent
PlusOne
Text
"-1" -> ReactionContent -> Parser ReactionContent
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReactionContent
MinusOne
Text
"laugh" -> ReactionContent -> Parser ReactionContent
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReactionContent
Laugh
Text
"confused" -> ReactionContent -> Parser ReactionContent
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReactionContent
Confused
Text
"heart" -> ReactionContent -> Parser ReactionContent
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReactionContent
Heart
Text
"hooray" -> ReactionContent -> Parser ReactionContent
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReactionContent
Hooray
Text
"rocket" -> ReactionContent -> Parser ReactionContent
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReactionContent
Rocket
Text
"eyes" -> ReactionContent -> Parser ReactionContent
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReactionContent
Eyes
Text
t -> String -> Parser ReactionContent
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ReactionContent)
-> String -> Parser ReactionContent
forall a b. (a -> b) -> a -> b
$ String
"Unknown ReactionContent: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
t
instance ToJSON ReactionContent where
toJSON :: ReactionContent -> Value
toJSON ReactionContent
PlusOne = Text -> Value
String Text
"+1"
toJSON ReactionContent
MinusOne = Text -> Value
String Text
"-1"
toJSON ReactionContent
Laugh = Text -> Value
String Text
"laugh"
toJSON ReactionContent
Confused = Text -> Value
String Text
"confused"
toJSON ReactionContent
Heart = Text -> Value
String Text
"heart"
toJSON ReactionContent
Hooray = Text -> Value
String Text
"hooray"
toJSON ReactionContent
Rocket = Text -> Value
String Text
"rocket"
toJSON ReactionContent
Eyes = Text -> Value
String Text
"eyes"