module GitHub.Data.Comments where
import GitHub.Data.Definitions
import GitHub.Data.Id (Id)
import GitHub.Data.URL (URL)
import GitHub.Internal.Prelude
import Prelude ()
data =
{ :: !(Maybe Int)
, :: !(Maybe Int)
, Comment -> Text
commentBody :: !Text
, :: !(Maybe Text)
, :: !UTCTime
, :: !(Maybe URL)
, :: !URL
, :: !(Maybe UTCTime)
, :: !(Maybe Text)
, :: !SimpleUser
, :: !(Id Comment)
}
deriving (Int -> Comment -> ShowS
[Comment] -> ShowS
Comment -> String
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, Typeable Comment
Comment -> DataType
Comment -> Constr
(forall b. Data b => b -> b) -> Comment -> Comment
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) -> Comment -> u
forall u. (forall d. Data d => d -> u) -> Comment -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Comment -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Comment -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Comment -> m Comment
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Comment -> m Comment
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Comment
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Comment -> c Comment
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Comment)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Comment)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Comment -> m Comment
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Comment -> m Comment
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Comment -> m Comment
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Comment -> m Comment
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Comment -> m Comment
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Comment -> m Comment
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Comment -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Comment -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Comment -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Comment -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Comment -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Comment -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Comment -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Comment -> r
gmapT :: (forall b. Data b => b -> b) -> Comment -> Comment
$cgmapT :: (forall b. Data b => b -> b) -> Comment -> Comment
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Comment)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Comment)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Comment)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Comment)
dataTypeOf :: Comment -> DataType
$cdataTypeOf :: Comment -> DataType
toConstr :: Comment -> Constr
$ctoConstr :: Comment -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Comment
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Comment
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Comment -> c Comment
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Comment -> c Comment
Data, Typeable, Comment -> Comment -> Bool
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, Eq Comment
Comment -> Comment -> Bool
Comment -> Comment -> Ordering
Comment -> Comment -> Comment
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 :: Comment -> Comment -> Comment
$cmin :: Comment -> Comment -> Comment
max :: Comment -> Comment -> Comment
$cmax :: Comment -> Comment -> Comment
>= :: Comment -> Comment -> Bool
$c>= :: Comment -> Comment -> Bool
> :: Comment -> Comment -> Bool
$c> :: Comment -> Comment -> Bool
<= :: Comment -> Comment -> Bool
$c<= :: Comment -> Comment -> Bool
< :: Comment -> Comment -> Bool
$c< :: Comment -> Comment -> Bool
compare :: Comment -> Comment -> Ordering
$ccompare :: Comment -> Comment -> Ordering
Ord, forall x. Rep Comment x -> Comment
forall x. Comment -> Rep Comment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Comment x -> Comment
$cfrom :: forall x. Comment -> Rep Comment x
Generic)
instance NFData Comment where rnf :: Comment -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Comment
instance FromJSON Comment where
parseJSON :: Value -> Parser Comment
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Comment" forall a b. (a -> b) -> a -> b
$ \Object
o -> Maybe Int
-> Maybe Int
-> Text
-> Maybe Text
-> UTCTime
-> Maybe URL
-> URL
-> Maybe UTCTime
-> Maybe Text
-> SimpleUser
-> Id Comment
-> Comment
Comment
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"position"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"line"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"body"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"commit_id"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"updated_at"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"html_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created_at"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"path"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
data =
{ NewComment -> Text
newCommentBody :: !Text
}
deriving (Int -> NewComment -> ShowS
[NewComment] -> ShowS
NewComment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewComment] -> ShowS
$cshowList :: [NewComment] -> ShowS
show :: NewComment -> String
$cshow :: NewComment -> String
showsPrec :: Int -> NewComment -> ShowS
$cshowsPrec :: Int -> NewComment -> ShowS
Show, Typeable NewComment
NewComment -> DataType
NewComment -> Constr
(forall b. Data b => b -> b) -> NewComment -> NewComment
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) -> NewComment -> u
forall u. (forall d. Data d => d -> u) -> NewComment -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewComment -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewComment -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewComment -> m NewComment
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewComment -> m NewComment
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewComment
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewComment -> c NewComment
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewComment)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewComment)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewComment -> m NewComment
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewComment -> m NewComment
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewComment -> m NewComment
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewComment -> m NewComment
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewComment -> m NewComment
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewComment -> m NewComment
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewComment -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewComment -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NewComment -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewComment -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewComment -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewComment -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewComment -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewComment -> r
gmapT :: (forall b. Data b => b -> b) -> NewComment -> NewComment
$cgmapT :: (forall b. Data b => b -> b) -> NewComment -> NewComment
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewComment)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewComment)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewComment)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewComment)
dataTypeOf :: NewComment -> DataType
$cdataTypeOf :: NewComment -> DataType
toConstr :: NewComment -> Constr
$ctoConstr :: NewComment -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewComment
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewComment
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewComment -> c NewComment
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewComment -> c NewComment
Data, Typeable, NewComment -> NewComment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewComment -> NewComment -> Bool
$c/= :: NewComment -> NewComment -> Bool
== :: NewComment -> NewComment -> Bool
$c== :: NewComment -> NewComment -> Bool
Eq, Eq NewComment
NewComment -> NewComment -> Bool
NewComment -> NewComment -> Ordering
NewComment -> NewComment -> NewComment
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 :: NewComment -> NewComment -> NewComment
$cmin :: NewComment -> NewComment -> NewComment
max :: NewComment -> NewComment -> NewComment
$cmax :: NewComment -> NewComment -> NewComment
>= :: NewComment -> NewComment -> Bool
$c>= :: NewComment -> NewComment -> Bool
> :: NewComment -> NewComment -> Bool
$c> :: NewComment -> NewComment -> Bool
<= :: NewComment -> NewComment -> Bool
$c<= :: NewComment -> NewComment -> Bool
< :: NewComment -> NewComment -> Bool
$c< :: NewComment -> NewComment -> Bool
compare :: NewComment -> NewComment -> Ordering
$ccompare :: NewComment -> NewComment -> Ordering
Ord, forall x. Rep NewComment x -> NewComment
forall x. NewComment -> Rep NewComment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NewComment x -> NewComment
$cfrom :: forall x. NewComment -> Rep NewComment x
Generic)
instance NFData NewComment where rnf :: NewComment -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary NewComment
instance ToJSON NewComment where
toJSON :: NewComment -> Value
toJSON (NewComment Text
b) = [Pair] -> Value
object [ Key
"body" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
b ]
data =
{ EditComment -> Text
editCommentBody :: !Text
}
deriving (Int -> EditComment -> ShowS
[EditComment] -> ShowS
EditComment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditComment] -> ShowS
$cshowList :: [EditComment] -> ShowS
show :: EditComment -> String
$cshow :: EditComment -> String
showsPrec :: Int -> EditComment -> ShowS
$cshowsPrec :: Int -> EditComment -> ShowS
Show, Typeable EditComment
EditComment -> DataType
EditComment -> Constr
(forall b. Data b => b -> b) -> EditComment -> EditComment
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) -> EditComment -> u
forall u. (forall d. Data d => d -> u) -> EditComment -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EditComment -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EditComment -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EditComment -> m EditComment
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditComment -> m EditComment
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EditComment
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EditComment -> c EditComment
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EditComment)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EditComment)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditComment -> m EditComment
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditComment -> m EditComment
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditComment -> m EditComment
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditComment -> m EditComment
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EditComment -> m EditComment
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EditComment -> m EditComment
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> EditComment -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> EditComment -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> EditComment -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> EditComment -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EditComment -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EditComment -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EditComment -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EditComment -> r
gmapT :: (forall b. Data b => b -> b) -> EditComment -> EditComment
$cgmapT :: (forall b. Data b => b -> b) -> EditComment -> EditComment
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EditComment)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c EditComment)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EditComment)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EditComment)
dataTypeOf :: EditComment -> DataType
$cdataTypeOf :: EditComment -> DataType
toConstr :: EditComment -> Constr
$ctoConstr :: EditComment -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EditComment
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EditComment
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EditComment -> c EditComment
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EditComment -> c EditComment
Data, Typeable, EditComment -> EditComment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditComment -> EditComment -> Bool
$c/= :: EditComment -> EditComment -> Bool
== :: EditComment -> EditComment -> Bool
$c== :: EditComment -> EditComment -> Bool
Eq, Eq EditComment
EditComment -> EditComment -> Bool
EditComment -> EditComment -> Ordering
EditComment -> EditComment -> EditComment
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 :: EditComment -> EditComment -> EditComment
$cmin :: EditComment -> EditComment -> EditComment
max :: EditComment -> EditComment -> EditComment
$cmax :: EditComment -> EditComment -> EditComment
>= :: EditComment -> EditComment -> Bool
$c>= :: EditComment -> EditComment -> Bool
> :: EditComment -> EditComment -> Bool
$c> :: EditComment -> EditComment -> Bool
<= :: EditComment -> EditComment -> Bool
$c<= :: EditComment -> EditComment -> Bool
< :: EditComment -> EditComment -> Bool
$c< :: EditComment -> EditComment -> Bool
compare :: EditComment -> EditComment -> Ordering
$ccompare :: EditComment -> EditComment -> Ordering
Ord, forall x. Rep EditComment x -> EditComment
forall x. EditComment -> Rep EditComment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditComment x -> EditComment
$cfrom :: forall x. EditComment -> Rep EditComment x
Generic)
instance NFData EditComment where rnf :: EditComment -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary EditComment
instance ToJSON EditComment where
toJSON :: EditComment -> Value
toJSON (EditComment Text
b) = [Pair] -> Value
object [ Key
"body" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
b ]
data =
{ :: !Text
, :: !Text
, :: !Int
, NewPullComment -> Text
newPullCommentBody :: !Text
}
deriving (Int -> NewPullComment -> ShowS
[NewPullComment] -> ShowS
NewPullComment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewPullComment] -> ShowS
$cshowList :: [NewPullComment] -> ShowS
show :: NewPullComment -> String
$cshow :: NewPullComment -> String
showsPrec :: Int -> NewPullComment -> ShowS
$cshowsPrec :: Int -> NewPullComment -> ShowS
Show, Typeable NewPullComment
NewPullComment -> DataType
NewPullComment -> Constr
(forall b. Data b => b -> b) -> NewPullComment -> NewPullComment
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) -> NewPullComment -> u
forall u. (forall d. Data d => d -> u) -> NewPullComment -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewPullComment -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewPullComment -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NewPullComment -> m NewPullComment
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NewPullComment -> m NewPullComment
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewPullComment
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewPullComment -> c NewPullComment
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewPullComment)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewPullComment)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NewPullComment -> m NewPullComment
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NewPullComment -> m NewPullComment
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NewPullComment -> m NewPullComment
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NewPullComment -> m NewPullComment
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NewPullComment -> m NewPullComment
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NewPullComment -> m NewPullComment
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> NewPullComment -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> NewPullComment -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NewPullComment -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewPullComment -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewPullComment -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewPullComment -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewPullComment -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewPullComment -> r
gmapT :: (forall b. Data b => b -> b) -> NewPullComment -> NewPullComment
$cgmapT :: (forall b. Data b => b -> b) -> NewPullComment -> NewPullComment
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewPullComment)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NewPullComment)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewPullComment)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewPullComment)
dataTypeOf :: NewPullComment -> DataType
$cdataTypeOf :: NewPullComment -> DataType
toConstr :: NewPullComment -> Constr
$ctoConstr :: NewPullComment -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewPullComment
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewPullComment
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewPullComment -> c NewPullComment
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewPullComment -> c NewPullComment
Data, Typeable, NewPullComment -> NewPullComment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewPullComment -> NewPullComment -> Bool
$c/= :: NewPullComment -> NewPullComment -> Bool
== :: NewPullComment -> NewPullComment -> Bool
$c== :: NewPullComment -> NewPullComment -> Bool
Eq, Eq NewPullComment
NewPullComment -> NewPullComment -> Bool
NewPullComment -> NewPullComment -> Ordering
NewPullComment -> NewPullComment -> NewPullComment
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 :: NewPullComment -> NewPullComment -> NewPullComment
$cmin :: NewPullComment -> NewPullComment -> NewPullComment
max :: NewPullComment -> NewPullComment -> NewPullComment
$cmax :: NewPullComment -> NewPullComment -> NewPullComment
>= :: NewPullComment -> NewPullComment -> Bool
$c>= :: NewPullComment -> NewPullComment -> Bool
> :: NewPullComment -> NewPullComment -> Bool
$c> :: NewPullComment -> NewPullComment -> Bool
<= :: NewPullComment -> NewPullComment -> Bool
$c<= :: NewPullComment -> NewPullComment -> Bool
< :: NewPullComment -> NewPullComment -> Bool
$c< :: NewPullComment -> NewPullComment -> Bool
compare :: NewPullComment -> NewPullComment -> Ordering
$ccompare :: NewPullComment -> NewPullComment -> Ordering
Ord, forall x. Rep NewPullComment x -> NewPullComment
forall x. NewPullComment -> Rep NewPullComment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NewPullComment x -> NewPullComment
$cfrom :: forall x. NewPullComment -> Rep NewPullComment x
Generic)
instance NFData NewPullComment where rnf :: NewPullComment -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary NewPullComment
instance ToJSON NewPullComment where
toJSON :: NewPullComment -> Value
toJSON (NewPullComment Text
c Text
path Int
pos Text
b) =
[Pair] -> Value
object [ Key
"body" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
b
, Key
"commit_id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
c
, Key
"path" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
path
, Key
"position" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
pos
]
data =
{ PullCommentReply -> Text
pullCommentReplyBody :: Text
}
deriving (Int -> PullCommentReply -> ShowS
[PullCommentReply] -> ShowS
PullCommentReply -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PullCommentReply] -> ShowS
$cshowList :: [PullCommentReply] -> ShowS
show :: PullCommentReply -> String
$cshow :: PullCommentReply -> String
showsPrec :: Int -> PullCommentReply -> ShowS
$cshowsPrec :: Int -> PullCommentReply -> ShowS
Show, Typeable PullCommentReply
PullCommentReply -> DataType
PullCommentReply -> Constr
(forall b. Data b => b -> b)
-> PullCommentReply -> PullCommentReply
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) -> PullCommentReply -> u
forall u. (forall d. Data d => d -> u) -> PullCommentReply -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PullCommentReply -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PullCommentReply -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PullCommentReply -> m PullCommentReply
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullCommentReply -> m PullCommentReply
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PullCommentReply
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PullCommentReply -> c PullCommentReply
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PullCommentReply)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PullCommentReply)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullCommentReply -> m PullCommentReply
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullCommentReply -> m PullCommentReply
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullCommentReply -> m PullCommentReply
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullCommentReply -> m PullCommentReply
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PullCommentReply -> m PullCommentReply
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PullCommentReply -> m PullCommentReply
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PullCommentReply -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PullCommentReply -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PullCommentReply -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PullCommentReply -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PullCommentReply -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PullCommentReply -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PullCommentReply -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PullCommentReply -> r
gmapT :: (forall b. Data b => b -> b)
-> PullCommentReply -> PullCommentReply
$cgmapT :: (forall b. Data b => b -> b)
-> PullCommentReply -> PullCommentReply
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PullCommentReply)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PullCommentReply)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PullCommentReply)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PullCommentReply)
dataTypeOf :: PullCommentReply -> DataType
$cdataTypeOf :: PullCommentReply -> DataType
toConstr :: PullCommentReply -> Constr
$ctoConstr :: PullCommentReply -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PullCommentReply
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PullCommentReply
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PullCommentReply -> c PullCommentReply
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PullCommentReply -> c PullCommentReply
Data, Typeable, PullCommentReply -> PullCommentReply -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PullCommentReply -> PullCommentReply -> Bool
$c/= :: PullCommentReply -> PullCommentReply -> Bool
== :: PullCommentReply -> PullCommentReply -> Bool
$c== :: PullCommentReply -> PullCommentReply -> Bool
Eq, Eq PullCommentReply
PullCommentReply -> PullCommentReply -> Bool
PullCommentReply -> PullCommentReply -> Ordering
PullCommentReply -> PullCommentReply -> PullCommentReply
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 :: PullCommentReply -> PullCommentReply -> PullCommentReply
$cmin :: PullCommentReply -> PullCommentReply -> PullCommentReply
max :: PullCommentReply -> PullCommentReply -> PullCommentReply
$cmax :: PullCommentReply -> PullCommentReply -> PullCommentReply
>= :: PullCommentReply -> PullCommentReply -> Bool
$c>= :: PullCommentReply -> PullCommentReply -> Bool
> :: PullCommentReply -> PullCommentReply -> Bool
$c> :: PullCommentReply -> PullCommentReply -> Bool
<= :: PullCommentReply -> PullCommentReply -> Bool
$c<= :: PullCommentReply -> PullCommentReply -> Bool
< :: PullCommentReply -> PullCommentReply -> Bool
$c< :: PullCommentReply -> PullCommentReply -> Bool
compare :: PullCommentReply -> PullCommentReply -> Ordering
$ccompare :: PullCommentReply -> PullCommentReply -> Ordering
Ord, forall x. Rep PullCommentReply x -> PullCommentReply
forall x. PullCommentReply -> Rep PullCommentReply x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PullCommentReply x -> PullCommentReply
$cfrom :: forall x. PullCommentReply -> Rep PullCommentReply x
Generic)
instance NFData PullCommentReply where rnf :: PullCommentReply -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance ToJSON PullCommentReply where
toJSON :: PullCommentReply -> Value
toJSON (PullCommentReply Text
b) =
[Pair] -> Value
object [ Key
"body" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
b
]