{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}

-- |
-- Module      : Network.Reddit.Types.Item
-- Copyright   : (c) 2021 Rory Tyler Hayford
-- License     : BSD-3-Clause
-- Maintainer  : rory.hayford@protonmail.com
-- Stability   : experimental
-- Portability : GHC
--
module Network.Reddit.Types.Item
    ( Item(..)
    , ItemID(..)
    , PostedItem
    , Vote(..)
    , Report
    , mkReport
    ) where

import           Control.Monad.Catch             ( MonadThrow(throwM) )

import           Data.Aeson
                 ( (.:)
                 , FromJSON(..)
                 , Options(sumEncoding)
                 , SumEncoding(UntaggedValue)
                 , Value(Object)
                 , defaultOptions
                 , genericParseJSON
                 , withObject
                 )
import           Data.Text                       ( Text )
import qualified Data.Text                       as T

import           GHC.Generics                    ( Generic )

import           Network.Reddit.Types.Comment
import           Network.Reddit.Types.Internal
import           Network.Reddit.Types.Submission

import           Web.HttpApiData                 ( ToHttpApiData )

-- | Wraps either a 'CommentID' or a 'SubmissionID'. This is required to use
-- 'Item's with 'Paginator's
data ItemID
    = CommentItemID CommentID
    | SubmissionItemID SubmissionID
    deriving stock ( Int -> ItemID -> ShowS
[ItemID] -> ShowS
ItemID -> String
(Int -> ItemID -> ShowS)
-> (ItemID -> String) -> ([ItemID] -> ShowS) -> Show ItemID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ItemID] -> ShowS
$cshowList :: [ItemID] -> ShowS
show :: ItemID -> String
$cshow :: ItemID -> String
showsPrec :: Int -> ItemID -> ShowS
$cshowsPrec :: Int -> ItemID -> ShowS
Show, ItemID -> ItemID -> Bool
(ItemID -> ItemID -> Bool)
-> (ItemID -> ItemID -> Bool) -> Eq ItemID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ItemID -> ItemID -> Bool
$c/= :: ItemID -> ItemID -> Bool
== :: ItemID -> ItemID -> Bool
$c== :: ItemID -> ItemID -> Bool
Eq, (forall x. ItemID -> Rep ItemID x)
-> (forall x. Rep ItemID x -> ItemID) -> Generic ItemID
forall x. Rep ItemID x -> ItemID
forall x. ItemID -> Rep ItemID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ItemID x -> ItemID
$cfrom :: forall x. ItemID -> Rep ItemID x
Generic )

instance Thing ItemID where
    fullname :: ItemID -> Text
fullname (CommentItemID CommentID
cid)    = CommentID -> Text
forall a. Thing a => a -> Text
fullname CommentID
cid
    fullname (SubmissionItemID SubmissionID
sid) = SubmissionID -> Text
forall a. Thing a => a -> Text
fullname SubmissionID
sid

instance FromJSON ItemID where
    parseJSON :: Value -> Parser ItemID
parseJSON =
        Options -> Value -> Parser ItemID
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions { sumEncoding :: SumEncoding
sumEncoding = SumEncoding
UntaggedValue }

-- | Certain endpoints will return either 'Comment's or a 'Submission's, or both
data Item
    = CommentItem Comment
    | SubmissionItem Submission
    deriving stock ( Int -> Item -> ShowS
[Item] -> ShowS
Item -> String
(Int -> Item -> ShowS)
-> (Item -> String) -> ([Item] -> ShowS) -> Show Item
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Item] -> ShowS
$cshowList :: [Item] -> ShowS
show :: Item -> String
$cshow :: Item -> String
showsPrec :: Int -> Item -> ShowS
$cshowsPrec :: Int -> Item -> ShowS
Show, Item -> Item -> Bool
(Item -> Item -> Bool) -> (Item -> Item -> Bool) -> Eq Item
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Item -> Item -> Bool
$c/= :: Item -> Item -> Bool
== :: Item -> Item -> Bool
$c== :: Item -> Item -> Bool
Eq, (forall x. Item -> Rep Item x)
-> (forall x. Rep Item x -> Item) -> Generic Item
forall x. Rep Item x -> Item
forall x. Item -> Rep Item x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Item x -> Item
$cfrom :: forall x. Item -> Rep Item x
Generic )

instance Paginable Item where
    type PaginateOptions Item = ItemOpts

    type PaginateThing Item = ItemID

    defaultOpts :: PaginateOptions Item
defaultOpts = ItemOpts
PaginateOptions Item
defaultItemOpts

    getFullname :: Item -> PaginateThing Item
getFullname = \case
        CommentItem Comment { CommentID
$sel:commentID:Comment :: Comment -> CommentID
commentID :: CommentID
commentID }          -> CommentID -> ItemID
CommentItemID CommentID
commentID
        SubmissionItem Submission { SubmissionID
$sel:submissionID:Submission :: Submission -> SubmissionID
submissionID :: SubmissionID
submissionID } ->
            SubmissionID -> ItemID
SubmissionItemID SubmissionID
submissionID

instance FromJSON Item where
    parseJSON :: Value -> Parser Item
parseJSON = String -> (Object -> Parser Item) -> Value -> Parser Item
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Item" ((Object -> Parser Item) -> Value -> Parser Item)
-> (Object -> Parser Item) -> Value -> Parser Item
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 Item) -> Parser Item
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        RedditKind
x
            | RedditKind
x RedditKind -> RedditKind -> Bool
forall a. Eq a => a -> a -> Bool
== RedditKind
CommentKind -> Comment -> Item
CommentItem (Comment -> Item) -> Parser Comment -> Parser Item
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
x RedditKind -> RedditKind -> Bool
forall a. Eq a => a -> a -> Bool
== RedditKind
SubmissionKind -> Submission -> Item
SubmissionItem (Submission -> Item) -> Parser Submission -> Parser Item
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Submission
forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
o)
            | Bool
otherwise -> Parser Item
forall a. Monoid a => a
mempty

-- | Wrapper for parsing new 'Item's, 'Comment's, or 'Submission's that are returned
-- after requesting their creation
newtype PostedItem a = PostedItem a
    deriving stock ( Int -> PostedItem a -> ShowS
[PostedItem a] -> ShowS
PostedItem a -> String
(Int -> PostedItem a -> ShowS)
-> (PostedItem a -> String)
-> ([PostedItem a] -> ShowS)
-> Show (PostedItem a)
forall a. Show a => Int -> PostedItem a -> ShowS
forall a. Show a => [PostedItem a] -> ShowS
forall a. Show a => PostedItem a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostedItem a] -> ShowS
$cshowList :: forall a. Show a => [PostedItem a] -> ShowS
show :: PostedItem a -> String
$cshow :: forall a. Show a => PostedItem a -> String
showsPrec :: Int -> PostedItem a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> PostedItem a -> ShowS
Show, (forall x. PostedItem a -> Rep (PostedItem a) x)
-> (forall x. Rep (PostedItem a) x -> PostedItem a)
-> Generic (PostedItem a)
forall x. Rep (PostedItem a) x -> PostedItem a
forall x. PostedItem a -> Rep (PostedItem a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (PostedItem a) x -> PostedItem a
forall a x. PostedItem a -> Rep (PostedItem a) x
$cto :: forall a x. Rep (PostedItem a) x -> PostedItem a
$cfrom :: forall a x. PostedItem a -> Rep (PostedItem a) x
Generic )

deriving newtype instance Eq a => Eq (PostedItem a)

instance FromJSON (PostedItem Comment) where
    parseJSON :: Value -> Parser (PostedItem Comment)
parseJSON = String
-> (Object -> Parser (PostedItem Comment))
-> Value
-> Parser (PostedItem Comment)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PostedItem Comment" ((Object -> Parser (PostedItem Comment))
 -> Value -> Parser (PostedItem Comment))
-> (Object -> Parser (PostedItem Comment))
-> Value
-> Parser (PostedItem Comment)
forall a b. (a -> b) -> a -> b
$ \Object
o -> [Value] -> Parser (PostedItem Comment)
postedCommentP
        ([Value] -> Parser (PostedItem Comment))
-> Parser [Value] -> Parser (PostedItem Comment)
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
        postedCommentP :: [Value] -> Parser (PostedItem Comment)
postedCommentP [ Object Object
o ] = Comment -> PostedItem Comment
forall a. a -> PostedItem a
PostedItem
            (Comment -> PostedItem Comment)
-> Parser Comment -> Parser (PostedItem Comment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object -> Parser Comment
commentP (Object -> Parser Comment) -> Parser Object -> Parser Comment
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
"data")
        postedCommentP [Value]
_            = Parser (PostedItem Comment)
forall a. Monoid a => a
mempty

instance FromJSON (PostedItem Submission) where
    parseJSON :: Value -> Parser (PostedItem Submission)
parseJSON = String
-> (Object -> Parser (PostedItem Submission))
-> Value
-> Parser (PostedItem Submission)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PostedItem Submission" ((Object -> Parser (PostedItem Submission))
 -> Value -> Parser (PostedItem Submission))
-> (Object -> Parser (PostedItem Submission))
-> Value
-> Parser (PostedItem Submission)
forall a b. (a -> b) -> a -> b
$ \Object
o -> [Value] -> Parser (PostedItem Submission)
postedSubmissionP
        ([Value] -> Parser (PostedItem Submission))
-> Parser [Value] -> Parser (PostedItem Submission)
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
        postedSubmissionP :: [Value] -> Parser (PostedItem Submission)
postedSubmissionP [ Object Object
o ] = Submission -> PostedItem Submission
forall a. a -> PostedItem a
PostedItem
            (Submission -> PostedItem Submission)
-> Parser Submission -> Parser (PostedItem Submission)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object -> Parser Submission
submissionP (Object -> Parser Submission) -> Parser Object -> Parser Submission
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
"data")
        postedSubmissionP [Value]
_            = Parser (PostedItem Submission)
forall a. Monoid a => a
mempty

instance FromJSON (PostedItem Item) where
    parseJSON :: Value -> Parser (PostedItem Item)
parseJSON = String
-> (Object -> Parser (PostedItem Item))
-> Value
-> Parser (PostedItem Item)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PostedItem Item" ((Object -> Parser (PostedItem Item))
 -> Value -> Parser (PostedItem Item))
-> (Object -> Parser (PostedItem Item))
-> Value
-> Parser (PostedItem Item)
forall a b. (a -> b) -> a -> b
$ \Object
o -> [Value] -> Parser (PostedItem Item)
postedItemP
        ([Value] -> Parser (PostedItem Item))
-> Parser [Value] -> Parser (PostedItem Item)
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
        postedItemP :: [Value] -> Parser (PostedItem Item)
postedItemP [ Object Object
o ] = (Object
o Object -> Text -> Parser RedditKind
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"kind") Parser RedditKind
-> (RedditKind -> Parser (PostedItem Item))
-> Parser (PostedItem Item)
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 -> Item -> PostedItem Item
forall a. a -> PostedItem a
PostedItem (Item -> PostedItem Item)
-> (Comment -> Item) -> Comment -> PostedItem Item
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Comment -> Item
CommentItem
                    (Comment -> PostedItem Item)
-> Parser Comment -> Parser (PostedItem Item)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object -> Parser Comment
commentP (Object -> Parser Comment) -> Parser Object -> Parser Comment
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
"data")
                | RedditKind
k RedditKind -> RedditKind -> Bool
forall a. Eq a => a -> a -> Bool
== RedditKind
SubmissionKind -> Item -> PostedItem Item
forall a. a -> PostedItem a
PostedItem (Item -> PostedItem Item)
-> (Submission -> Item) -> Submission -> PostedItem Item
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Submission -> Item
SubmissionItem
                    (Submission -> PostedItem Item)
-> Parser Submission -> Parser (PostedItem Item)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object -> Parser Submission
submissionP (Object -> Parser Submission) -> Parser Object -> Parser Submission
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
"data")
                | Bool
otherwise -> Parser (PostedItem Item)
forall a. Monoid a => a
mempty
        postedItemP [Value]
_            = Parser (PostedItem Item)
forall a. Monoid a => a
mempty

-- | The direction in which to vote
data Vote
    = Downvote
    | Unvote
    | Upvote
    deriving stock ( Int -> Vote -> ShowS
[Vote] -> ShowS
Vote -> String
(Int -> Vote -> ShowS)
-> (Vote -> String) -> ([Vote] -> ShowS) -> Show Vote
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Vote] -> ShowS
$cshowList :: [Vote] -> ShowS
show :: Vote -> String
$cshow :: Vote -> String
showsPrec :: Int -> Vote -> ShowS
$cshowsPrec :: Int -> Vote -> ShowS
Show, Vote -> Vote -> Bool
(Vote -> Vote -> Bool) -> (Vote -> Vote -> Bool) -> Eq Vote
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Vote -> Vote -> Bool
$c/= :: Vote -> Vote -> Bool
== :: Vote -> Vote -> Bool
$c== :: Vote -> Vote -> Bool
Eq, (forall x. Vote -> Rep Vote x)
-> (forall x. Rep Vote x -> Vote) -> Generic Vote
forall x. Rep Vote x -> Vote
forall x. Vote -> Rep Vote x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Vote x -> Vote
$cfrom :: forall x. Vote -> Rep Vote x
Generic, Eq Vote
Eq Vote
-> (Vote -> Vote -> Ordering)
-> (Vote -> Vote -> Bool)
-> (Vote -> Vote -> Bool)
-> (Vote -> Vote -> Bool)
-> (Vote -> Vote -> Bool)
-> (Vote -> Vote -> Vote)
-> (Vote -> Vote -> Vote)
-> Ord Vote
Vote -> Vote -> Bool
Vote -> Vote -> Ordering
Vote -> Vote -> Vote
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 :: Vote -> Vote -> Vote
$cmin :: Vote -> Vote -> Vote
max :: Vote -> Vote -> Vote
$cmax :: Vote -> Vote -> Vote
>= :: Vote -> Vote -> Bool
$c>= :: Vote -> Vote -> Bool
> :: Vote -> Vote -> Bool
$c> :: Vote -> Vote -> Bool
<= :: Vote -> Vote -> Bool
$c<= :: Vote -> Vote -> Bool
< :: Vote -> Vote -> Bool
$c< :: Vote -> Vote -> Bool
compare :: Vote -> Vote -> Ordering
$ccompare :: Vote -> Vote -> Ordering
$cp1Ord :: Eq Vote
Ord )

-- | The reason for issuing a report. The length of the contained text must be <=
-- 100 characters
newtype Report = Report Text
    deriving stock ( Int -> Report -> ShowS
[Report] -> ShowS
Report -> String
(Int -> Report -> ShowS)
-> (Report -> String) -> ([Report] -> ShowS) -> Show Report
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Report] -> ShowS
$cshowList :: [Report] -> ShowS
show :: Report -> String
$cshow :: Report -> String
showsPrec :: Int -> Report -> ShowS
$cshowsPrec :: Int -> Report -> ShowS
Show, (forall x. Report -> Rep Report x)
-> (forall x. Rep Report x -> Report) -> Generic Report
forall x. Rep Report x -> Report
forall x. Report -> Rep Report x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Report x -> Report
$cfrom :: forall x. Report -> Rep Report x
Generic )
    deriving newtype ( Report -> Report -> Bool
(Report -> Report -> Bool)
-> (Report -> Report -> Bool) -> Eq Report
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Report -> Report -> Bool
$c/= :: Report -> Report -> Bool
== :: Report -> Report -> Bool
$c== :: Report -> Report -> Bool
Eq, Report -> ByteString
Report -> Builder
Report -> Text
(Report -> Text)
-> (Report -> Builder)
-> (Report -> ByteString)
-> (Report -> Text)
-> ToHttpApiData Report
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: Report -> Text
$ctoQueryParam :: Report -> Text
toHeader :: Report -> ByteString
$ctoHeader :: Report -> ByteString
toEncodedUrlPiece :: Report -> Builder
$ctoEncodedUrlPiece :: Report -> Builder
toUrlPiece :: Report -> Text
$ctoUrlPiece :: Report -> Text
ToHttpApiData )

-- | Smart constructor for 'Report's, which may be no longer than 100 characters
-- in length
mkReport :: MonadThrow m => Text -> m Report
mkReport :: Text -> m Report
mkReport Text
txt
    | Text -> Int
T.length Text
txt Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
100 =
        ClientException -> m Report
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ClientException -> m Report) -> ClientException -> m Report
forall a b. (a -> b) -> a -> b
$ Text -> ClientException
OtherError Text
"mkReport: length must not exceed 100 characters"
    | Bool
otherwise = Report -> m Report
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Report -> m Report) -> Report -> m Report
forall a b. (a -> b) -> a -> b
$ Text -> Report
Report Text
txt