{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Network.Reddit.Types.Comment
( Comment(..)
, CommentID(CommentID)
, MoreComments(..)
, ChildComment(..)
, WithChildren
, WithReplies
, commentP
, LoadedChildren
) where
import Control.Monad ( (<=<) )
import Data.Aeson
( (.:)
, (.:?)
, FromJSON(..)
, Object
, Value(Object, String)
, withArray
, withObject
, withText
)
import Data.Aeson.Types ( Parser )
import Data.Coerce ( coerce )
import Data.Generics.Product ( HasField(field) )
import Data.Sequence ( Seq((:<|)) )
import Data.Text ( Text )
import Data.Time ( UTCTime )
import GHC.Exts ( IsList(toList, fromList) )
import GHC.Generics ( Generic )
import Lens.Micro
import Network.Reddit.Types.Account
import Network.Reddit.Types.Internal
import Network.Reddit.Types.Submission ( SubmissionID )
import Network.Reddit.Types.Subreddit
import Web.HttpApiData ( ToHttpApiData(..) )
newtype = Text
deriving stock ( Int -> CommentID -> ShowS
[CommentID] -> ShowS
CommentID -> String
(Int -> CommentID -> ShowS)
-> (CommentID -> String)
-> ([CommentID] -> ShowS)
-> Show CommentID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommentID] -> ShowS
$cshowList :: [CommentID] -> ShowS
show :: CommentID -> String
$cshow :: CommentID -> String
showsPrec :: Int -> CommentID -> ShowS
$cshowsPrec :: Int -> CommentID -> ShowS
Show, (forall x. CommentID -> Rep CommentID x)
-> (forall x. Rep CommentID x -> CommentID) -> Generic CommentID
forall x. Rep CommentID x -> CommentID
forall x. CommentID -> Rep CommentID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommentID x -> CommentID
$cfrom :: forall x. CommentID -> Rep CommentID x
Generic )
deriving newtype ( CommentID -> CommentID -> Bool
(CommentID -> CommentID -> Bool)
-> (CommentID -> CommentID -> Bool) -> Eq CommentID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommentID -> CommentID -> Bool
$c/= :: CommentID -> CommentID -> Bool
== :: CommentID -> CommentID -> Bool
$c== :: CommentID -> CommentID -> Bool
Eq, Eq CommentID
Eq CommentID
-> (CommentID -> CommentID -> Ordering)
-> (CommentID -> CommentID -> Bool)
-> (CommentID -> CommentID -> Bool)
-> (CommentID -> CommentID -> Bool)
-> (CommentID -> CommentID -> Bool)
-> (CommentID -> CommentID -> CommentID)
-> (CommentID -> CommentID -> CommentID)
-> Ord CommentID
CommentID -> CommentID -> Bool
CommentID -> CommentID -> Ordering
CommentID -> CommentID -> CommentID
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 :: CommentID -> CommentID -> CommentID
$cmin :: CommentID -> CommentID -> CommentID
max :: CommentID -> CommentID -> CommentID
$cmax :: CommentID -> CommentID -> CommentID
>= :: CommentID -> CommentID -> Bool
$c>= :: CommentID -> CommentID -> Bool
> :: CommentID -> CommentID -> Bool
$c> :: CommentID -> CommentID -> Bool
<= :: CommentID -> CommentID -> Bool
$c<= :: CommentID -> CommentID -> Bool
< :: CommentID -> CommentID -> Bool
$c< :: CommentID -> CommentID -> Bool
compare :: CommentID -> CommentID -> Ordering
$ccompare :: CommentID -> CommentID -> Ordering
$cp1Ord :: Eq CommentID
Ord, CommentID -> ByteString
CommentID -> Builder
CommentID -> Text
(CommentID -> Text)
-> (CommentID -> Builder)
-> (CommentID -> ByteString)
-> (CommentID -> Text)
-> ToHttpApiData CommentID
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: CommentID -> Text
$ctoQueryParam :: CommentID -> Text
toHeader :: CommentID -> ByteString
$ctoHeader :: CommentID -> ByteString
toEncodedUrlPiece :: CommentID -> Builder
$ctoEncodedUrlPiece :: CommentID -> Builder
toUrlPiece :: CommentID -> Text
$ctoUrlPiece :: CommentID -> Text
ToHttpApiData )
instance FromJSON CommentID where
parseJSON :: Value -> Parser CommentID
parseJSON = String -> (Text -> Parser CommentID) -> Value -> Parser CommentID
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"CommentID" (Parser Text -> Parser CommentID
coerce (Parser Text -> Parser CommentID)
-> (Text -> Parser Text) -> Text -> Parser CommentID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RedditKind -> Text -> Parser Text
dropTypePrefix RedditKind
CommentKind)
instance Thing CommentID where
fullname :: CommentID -> Text
fullname (CommentID Text
cid) = RedditKind -> Text -> Text
prependType RedditKind
CommentKind Text
cid
data =
{ :: CommentID
, :: Username
, Comment -> Text
body :: Body
, Comment -> Text
bodyHTML :: Body
, :: Seq ChildComment
, :: Maybe Integer
, :: Maybe Integer
, :: Maybe Integer
, :: UTCTime
, :: Maybe UTCTime
, :: SubredditName
, :: SubredditID
, :: Int
, :: Maybe Bool
, :: SubmissionID
, :: Maybe URL
, :: Maybe Username
, :: URL
, :: Seq ItemReport
, :: Seq ItemReport
, :: Maybe Integer
, :: Maybe Distinction
, :: Bool
, :: Bool
}
deriving stock ( Int -> Comment -> ShowS
[Comment] -> ShowS
Comment -> String
(Int -> Comment -> ShowS)
-> (Comment -> String) -> ([Comment] -> ShowS) -> Show Comment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Comment] -> ShowS
$cshowList :: [Comment] -> ShowS
show :: Comment -> String
$cshow :: Comment -> String
showsPrec :: Int -> Comment -> ShowS
$cshowsPrec :: Int -> Comment -> ShowS
Show, Comment -> Comment -> Bool
(Comment -> Comment -> Bool)
-> (Comment -> Comment -> Bool) -> Eq Comment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Comment -> Comment -> Bool
$c/= :: Comment -> Comment -> Bool
== :: Comment -> Comment -> Bool
$c== :: Comment -> Comment -> Bool
Eq, (forall x. Comment -> Rep Comment x)
-> (forall x. Rep Comment x -> Comment) -> Generic Comment
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 FromJSON Comment where
parseJSON :: Value -> Parser Comment
parseJSON = RedditKind
-> String -> (Object -> Parser Comment) -> Value -> Parser Comment
forall b a.
FromJSON b =>
RedditKind -> String -> (b -> Parser a) -> Value -> Parser a
withKind RedditKind
CommentKind String
"Comment" Object -> Parser Comment
commentP
commentP :: Object -> Parser Comment
Object
o = do
CommentID
commentID <- Object
o Object -> Text -> Parser CommentID
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Username
author <- Object
o Object -> Text -> Parser Username
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"author"
Text
body <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"body"
Text
bodyHTML <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"body_html"
Seq ChildComment
replies <- Value -> Parser (Seq ChildComment)
repliesP (Value -> Parser (Seq ChildComment))
-> Parser Value -> Parser (Seq ChildComment)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"replies"
Maybe Integer
score <- Object
o Object -> Text -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"score"
Maybe Integer
ups <- Object
o Object -> Text -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"ups"
Maybe Integer
downs <- Object
o Object -> Text -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"downs"
UTCTime
created <- Integer -> UTCTime
integerToUTC (Integer -> UTCTime) -> Parser Integer -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Integer
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"created_utc"
Maybe UTCTime
edited <- Value -> Parser (Maybe UTCTime)
editedP (Value -> Parser (Maybe UTCTime))
-> Parser Value -> Parser (Maybe UTCTime)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"edited"
SubredditName
subreddit <- Object
o Object -> Text -> Parser SubredditName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"subreddit"
SubredditID
subredditID <- Object
o Object -> Text -> Parser SubredditID
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"subreddit_id"
Int
gilded <- Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"gilded"
Maybe Bool
scoreHidden <- Object
o Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"score_hidden"
SubmissionID
linkID <- Object
o Object -> Text -> Parser SubmissionID
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"link_id"
Maybe Text
linkURL <- Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"link_url"
Maybe Username
linkAuthor <- Object
o Object -> Text -> Parser (Maybe Username)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"link_author"
Text
permaLink <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"permalink"
Seq ItemReport
userReports <- Object
o Object -> Text -> Parser (Seq ItemReport)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"user_reports"
Seq ItemReport
modReports <- Object
o Object -> Text -> Parser (Seq ItemReport)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"mod_reports"
Maybe Integer
numReports <- Object
o Object -> Text -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"num_reports"
Maybe Distinction
distinguished <- Object
o Object -> Text -> Parser (Maybe Distinction)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"distinguished"
Bool
isSubmitter <- Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_submitter"
Bool
stickied <- Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"stickied"
Comment -> Parser Comment
forall (f :: * -> *) a. Applicative f => a -> f a
pure Comment :: CommentID
-> Username
-> Text
-> Text
-> Seq ChildComment
-> Maybe Integer
-> Maybe Integer
-> Maybe Integer
-> UTCTime
-> Maybe UTCTime
-> SubredditName
-> SubredditID
-> Int
-> Maybe Bool
-> SubmissionID
-> Maybe Text
-> Maybe Username
-> Text
-> Seq ItemReport
-> Seq ItemReport
-> Maybe Integer
-> Maybe Distinction
-> Bool
-> Bool
-> Comment
Comment { Bool
Int
Maybe Bool
Maybe Integer
Maybe Text
Maybe UTCTime
Maybe Distinction
Maybe Username
Text
UTCTime
Seq ItemReport
Seq ChildComment
SubredditID
SubredditName
Username
SubmissionID
CommentID
stickied :: Bool
isSubmitter :: Bool
distinguished :: Maybe Distinction
numReports :: Maybe Integer
modReports :: Seq ItemReport
userReports :: Seq ItemReport
permaLink :: Text
linkAuthor :: Maybe Username
linkURL :: Maybe Text
linkID :: SubmissionID
scoreHidden :: Maybe Bool
gilded :: Int
subredditID :: SubredditID
subreddit :: SubredditName
edited :: Maybe UTCTime
created :: UTCTime
downs :: Maybe Integer
ups :: Maybe Integer
score :: Maybe Integer
replies :: Seq ChildComment
bodyHTML :: Text
body :: Text
author :: Username
commentID :: CommentID
$sel:stickied:Comment :: Bool
$sel:isSubmitter:Comment :: Bool
$sel:distinguished:Comment :: Maybe Distinction
$sel:numReports:Comment :: Maybe Integer
$sel:modReports:Comment :: Seq ItemReport
$sel:userReports:Comment :: Seq ItemReport
$sel:permaLink:Comment :: Text
$sel:linkAuthor:Comment :: Maybe Username
$sel:linkURL:Comment :: Maybe Text
$sel:linkID:Comment :: SubmissionID
$sel:scoreHidden:Comment :: Maybe Bool
$sel:gilded:Comment :: Int
$sel:subredditID:Comment :: SubredditID
$sel:subreddit:Comment :: SubredditName
$sel:edited:Comment :: Maybe UTCTime
$sel:created:Comment :: UTCTime
$sel:downs:Comment :: Maybe Integer
$sel:ups:Comment :: Maybe Integer
$sel:score:Comment :: Maybe Integer
$sel:replies:Comment :: Seq ChildComment
$sel:bodyHTML:Comment :: Text
$sel:body:Comment :: Text
$sel:author:Comment :: Username
$sel:commentID:Comment :: CommentID
.. }
where
repliesP :: Value -> Parser (Seq ChildComment)
repliesP (String Text
_) = Seq ChildComment -> Parser (Seq ChildComment)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Seq ChildComment
forall a. Monoid a => a
mempty
repliesP v :: Value
v@(Object Object
_) = Value -> Parser (Listing CommentID ChildComment)
forall a. FromJSON a => Value -> Parser a
parseJSON @(Listing CommentID ChildComment) Value
v
Parser (Listing CommentID ChildComment)
-> (Listing CommentID ChildComment -> Seq ChildComment)
-> Parser (Seq ChildComment)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Listing CommentID ChildComment
-> Getting
(Seq ChildComment)
(Listing CommentID ChildComment)
(Seq ChildComment)
-> Seq ChildComment
forall s a. s -> Getting a s a -> a
^. forall s t a b. HasField "children" s t a b => Lens s t a b
forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"children")
repliesP Value
_ = Parser (Seq ChildComment)
forall a. Monoid a => a
mempty
instance Paginable Comment where
type PaginateOptions Comment = ItemOpts Comment
type PaginateThing Comment = CommentID
defaultOpts :: PaginateOptions Comment
defaultOpts = PaginateOptions Comment
forall a. ItemOpts a
defaultItemOpts
getFullname :: Comment -> PaginateThing Comment
getFullname Comment { CommentID
commentID :: CommentID
$sel:commentID:Comment :: Comment -> CommentID
commentID } = PaginateThing Comment
CommentID
commentID
newtype WithChildren = WithChildren (Seq ChildComment)
deriving stock ( Int -> WithChildren -> ShowS
[WithChildren] -> ShowS
WithChildren -> String
(Int -> WithChildren -> ShowS)
-> (WithChildren -> String)
-> ([WithChildren] -> ShowS)
-> Show WithChildren
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WithChildren] -> ShowS
$cshowList :: [WithChildren] -> ShowS
show :: WithChildren -> String
$cshow :: WithChildren -> String
showsPrec :: Int -> WithChildren -> ShowS
$cshowsPrec :: Int -> WithChildren -> ShowS
Show, WithChildren -> WithChildren -> Bool
(WithChildren -> WithChildren -> Bool)
-> (WithChildren -> WithChildren -> Bool) -> Eq WithChildren
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WithChildren -> WithChildren -> Bool
$c/= :: WithChildren -> WithChildren -> Bool
== :: WithChildren -> WithChildren -> Bool
$c== :: WithChildren -> WithChildren -> Bool
Eq, (forall x. WithChildren -> Rep WithChildren x)
-> (forall x. Rep WithChildren x -> WithChildren)
-> Generic WithChildren
forall x. Rep WithChildren x -> WithChildren
forall x. WithChildren -> Rep WithChildren x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WithChildren x -> WithChildren
$cfrom :: forall x. WithChildren -> Rep WithChildren x
Generic )
instance FromJSON WithChildren where
parseJSON :: Value -> Parser WithChildren
parseJSON = String
-> (Array -> Parser WithChildren) -> Value -> Parser WithChildren
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray String
"WithChildren" ([Value] -> Parser WithChildren
parseWithComments ([Value] -> Parser WithChildren)
-> (Array -> [Value]) -> Array -> Parser WithChildren
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> [Value]
forall l. IsList l => l -> [Item l]
toList)
where
parseWithComments :: [Value] -> Parser WithChildren
parseWithComments [ Value
_, Value
cs ] = Seq ChildComment -> WithChildren
WithChildren
(Seq ChildComment -> WithChildren)
-> Parser (Seq ChildComment) -> Parser WithChildren
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Parser (Listing CommentID ChildComment)
forall a. FromJSON a => Value -> Parser a
parseJSON @(Listing CommentID ChildComment) Value
cs
Parser (Listing CommentID ChildComment)
-> (Listing CommentID ChildComment -> Seq ChildComment)
-> Parser (Seq ChildComment)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Listing CommentID ChildComment
-> Getting
(Seq ChildComment)
(Listing CommentID ChildComment)
(Seq ChildComment)
-> Seq ChildComment
forall s a. s -> Getting a s a -> a
^. forall s t a b. HasField "children" s t a b => Lens s t a b
forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"children"))
parseWithComments [Value]
_ = Parser WithChildren
forall a. Monoid a => a
mempty
newtype WithReplies = WithReplies Comment
deriving stock ( Int -> WithReplies -> ShowS
[WithReplies] -> ShowS
WithReplies -> String
(Int -> WithReplies -> ShowS)
-> (WithReplies -> String)
-> ([WithReplies] -> ShowS)
-> Show WithReplies
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WithReplies] -> ShowS
$cshowList :: [WithReplies] -> ShowS
show :: WithReplies -> String
$cshow :: WithReplies -> String
showsPrec :: Int -> WithReplies -> ShowS
$cshowsPrec :: Int -> WithReplies -> ShowS
Show, WithReplies -> WithReplies -> Bool
(WithReplies -> WithReplies -> Bool)
-> (WithReplies -> WithReplies -> Bool) -> Eq WithReplies
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WithReplies -> WithReplies -> Bool
$c/= :: WithReplies -> WithReplies -> Bool
== :: WithReplies -> WithReplies -> Bool
$c== :: WithReplies -> WithReplies -> Bool
Eq, (forall x. WithReplies -> Rep WithReplies x)
-> (forall x. Rep WithReplies x -> WithReplies)
-> Generic WithReplies
forall x. Rep WithReplies x -> WithReplies
forall x. WithReplies -> Rep WithReplies x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WithReplies x -> WithReplies
$cfrom :: forall x. WithReplies -> Rep WithReplies x
Generic )
instance FromJSON WithReplies where
parseJSON :: Value -> Parser WithReplies
parseJSON = String
-> (Array -> Parser WithReplies) -> Value -> Parser WithReplies
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray String
"WithReplies" ([Value] -> Parser WithReplies
parseWithReplies ([Value] -> Parser WithReplies)
-> (Array -> [Value]) -> Array -> Parser WithReplies
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> [Value]
forall l. IsList l => l -> [Item l]
toList)
where
parseWithReplies :: [Value] -> Parser WithReplies
parseWithReplies [ Value
_, Value
cs ] = do
Listing { Seq Comment
$sel:children:Listing :: forall t a. Listing t a -> Seq a
children :: Seq Comment
children } <- Value -> Parser (Listing CommentID Comment)
forall a. FromJSON a => Value -> Parser a
parseJSON @(Listing CommentID Comment) Value
cs
case Seq Comment
children of
Comment
c :<| Seq Comment
_ -> WithReplies -> Parser WithReplies
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WithReplies -> Parser WithReplies)
-> WithReplies -> Parser WithReplies
forall a b. (a -> b) -> a -> b
$ Comment -> WithReplies
WithReplies Comment
c
Seq Comment
_ -> Parser WithReplies
forall a. Monoid a => a
mempty
parseWithReplies [Value]
_ = Parser WithReplies
forall a. Monoid a => a
mempty
data
= TopLevel Comment
| More MoreComments
deriving stock ( Int -> ChildComment -> ShowS
[ChildComment] -> ShowS
ChildComment -> String
(Int -> ChildComment -> ShowS)
-> (ChildComment -> String)
-> ([ChildComment] -> ShowS)
-> Show ChildComment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChildComment] -> ShowS
$cshowList :: [ChildComment] -> ShowS
show :: ChildComment -> String
$cshow :: ChildComment -> String
showsPrec :: Int -> ChildComment -> ShowS
$cshowsPrec :: Int -> ChildComment -> ShowS
Show, ChildComment -> ChildComment -> Bool
(ChildComment -> ChildComment -> Bool)
-> (ChildComment -> ChildComment -> Bool) -> Eq ChildComment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChildComment -> ChildComment -> Bool
$c/= :: ChildComment -> ChildComment -> Bool
== :: ChildComment -> ChildComment -> Bool
$c== :: ChildComment -> ChildComment -> Bool
Eq, (forall x. ChildComment -> Rep ChildComment x)
-> (forall x. Rep ChildComment x -> ChildComment)
-> Generic ChildComment
forall x. Rep ChildComment x -> ChildComment
forall x. ChildComment -> Rep ChildComment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChildComment x -> ChildComment
$cfrom :: forall x. ChildComment -> Rep ChildComment x
Generic )
instance FromJSON ChildComment where
parseJSON :: Value -> Parser ChildComment
parseJSON = String
-> (Object -> Parser ChildComment) -> Value -> Parser ChildComment
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ChildComment" ((Object -> Parser ChildComment) -> Value -> Parser ChildComment)
-> (Object -> Parser ChildComment) -> Value -> Parser ChildComment
forall a b. (a -> b) -> a -> b
$ \Object
o -> Object
o Object -> Text -> Parser RedditKind
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"kind" Parser RedditKind
-> (RedditKind -> Parser ChildComment) -> Parser ChildComment
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
RedditKind
k
| RedditKind
k RedditKind -> RedditKind -> Bool
forall a. Eq a => a -> a -> Bool
== RedditKind
CommentKind -> Comment -> ChildComment
TopLevel (Comment -> ChildComment) -> Parser Comment -> Parser ChildComment
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Comment
forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
o)
| RedditKind
k RedditKind -> RedditKind -> Bool
forall a. Eq a => a -> a -> Bool
== RedditKind
MoreKind -> MoreComments -> ChildComment
More (MoreComments -> ChildComment)
-> Parser MoreComments -> Parser ChildComment
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser MoreComments
forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
o)
| Bool
otherwise -> Parser ChildComment
forall a. Monoid a => a
mempty
newtype LoadedChildren = LoadedChildren (Seq ChildComment)
deriving stock ( Int -> LoadedChildren -> ShowS
[LoadedChildren] -> ShowS
LoadedChildren -> String
(Int -> LoadedChildren -> ShowS)
-> (LoadedChildren -> String)
-> ([LoadedChildren] -> ShowS)
-> Show LoadedChildren
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LoadedChildren] -> ShowS
$cshowList :: [LoadedChildren] -> ShowS
show :: LoadedChildren -> String
$cshow :: LoadedChildren -> String
showsPrec :: Int -> LoadedChildren -> ShowS
$cshowsPrec :: Int -> LoadedChildren -> ShowS
Show, (forall x. LoadedChildren -> Rep LoadedChildren x)
-> (forall x. Rep LoadedChildren x -> LoadedChildren)
-> Generic LoadedChildren
forall x. Rep LoadedChildren x -> LoadedChildren
forall x. LoadedChildren -> Rep LoadedChildren x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LoadedChildren x -> LoadedChildren
$cfrom :: forall x. LoadedChildren -> Rep LoadedChildren x
Generic )
deriving newtype ( LoadedChildren -> LoadedChildren -> Bool
(LoadedChildren -> LoadedChildren -> Bool)
-> (LoadedChildren -> LoadedChildren -> Bool) -> Eq LoadedChildren
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LoadedChildren -> LoadedChildren -> Bool
$c/= :: LoadedChildren -> LoadedChildren -> Bool
== :: LoadedChildren -> LoadedChildren -> Bool
$c== :: LoadedChildren -> LoadedChildren -> Bool
Eq )
instance FromJSON LoadedChildren where
parseJSON :: Value -> Parser LoadedChildren
parseJSON = String
-> (Object -> Parser LoadedChildren)
-> Value
-> Parser LoadedChildren
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"LoadedChildren" ((Object -> Parser LoadedChildren)
-> Value -> Parser LoadedChildren)
-> (Object -> Parser LoadedChildren)
-> Value
-> Parser LoadedChildren
forall a b. (a -> b) -> a -> b
$ \Object
o -> Seq ChildComment -> LoadedChildren
LoadedChildren (Seq ChildComment -> LoadedChildren)
-> ([ChildComment] -> Seq ChildComment)
-> [ChildComment]
-> LoadedChildren
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ChildComment] -> Seq ChildComment
forall l. IsList l => [Item l] -> l
fromList
([ChildComment] -> LoadedChildren)
-> Parser [ChildComment] -> Parser LoadedChildren
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Parser [ChildComment]
loadedP (Value -> Parser [ChildComment])
-> Parser Value -> Parser [ChildComment]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ((Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"things") (Object -> Parser Value) -> Parser Object -> Parser Value
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"data") (Object -> Parser Object) -> Parser Object -> Parser Object
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"json"))
where
loadedP :: Value -> Parser [ChildComment]
loadedP = String
-> (Array -> Parser [ChildComment])
-> Value
-> Parser [ChildComment]
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray String
"[ChildComment]" ((Value -> Parser ChildComment) -> [Value] -> Parser [ChildComment]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Value -> Parser ChildComment
forall a. FromJSON a => Value -> Parser a
parseJSON ([Value] -> Parser [ChildComment])
-> (Array -> [Value]) -> Array -> Parser [ChildComment]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> [Value]
forall l. IsList l => l -> [Item l]
toList)
data =
{ :: Seq CommentID
, :: Integer
}
deriving stock ( Int -> MoreComments -> ShowS
[MoreComments] -> ShowS
MoreComments -> String
(Int -> MoreComments -> ShowS)
-> (MoreComments -> String)
-> ([MoreComments] -> ShowS)
-> Show MoreComments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MoreComments] -> ShowS
$cshowList :: [MoreComments] -> ShowS
show :: MoreComments -> String
$cshow :: MoreComments -> String
showsPrec :: Int -> MoreComments -> ShowS
$cshowsPrec :: Int -> MoreComments -> ShowS
Show, MoreComments -> MoreComments -> Bool
(MoreComments -> MoreComments -> Bool)
-> (MoreComments -> MoreComments -> Bool) -> Eq MoreComments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MoreComments -> MoreComments -> Bool
$c/= :: MoreComments -> MoreComments -> Bool
== :: MoreComments -> MoreComments -> Bool
$c== :: MoreComments -> MoreComments -> Bool
Eq, (forall x. MoreComments -> Rep MoreComments x)
-> (forall x. Rep MoreComments x -> MoreComments)
-> Generic MoreComments
forall x. Rep MoreComments x -> MoreComments
forall x. MoreComments -> Rep MoreComments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MoreComments x -> MoreComments
$cfrom :: forall x. MoreComments -> Rep MoreComments x
Generic )
instance FromJSON MoreComments where
parseJSON :: Value -> Parser MoreComments
parseJSON = String
-> (Object -> Parser MoreComments) -> Value -> Parser MoreComments
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"MoreComments" ((Object -> Parser MoreComments) -> Value -> Parser MoreComments)
-> (Object -> Parser MoreComments) -> Value -> Parser MoreComments
forall a b. (a -> b) -> a -> b
$ Object -> Parser MoreComments
parseMore (Object -> Parser MoreComments)
-> (Object -> Parser Object) -> Object -> Parser MoreComments
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"data")
where
parseMore :: Object -> Parser MoreComments
parseMore Object
o = Seq CommentID -> Integer -> MoreComments
MoreComments (Seq CommentID -> Integer -> MoreComments)
-> Parser (Seq CommentID) -> Parser (Integer -> MoreComments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Seq CommentID)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"children" Parser (Integer -> MoreComments)
-> Parser Integer -> Parser MoreComments
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Integer
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"count"