{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Network.Reddit.Types.Submission
    ( Submission(..)
    , SubmissionID(SubmissionID)
    , SubmissionContent(..)
    , submissionP
    , PollData(..)
    , PollOption(..)
    , PollOptionID
      
    , Collection(..)
    , CollectionLayout(..)
    , CollectionID
    , NewCollection(..)
      
    , SubmissionOptions(..)
    , mkSubmissionOptions
    , NewSubmission(..)
    , S3UploadLease(..)
    , UploadType(..)
    , UploadResult(..)
    , CrosspostOptions(..)
    , mkCrosspostOptions
    , PostedCrosspost
    , Poll(..)
    , PollSubmission(PollSubmission)
    , mkPoll
    , GalleryImage(..)
    , mkGalleryImage
    , galleryImageToUpload
    , GallerySubmission(GallerySubmission)
    , InlineMedia(..)
    , InlineMediaType(..)
    , InlineMediaUpload(..)
    , inlineMediaToUpload
    , writeInlineMedia
    , Fancypants
    , PostedSubmission
      
    , Search(..)
    , SearchSort(..)
    , SearchCategory
    , mkSearchCategory
    , SearchOpts(..)
    , ResultID(ResultID)
    , SearchSyntax(..)
    , mkSearch
    ) where
import           Control.Monad                  ( (<=<) )
import           Control.Monad.Catch            ( MonadThrow(throwM) )
import           Data.Aeson
                 ( (.:)
                 , (.:?)
                 , FromJSON(..)
                 , KeyValue((.=))
                 , Object
                 , Options(..)
                 , ToJSON(toJSON)
                 , defaultOptions
                 , genericParseJSON
                 , genericToJSON
                 , object
                 , withArray
                 , withObject
                 , withText
                 )
import           Data.Aeson.Casing              ( snakeCase )
import           Data.Aeson.Types               ( Parser )
import           Data.Bool                      ( bool )
import           Data.Char                      ( toUpper )
import           Data.Coerce                    ( coerce )
import           Data.Foldable                  ( asum )
import qualified Data.Foldable                  as F
import           Data.Generics.Wrapped          ( wrappedTo )
import qualified Data.HashMap.Strict            as HM
import           Data.HashMap.Strict            ( HashMap )
import           Data.Ix                        ( Ix(inRange) )
import           Data.Maybe
                 ( catMaybes
                 , fromMaybe
                 , isJust
                 )
import           Data.Sequence                  ( Seq )
import           Data.Text                      ( Text )
import qualified Data.Text                      as T
import           Data.Time                      ( UTCTime )
import           GHC.Exts                       ( IsList(..) )
import           GHC.Generics                   ( Generic )
import           Network.Reddit.Types.Account
import           Network.Reddit.Types.Flair
import           Network.Reddit.Types.Internal
import           Network.Reddit.Types.Subreddit
import           Web.FormUrlEncoded             ( ToForm(..) )
import           Web.HttpApiData                ( ToHttpApiData(toQueryParam)
                                                , showTextData
                                                )
newtype SubmissionID = SubmissionID Text
    deriving stock ( Int -> SubmissionID -> ShowS
[SubmissionID] -> ShowS
SubmissionID -> String
(Int -> SubmissionID -> ShowS)
-> (SubmissionID -> String)
-> ([SubmissionID] -> ShowS)
-> Show SubmissionID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubmissionID] -> ShowS
$cshowList :: [SubmissionID] -> ShowS
show :: SubmissionID -> String
$cshow :: SubmissionID -> String
showsPrec :: Int -> SubmissionID -> ShowS
$cshowsPrec :: Int -> SubmissionID -> ShowS
Show, (forall x. SubmissionID -> Rep SubmissionID x)
-> (forall x. Rep SubmissionID x -> SubmissionID)
-> Generic SubmissionID
forall x. Rep SubmissionID x -> SubmissionID
forall x. SubmissionID -> Rep SubmissionID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubmissionID x -> SubmissionID
$cfrom :: forall x. SubmissionID -> Rep SubmissionID x
Generic )
    deriving newtype ( SubmissionID -> SubmissionID -> Bool
(SubmissionID -> SubmissionID -> Bool)
-> (SubmissionID -> SubmissionID -> Bool) -> Eq SubmissionID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubmissionID -> SubmissionID -> Bool
$c/= :: SubmissionID -> SubmissionID -> Bool
== :: SubmissionID -> SubmissionID -> Bool
$c== :: SubmissionID -> SubmissionID -> Bool
Eq, SubmissionID -> ByteString
SubmissionID -> Builder
SubmissionID -> Text
(SubmissionID -> Text)
-> (SubmissionID -> Builder)
-> (SubmissionID -> ByteString)
-> (SubmissionID -> Text)
-> ToHttpApiData SubmissionID
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: SubmissionID -> Text
$ctoQueryParam :: SubmissionID -> Text
toHeader :: SubmissionID -> ByteString
$ctoHeader :: SubmissionID -> ByteString
toEncodedUrlPiece :: SubmissionID -> Builder
$ctoEncodedUrlPiece :: SubmissionID -> Builder
toUrlPiece :: SubmissionID -> Text
$ctoUrlPiece :: SubmissionID -> Text
ToHttpApiData )
instance FromJSON SubmissionID where
    parseJSON :: Value -> Parser SubmissionID
parseJSON =
        String
-> (Text -> Parser SubmissionID) -> Value -> Parser SubmissionID
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"SubmissionID" (Parser Text -> Parser SubmissionID
coerce (Parser Text -> Parser SubmissionID)
-> (Text -> Parser Text) -> Text -> Parser SubmissionID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RedditKind -> Text -> Parser Text
dropTypePrefix RedditKind
SubmissionKind)
instance Thing SubmissionID where
    fullname :: SubmissionID -> Text
fullname (SubmissionID Text
sid) = RedditKind -> Text -> Text
prependType RedditKind
SubmissionKind Text
sid
data Submission = Submission
    { Submission -> SubmissionID
submissionID  :: SubmissionID
    , Submission -> Text
title         :: Title
    , Submission -> Username
author        :: Username
    , Submission -> SubmissionContent
content       :: SubmissionContent
    , Submission -> SubredditName
subreddit     :: SubredditName
    , Submission -> UTCTime
created       :: UTCTime
    , Submission -> Maybe UTCTime
edited        :: Maybe UTCTime
    , Submission -> Text
permalink     :: URL
    , Submission -> Text
domain        :: Domain
    ,    :: Integer
    , Submission -> Integer
score         :: Integer
    , Submission -> Maybe Integer
ups           :: Maybe Integer
    , Submission -> Maybe Integer
downs         :: Maybe Integer
    , Submission -> Maybe Rational
upvoteRatio   :: Maybe Rational
    , Submission -> Integer
gilded        :: Integer
    , Submission -> Seq ItemReport
userReports   :: Seq ItemReport
    , Submission -> Seq ItemReport
modReports    :: Seq ItemReport
    , Submission -> Maybe Integer
numReports    :: Maybe Integer
    , Submission -> Maybe Distinction
distinguished :: Maybe Distinction
    , Submission -> Bool
isOC          :: Bool
    , Submission -> Bool
clicked       :: Bool
    , Submission -> Bool
over18        :: Bool
    , Submission -> Bool
locked        :: Bool
    , Submission -> Bool
spoiler       :: Bool
    , Submission -> Maybe PollData
pollData      :: Maybe PollData
    }
    deriving stock ( Int -> Submission -> ShowS
[Submission] -> ShowS
Submission -> String
(Int -> Submission -> ShowS)
-> (Submission -> String)
-> ([Submission] -> ShowS)
-> Show Submission
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Submission] -> ShowS
$cshowList :: [Submission] -> ShowS
show :: Submission -> String
$cshow :: Submission -> String
showsPrec :: Int -> Submission -> ShowS
$cshowsPrec :: Int -> Submission -> ShowS
Show, Submission -> Submission -> Bool
(Submission -> Submission -> Bool)
-> (Submission -> Submission -> Bool) -> Eq Submission
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Submission -> Submission -> Bool
$c/= :: Submission -> Submission -> Bool
== :: Submission -> Submission -> Bool
$c== :: Submission -> Submission -> Bool
Eq, (forall x. Submission -> Rep Submission x)
-> (forall x. Rep Submission x -> Submission) -> Generic Submission
forall x. Rep Submission x -> Submission
forall x. Submission -> Rep Submission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Submission x -> Submission
$cfrom :: forall x. Submission -> Rep Submission x
Generic )
instance FromJSON Submission where
    parseJSON :: Value -> Parser Submission
parseJSON = RedditKind
-> String
-> (Object -> Parser Submission)
-> Value
-> Parser Submission
forall b a.
FromJSON b =>
RedditKind -> String -> (b -> Parser a) -> Value -> Parser a
withKind RedditKind
SubmissionKind String
"Submission" Object -> Parser Submission
submissionP
submissionP :: Object -> Parser Submission
submissionP :: Object -> Parser Submission
submissionP Object
o = do
    SubmissionID
submissionID <- Object
o Object -> Text -> Parser SubmissionID
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
    Text
title <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"title"
    Username
author <- Object
o Object -> Text -> Parser Username
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"author"
    SubredditName
subreddit <- Object
o Object -> Text -> Parser SubredditName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"subreddit"
    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")
    Integer
score <- Object
o Object -> Text -> Parser Integer
forall a. FromJSON a => Object -> Text -> Parser 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"
    SubmissionContent
content <- Object -> Parser SubmissionContent
contentP Object
o
    Text
permalink <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"permalink"
    Integer
numComments <- Object
o Object -> Text -> Parser Integer
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"num_comments"
    Integer
gilded <- Object
o Object -> Text -> Parser Integer
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"gilded"
    Maybe Rational
upvoteRatio <- Object
o Object -> Text -> Parser (Maybe Rational)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"upvote_ratio"
    Bool
isOC <- Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_original_content"
    Bool
clicked <- Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"clicked"
    Bool
over18 <- Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"over_18"
    Bool
locked <- Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"locked"
    Bool
spoiler <- Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"spoiler"
    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"
    Maybe PollData
pollData <- Object
o Object -> Text -> Parser (Maybe PollData)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"poll_data"
    Text
domain <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"domain"
    Submission -> Parser Submission
forall (f :: * -> *) a. Applicative f => a -> f a
pure Submission :: SubmissionID
-> Text
-> Username
-> SubmissionContent
-> SubredditName
-> UTCTime
-> Maybe UTCTime
-> Text
-> Text
-> Integer
-> Integer
-> Maybe Integer
-> Maybe Integer
-> Maybe Rational
-> Integer
-> Seq ItemReport
-> Seq ItemReport
-> Maybe Integer
-> Maybe Distinction
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe PollData
-> Submission
Submission { Bool
Integer
Maybe Integer
Maybe Rational
Maybe UTCTime
Maybe Distinction
Maybe PollData
Text
UTCTime
Seq ItemReport
SubredditName
Username
SubmissionContent
SubmissionID
domain :: Text
pollData :: Maybe PollData
distinguished :: Maybe Distinction
numReports :: Maybe Integer
modReports :: Seq ItemReport
userReports :: Seq ItemReport
spoiler :: Bool
locked :: Bool
over18 :: Bool
clicked :: Bool
isOC :: Bool
upvoteRatio :: Maybe Rational
gilded :: Integer
numComments :: Integer
permalink :: Text
content :: SubmissionContent
downs :: Maybe Integer
ups :: Maybe Integer
score :: Integer
edited :: Maybe UTCTime
created :: UTCTime
subreddit :: SubredditName
author :: Username
title :: Text
submissionID :: SubmissionID
$sel:pollData:Submission :: Maybe PollData
$sel:spoiler:Submission :: Bool
$sel:locked:Submission :: Bool
$sel:over18:Submission :: Bool
$sel:clicked:Submission :: Bool
$sel:isOC:Submission :: Bool
$sel:distinguished:Submission :: Maybe Distinction
$sel:numReports:Submission :: Maybe Integer
$sel:modReports:Submission :: Seq ItemReport
$sel:userReports:Submission :: Seq ItemReport
$sel:gilded:Submission :: Integer
$sel:upvoteRatio:Submission :: Maybe Rational
$sel:downs:Submission :: Maybe Integer
$sel:ups:Submission :: Maybe Integer
$sel:score:Submission :: Integer
$sel:numComments:Submission :: Integer
$sel:domain:Submission :: Text
$sel:permalink:Submission :: Text
$sel:edited:Submission :: Maybe UTCTime
$sel:created:Submission :: UTCTime
$sel:subreddit:Submission :: SubredditName
$sel:content:Submission :: SubmissionContent
$sel:author:Submission :: Username
$sel:title:Submission :: Text
$sel:submissionID:Submission :: SubmissionID
.. }
  where
    contentP :: Object -> Parser SubmissionContent
contentP Object
v = (Object
v Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"is_self") Parser Bool
-> (Bool -> Parser SubmissionContent) -> Parser SubmissionContent
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Bool
False -> [Parser SubmissionContent] -> Parser SubmissionContent
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum [ Text -> SubmissionContent
ExternalLink (Text -> SubmissionContent)
-> Parser Text -> Parser SubmissionContent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"url", SubmissionContent -> Parser SubmissionContent
forall (f :: * -> *) a. Applicative f => a -> f a
pure SubmissionContent
EmptySubmission ]
        Bool
True  -> [Parser SubmissionContent] -> Parser SubmissionContent
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum [ Text -> Text -> SubmissionContent
SelfText (Text -> Text -> SubmissionContent)
-> Parser Text -> Parser (Text -> SubmissionContent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"selftext" Parser (Text -> SubmissionContent)
-> Parser Text -> Parser SubmissionContent
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"selftext_html"
                      , SubmissionContent -> Parser SubmissionContent
forall (f :: * -> *) a. Applicative f => a -> f a
pure SubmissionContent
EmptySubmission
                      ]
instance Paginable Submission where
    type PaginateOptions Submission = ItemOpts Submission
    type PaginateThing Submission = SubmissionID
    defaultOpts :: PaginateOptions Submission
defaultOpts = PaginateOptions Submission
forall a. ItemOpts a
defaultItemOpts
    getFullname :: Submission -> PaginateThing Submission
getFullname Submission { SubmissionID
submissionID :: SubmissionID
$sel:submissionID:Submission :: Submission -> SubmissionID
submissionID } = PaginateThing Submission
SubmissionID
submissionID
data SubmissionContent
    = SelfText Body Body
    | ExternalLink URL
    | EmptySubmission
    deriving stock ( Int -> SubmissionContent -> ShowS
[SubmissionContent] -> ShowS
SubmissionContent -> String
(Int -> SubmissionContent -> ShowS)
-> (SubmissionContent -> String)
-> ([SubmissionContent] -> ShowS)
-> Show SubmissionContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubmissionContent] -> ShowS
$cshowList :: [SubmissionContent] -> ShowS
show :: SubmissionContent -> String
$cshow :: SubmissionContent -> String
showsPrec :: Int -> SubmissionContent -> ShowS
$cshowsPrec :: Int -> SubmissionContent -> ShowS
Show, SubmissionContent -> SubmissionContent -> Bool
(SubmissionContent -> SubmissionContent -> Bool)
-> (SubmissionContent -> SubmissionContent -> Bool)
-> Eq SubmissionContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubmissionContent -> SubmissionContent -> Bool
$c/= :: SubmissionContent -> SubmissionContent -> Bool
== :: SubmissionContent -> SubmissionContent -> Bool
$c== :: SubmissionContent -> SubmissionContent -> Bool
Eq, (forall x. SubmissionContent -> Rep SubmissionContent x)
-> (forall x. Rep SubmissionContent x -> SubmissionContent)
-> Generic SubmissionContent
forall x. Rep SubmissionContent x -> SubmissionContent
forall x. SubmissionContent -> Rep SubmissionContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubmissionContent x -> SubmissionContent
$cfrom :: forall x. SubmissionContent -> Rep SubmissionContent x
Generic )
data PollData = PollData
    { PollData -> Seq PollOption
options        :: Seq PollOption
      
    , PollData -> Integer
totalVoteCount :: Integer
      
    , PollData -> UTCTime
votingEnds     :: UTCTime
      
    , PollData -> Maybe Text
userSelection  :: Maybe PollOptionID
    }
    deriving stock ( Int -> PollData -> ShowS
[PollData] -> ShowS
PollData -> String
(Int -> PollData -> ShowS)
-> (PollData -> String) -> ([PollData] -> ShowS) -> Show PollData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollData] -> ShowS
$cshowList :: [PollData] -> ShowS
show :: PollData -> String
$cshow :: PollData -> String
showsPrec :: Int -> PollData -> ShowS
$cshowsPrec :: Int -> PollData -> ShowS
Show, PollData -> PollData -> Bool
(PollData -> PollData -> Bool)
-> (PollData -> PollData -> Bool) -> Eq PollData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollData -> PollData -> Bool
$c/= :: PollData -> PollData -> Bool
== :: PollData -> PollData -> Bool
$c== :: PollData -> PollData -> Bool
Eq, (forall x. PollData -> Rep PollData x)
-> (forall x. Rep PollData x -> PollData) -> Generic PollData
forall x. Rep PollData x -> PollData
forall x. PollData -> Rep PollData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PollData x -> PollData
$cfrom :: forall x. PollData -> Rep PollData x
Generic )
instance FromJSON PollData where
    parseJSON :: Value -> Parser PollData
parseJSON = String -> (Object -> Parser PollData) -> Value -> Parser PollData
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PollData" ((Object -> Parser PollData) -> Value -> Parser PollData)
-> (Object -> Parser PollData) -> Value -> Parser PollData
forall a b. (a -> b) -> a -> b
$ \Object
o -> Seq PollOption -> Integer -> UTCTime -> Maybe Text -> PollData
PollData (Seq PollOption -> Integer -> UTCTime -> Maybe Text -> PollData)
-> Parser (Seq PollOption)
-> Parser (Integer -> UTCTime -> Maybe Text -> PollData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Seq PollOption)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"options"
        Parser (Integer -> UTCTime -> Maybe Text -> PollData)
-> Parser Integer -> Parser (UTCTime -> Maybe Text -> PollData)
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
"total_vote_count"
        Parser (UTCTime -> Maybe Text -> PollData)
-> Parser UTCTime -> Parser (Maybe Text -> PollData)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (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
"voting_end_timestamp")
        Parser (Maybe Text -> PollData)
-> Parser (Maybe Text) -> Parser PollData
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"user_selection"
data PollOption = PollOption
    { PollOption -> Text
pollOptionID :: PollOptionID
    , PollOption -> Text
text         :: Body
      
    , PollOption -> Integer
voteCount    :: Integer
    }
    deriving stock ( Int -> PollOption -> ShowS
[PollOption] -> ShowS
PollOption -> String
(Int -> PollOption -> ShowS)
-> (PollOption -> String)
-> ([PollOption] -> ShowS)
-> Show PollOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollOption] -> ShowS
$cshowList :: [PollOption] -> ShowS
show :: PollOption -> String
$cshow :: PollOption -> String
showsPrec :: Int -> PollOption -> ShowS
$cshowsPrec :: Int -> PollOption -> ShowS
Show, PollOption -> PollOption -> Bool
(PollOption -> PollOption -> Bool)
-> (PollOption -> PollOption -> Bool) -> Eq PollOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollOption -> PollOption -> Bool
$c/= :: PollOption -> PollOption -> Bool
== :: PollOption -> PollOption -> Bool
$c== :: PollOption -> PollOption -> Bool
Eq, (forall x. PollOption -> Rep PollOption x)
-> (forall x. Rep PollOption x -> PollOption) -> Generic PollOption
forall x. Rep PollOption x -> PollOption
forall x. PollOption -> Rep PollOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PollOption x -> PollOption
$cfrom :: forall x. PollOption -> Rep PollOption x
Generic )
instance FromJSON PollOption where
    parseJSON :: Value -> Parser PollOption
parseJSON = Options -> Value -> Parser PollOption
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions { ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier }
      where
        fieldLabelModifier :: ShowS
fieldLabelModifier = \case
            String
"pollOptionID" -> String
"id"
            String
s              -> ShowS
snakeCase String
s
type PollOptionID = Text
data Collection = Collection
    { Collection -> Text
collectionID :: CollectionID
    , Collection -> Username
author       :: Username
    , Collection -> Text
title        :: Title
    , Collection -> SubredditID
subredditID  :: SubredditID
    , Collection -> Text
description  :: Body
    , Collection -> Text
permalink    :: URL
    , Collection -> UTCTime
created      :: UTCTime
    , Collection -> UTCTime
lastUpdated  :: UTCTime
    , Collection -> Seq SubmissionID
linkIDs      :: Seq SubmissionID
      
      
      
      
      
      
    , Collection -> Seq Submission
sortedLinks  :: Seq Submission
    , Collection -> Maybe CollectionLayout
layout       :: Maybe CollectionLayout
    }
    deriving stock ( Int -> Collection -> ShowS
[Collection] -> ShowS
Collection -> String
(Int -> Collection -> ShowS)
-> (Collection -> String)
-> ([Collection] -> ShowS)
-> Show Collection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Collection] -> ShowS
$cshowList :: [Collection] -> ShowS
show :: Collection -> String
$cshow :: Collection -> String
showsPrec :: Int -> Collection -> ShowS
$cshowsPrec :: Int -> Collection -> ShowS
Show, Collection -> Collection -> Bool
(Collection -> Collection -> Bool)
-> (Collection -> Collection -> Bool) -> Eq Collection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Collection -> Collection -> Bool
$c/= :: Collection -> Collection -> Bool
== :: Collection -> Collection -> Bool
$c== :: Collection -> Collection -> Bool
Eq, (forall x. Collection -> Rep Collection x)
-> (forall x. Rep Collection x -> Collection) -> Generic Collection
forall x. Rep Collection x -> Collection
forall x. Collection -> Rep Collection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Collection x -> Collection
$cfrom :: forall x. Collection -> Rep Collection x
Generic )
instance FromJSON Collection where
    parseJSON :: Value -> Parser Collection
parseJSON = String
-> (Object -> Parser Collection) -> Value -> Parser Collection
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Collection" ((Object -> Parser Collection) -> Value -> Parser Collection)
-> (Object -> Parser Collection) -> Value -> Parser Collection
forall a b. (a -> b) -> a -> b
$ \Object
o -> Text
-> Username
-> Text
-> SubredditID
-> Text
-> Text
-> UTCTime
-> UTCTime
-> Seq SubmissionID
-> Seq Submission
-> Maybe CollectionLayout
-> Collection
Collection
        (Text
 -> Username
 -> Text
 -> SubredditID
 -> Text
 -> Text
 -> UTCTime
 -> UTCTime
 -> Seq SubmissionID
 -> Seq Submission
 -> Maybe CollectionLayout
 -> Collection)
-> Parser Text
-> Parser
     (Username
      -> Text
      -> SubredditID
      -> Text
      -> Text
      -> UTCTime
      -> UTCTime
      -> Seq SubmissionID
      -> Seq Submission
      -> Maybe CollectionLayout
      -> Collection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"collection_id"
        Parser
  (Username
   -> Text
   -> SubredditID
   -> Text
   -> Text
   -> UTCTime
   -> UTCTime
   -> Seq SubmissionID
   -> Seq Submission
   -> Maybe CollectionLayout
   -> Collection)
-> Parser Username
-> Parser
     (Text
      -> SubredditID
      -> Text
      -> Text
      -> UTCTime
      -> UTCTime
      -> Seq SubmissionID
      -> Seq Submission
      -> Maybe CollectionLayout
      -> Collection)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Username
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"author_name"
        Parser
  (Text
   -> SubredditID
   -> Text
   -> Text
   -> UTCTime
   -> UTCTime
   -> Seq SubmissionID
   -> Seq Submission
   -> Maybe CollectionLayout
   -> Collection)
-> Parser Text
-> Parser
     (SubredditID
      -> Text
      -> Text
      -> UTCTime
      -> UTCTime
      -> Seq SubmissionID
      -> Seq Submission
      -> Maybe CollectionLayout
      -> Collection)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"title"
        Parser
  (SubredditID
   -> Text
   -> Text
   -> UTCTime
   -> UTCTime
   -> Seq SubmissionID
   -> Seq Submission
   -> Maybe CollectionLayout
   -> Collection)
-> Parser SubredditID
-> Parser
     (Text
      -> Text
      -> UTCTime
      -> UTCTime
      -> Seq SubmissionID
      -> Seq Submission
      -> Maybe CollectionLayout
      -> Collection)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser SubredditID
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"subreddit_id"
        Parser
  (Text
   -> Text
   -> UTCTime
   -> UTCTime
   -> Seq SubmissionID
   -> Seq Submission
   -> Maybe CollectionLayout
   -> Collection)
-> Parser Text
-> Parser
     (Text
      -> UTCTime
      -> UTCTime
      -> Seq SubmissionID
      -> Seq Submission
      -> Maybe CollectionLayout
      -> Collection)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"description"
        Parser
  (Text
   -> UTCTime
   -> UTCTime
   -> Seq SubmissionID
   -> Seq Submission
   -> Maybe CollectionLayout
   -> Collection)
-> Parser Text
-> Parser
     (UTCTime
      -> UTCTime
      -> Seq SubmissionID
      -> Seq Submission
      -> Maybe CollectionLayout
      -> Collection)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"permalink"
        Parser
  (UTCTime
   -> UTCTime
   -> Seq SubmissionID
   -> Seq Submission
   -> Maybe CollectionLayout
   -> Collection)
-> Parser UTCTime
-> Parser
     (UTCTime
      -> Seq SubmissionID
      -> Seq Submission
      -> Maybe CollectionLayout
      -> Collection)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Double -> UTCTime
doubleToUTC (Double -> UTCTime) -> Parser Double -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Double
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"created_at_utc")
        Parser
  (UTCTime
   -> Seq SubmissionID
   -> Seq Submission
   -> Maybe CollectionLayout
   -> Collection)
-> Parser UTCTime
-> Parser
     (Seq SubmissionID
      -> Seq Submission -> Maybe CollectionLayout -> Collection)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Double -> UTCTime
doubleToUTC (Double -> UTCTime) -> Parser Double -> Parser UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Double
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"last_update_utc")
        Parser
  (Seq SubmissionID
   -> Seq Submission -> Maybe CollectionLayout -> Collection)
-> Parser (Seq SubmissionID)
-> Parser (Seq Submission -> Maybe CollectionLayout -> Collection)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Seq SubmissionID)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"link_ids"
        Parser (Seq Submission -> Maybe CollectionLayout -> Collection)
-> Parser (Seq Submission)
-> Parser (Maybe CollectionLayout -> Collection)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Maybe (Listing () Submission) -> Parser (Seq Submission)
linksP (Maybe (Listing () Submission) -> Parser (Seq Submission))
-> Parser (Maybe (Listing () Submission))
-> Parser (Seq Submission)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser (Maybe (Listing () Submission))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"sorted_links")
        Parser (Maybe CollectionLayout -> Collection)
-> Parser (Maybe CollectionLayout) -> Parser Collection
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe CollectionLayout)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"display_layout"
      where
        linksP :: Maybe (Listing () Submission) -> Parser (Seq Submission)
linksP      = \case
            Maybe (Listing () Submission)
Nothing -> Seq Submission -> Parser (Seq Submission)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Seq Submission
forall a. Monoid a => a
mempty
            Just (Listing { Seq Submission
$sel:children:Listing :: forall t a. Listing t a -> Seq a
children :: Seq Submission
children } :: Listing () Submission) ->
                Seq Submission -> Parser (Seq Submission)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Seq Submission
children
        doubleToUTC :: Double -> UTCTime
doubleToUTC = Integer -> UTCTime
integerToUTC (Integer -> UTCTime) -> (Double -> Integer) -> Double -> UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b. (RealFrac Double, Integral b) => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round @Double
data CollectionLayout
    = Gallery
    | Timeline
    deriving stock ( Int -> CollectionLayout -> ShowS
[CollectionLayout] -> ShowS
CollectionLayout -> String
(Int -> CollectionLayout -> ShowS)
-> (CollectionLayout -> String)
-> ([CollectionLayout] -> ShowS)
-> Show CollectionLayout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CollectionLayout] -> ShowS
$cshowList :: [CollectionLayout] -> ShowS
show :: CollectionLayout -> String
$cshow :: CollectionLayout -> String
showsPrec :: Int -> CollectionLayout -> ShowS
$cshowsPrec :: Int -> CollectionLayout -> ShowS
Show, CollectionLayout -> CollectionLayout -> Bool
(CollectionLayout -> CollectionLayout -> Bool)
-> (CollectionLayout -> CollectionLayout -> Bool)
-> Eq CollectionLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CollectionLayout -> CollectionLayout -> Bool
$c/= :: CollectionLayout -> CollectionLayout -> Bool
== :: CollectionLayout -> CollectionLayout -> Bool
$c== :: CollectionLayout -> CollectionLayout -> Bool
Eq, (forall x. CollectionLayout -> Rep CollectionLayout x)
-> (forall x. Rep CollectionLayout x -> CollectionLayout)
-> Generic CollectionLayout
forall x. Rep CollectionLayout x -> CollectionLayout
forall x. CollectionLayout -> Rep CollectionLayout x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CollectionLayout x -> CollectionLayout
$cfrom :: forall x. CollectionLayout -> Rep CollectionLayout x
Generic )
instance FromJSON CollectionLayout where
    parseJSON :: Value -> Parser CollectionLayout
parseJSON = Options -> Value -> Parser CollectionLayout
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON 
        Options
defaultOptions { constructorTagModifier :: ShowS
constructorTagModifier = (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
toUpper }
instance ToHttpApiData CollectionLayout where
    toQueryParam :: CollectionLayout -> Text
toQueryParam = Text -> Text
T.toUpper (Text -> Text)
-> (CollectionLayout -> Text) -> CollectionLayout -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CollectionLayout -> Text
forall a. Show a => a -> Text
showTextData
type CollectionID = Text
data NewCollection = NewCollection
    { NewCollection -> Text
title       :: Title
    , NewCollection -> Text
description :: Body
    , NewCollection -> SubredditID
subredditID :: SubredditID
    , NewCollection -> Maybe CollectionLayout
layout      :: Maybe CollectionLayout
    }
    deriving stock ( Int -> NewCollection -> ShowS
[NewCollection] -> ShowS
NewCollection -> String
(Int -> NewCollection -> ShowS)
-> (NewCollection -> String)
-> ([NewCollection] -> ShowS)
-> Show NewCollection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewCollection] -> ShowS
$cshowList :: [NewCollection] -> ShowS
show :: NewCollection -> String
$cshow :: NewCollection -> String
showsPrec :: Int -> NewCollection -> ShowS
$cshowsPrec :: Int -> NewCollection -> ShowS
Show, NewCollection -> NewCollection -> Bool
(NewCollection -> NewCollection -> Bool)
-> (NewCollection -> NewCollection -> Bool) -> Eq NewCollection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewCollection -> NewCollection -> Bool
$c/= :: NewCollection -> NewCollection -> Bool
== :: NewCollection -> NewCollection -> Bool
$c== :: NewCollection -> NewCollection -> Bool
Eq, (forall x. NewCollection -> Rep NewCollection x)
-> (forall x. Rep NewCollection x -> NewCollection)
-> Generic NewCollection
forall x. Rep NewCollection x -> NewCollection
forall x. NewCollection -> Rep NewCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NewCollection x -> NewCollection
$cfrom :: forall x. NewCollection -> Rep NewCollection x
Generic )
instance ToForm NewCollection where
    toForm :: NewCollection -> Form
toForm NewCollection { Maybe CollectionLayout
Text
SubredditID
layout :: Maybe CollectionLayout
subredditID :: SubredditID
description :: Text
title :: Text
$sel:layout:NewCollection :: NewCollection -> Maybe CollectionLayout
$sel:subredditID:NewCollection :: NewCollection -> SubredditID
$sel:description:NewCollection :: NewCollection -> Text
$sel:title:NewCollection :: NewCollection -> Text
.. } = [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList
        ([Item Form] -> Form) -> [Item Form] -> Form
forall a b. (a -> b) -> a -> b
$ [ (Text
"title", Text
title)
          , (Text
"description", Text
description)
          , (Text
"sr_fullname", SubredditID -> Text
forall a. Thing a => a -> Text
fullname SubredditID
subredditID)
          ]
        [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> ((Text, Text) -> [(Text, Text)])
-> Maybe (Text, Text) -> [(Text, Text)]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Text, Text) -> [(Text, Text)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Text
"display_layout", ) (Text -> (Text, Text))
-> (CollectionLayout -> Text) -> CollectionLayout -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CollectionLayout -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam (CollectionLayout -> (Text, Text))
-> Maybe CollectionLayout -> Maybe (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe CollectionLayout
layout)
data SubmissionOptions = SubmissionOptions
    { 
      SubmissionOptions -> Text
title        :: Title
    , SubmissionOptions -> SubredditName
subreddit    :: SubredditName
    , SubmissionOptions -> Bool
nsfw         :: Bool
    , SubmissionOptions -> Bool
sendreplies  :: Bool
    , SubmissionOptions -> Bool
resubmit     :: Bool
    , SubmissionOptions -> Bool
spoiler      :: Bool
      
      
    , SubmissionOptions -> Maybe Text
collectionID :: Maybe CollectionID
    , SubmissionOptions -> Maybe Text
flairID      :: Maybe FlairID
      
      
      
      
      
      
    , SubmissionOptions -> Maybe FlairText
flairText    :: Maybe FlairText
    }
    deriving stock ( Int -> SubmissionOptions -> ShowS
[SubmissionOptions] -> ShowS
SubmissionOptions -> String
(Int -> SubmissionOptions -> ShowS)
-> (SubmissionOptions -> String)
-> ([SubmissionOptions] -> ShowS)
-> Show SubmissionOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubmissionOptions] -> ShowS
$cshowList :: [SubmissionOptions] -> ShowS
show :: SubmissionOptions -> String
$cshow :: SubmissionOptions -> String
showsPrec :: Int -> SubmissionOptions -> ShowS
$cshowsPrec :: Int -> SubmissionOptions -> ShowS
Show, SubmissionOptions -> SubmissionOptions -> Bool
(SubmissionOptions -> SubmissionOptions -> Bool)
-> (SubmissionOptions -> SubmissionOptions -> Bool)
-> Eq SubmissionOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubmissionOptions -> SubmissionOptions -> Bool
$c/= :: SubmissionOptions -> SubmissionOptions -> Bool
== :: SubmissionOptions -> SubmissionOptions -> Bool
$c== :: SubmissionOptions -> SubmissionOptions -> Bool
Eq, (forall x. SubmissionOptions -> Rep SubmissionOptions x)
-> (forall x. Rep SubmissionOptions x -> SubmissionOptions)
-> Generic SubmissionOptions
forall x. Rep SubmissionOptions x -> SubmissionOptions
forall x. SubmissionOptions -> Rep SubmissionOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubmissionOptions x -> SubmissionOptions
$cfrom :: forall x. SubmissionOptions -> Rep SubmissionOptions x
Generic )
instance ToForm SubmissionOptions where
    toForm :: SubmissionOptions -> Form
toForm SubmissionOptions { Bool
Maybe Text
Maybe FlairText
Text
SubredditName
flairText :: Maybe FlairText
flairID :: Maybe Text
collectionID :: Maybe Text
spoiler :: Bool
resubmit :: Bool
sendreplies :: Bool
nsfw :: Bool
subreddit :: SubredditName
title :: Text
$sel:flairText:SubmissionOptions :: SubmissionOptions -> Maybe FlairText
$sel:flairID:SubmissionOptions :: SubmissionOptions -> Maybe Text
$sel:collectionID:SubmissionOptions :: SubmissionOptions -> Maybe Text
$sel:spoiler:SubmissionOptions :: SubmissionOptions -> Bool
$sel:resubmit:SubmissionOptions :: SubmissionOptions -> Bool
$sel:sendreplies:SubmissionOptions :: SubmissionOptions -> Bool
$sel:nsfw:SubmissionOptions :: SubmissionOptions -> Bool
$sel:subreddit:SubmissionOptions :: SubmissionOptions -> SubredditName
$sel:title:SubmissionOptions :: SubmissionOptions -> Text
.. } = [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList
        ([Item Form] -> Form) -> [Item Form] -> Form
forall a b. (a -> b) -> a -> b
$ [ (Text
"sr", SubredditName -> Text
forall s t a b. Wrapped s t a b => s -> a
wrappedTo SubredditName
subreddit)
          , (Text
"title", Text
title)
          , (Text
"nsfw", Bool -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Bool
nsfw)
          , (Text
"spoiler", Bool -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Bool
spoiler)
          , (Text
"sendreplies", Bool -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Bool
sendreplies)
          , (Text
"resubmit", Bool -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Bool
resubmit)
          , (Text
"extension", Text
"json")
          , (Text
"api_type", Text
"json")
          ]
        [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> [Maybe (Text, Text)] -> [(Text, Text)]
forall a. [Maybe a] -> [a]
catMaybes [ (Text
"collection_id", ) (Text -> (Text, Text)) -> Maybe Text -> Maybe (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
collectionID
                     , (Text
"flair_id", ) (Text -> (Text, Text)) -> Maybe Text -> Maybe (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
flairID
                     , (Text
"flair_text", ) (Text -> (Text, Text))
-> (FlairText -> Text) -> FlairText -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlairText -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam (FlairText -> (Text, Text))
-> Maybe FlairText -> Maybe (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FlairText
flairText
                     ]
data NewSubmission
    = SelfPost Body SubmissionOptions
    | WithInlineMedia Fancypants SubmissionOptions
      
      
      
      
    | Link URL SubmissionOptions
    | ImagePost UploadURL SubmissionOptions
      
      
      
    | VideoPost UploadURL UploadURL Bool SubmissionOptions
      
      
      
    deriving stock ( Int -> NewSubmission -> ShowS
[NewSubmission] -> ShowS
NewSubmission -> String
(Int -> NewSubmission -> ShowS)
-> (NewSubmission -> String)
-> ([NewSubmission] -> ShowS)
-> Show NewSubmission
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewSubmission] -> ShowS
$cshowList :: [NewSubmission] -> ShowS
show :: NewSubmission -> String
$cshow :: NewSubmission -> String
showsPrec :: Int -> NewSubmission -> ShowS
$cshowsPrec :: Int -> NewSubmission -> ShowS
Show, NewSubmission -> NewSubmission -> Bool
(NewSubmission -> NewSubmission -> Bool)
-> (NewSubmission -> NewSubmission -> Bool) -> Eq NewSubmission
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewSubmission -> NewSubmission -> Bool
$c/= :: NewSubmission -> NewSubmission -> Bool
== :: NewSubmission -> NewSubmission -> Bool
$c== :: NewSubmission -> NewSubmission -> Bool
Eq, (forall x. NewSubmission -> Rep NewSubmission x)
-> (forall x. Rep NewSubmission x -> NewSubmission)
-> Generic NewSubmission
forall x. Rep NewSubmission x -> NewSubmission
forall x. NewSubmission -> Rep NewSubmission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NewSubmission x -> NewSubmission
$cfrom :: forall x. NewSubmission -> Rep NewSubmission x
Generic )
instance ToForm NewSubmission where
    toForm :: NewSubmission -> Form
toForm = \case
        SelfPost Text
body SubmissionOptions
os ->
            [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList [ (Text
"kind", Text
"self"), (Text
"text", Text
body) ] Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> SubmissionOptions -> Form
forall a. ToForm a => a -> Form
toForm SubmissionOptions
os
        WithInlineMedia Fancypants
body SubmissionOptions
os ->
            [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList [ (Text
"kind", Text
"self"), (Text
"richtext_json", Fancypants -> Text
forall a. ToJSON a => a -> Text
textEncode Fancypants
body) ]
            Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> SubmissionOptions -> Form
forall a. ToForm a => a -> Form
toForm SubmissionOptions
os
        Link Text
url SubmissionOptions
os ->
            [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList [ (Text
"kind", Text
"link"), (Text
"url", Text
url) ] Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> SubmissionOptions -> Form
forall a. ToForm a => a -> Form
toForm SubmissionOptions
os
        ImagePost UploadURL
url SubmissionOptions
os ->
            [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList [ (Text
"kind", Text
"image"), (Text
"url", UploadURL -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam UploadURL
url) ]
            Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> SubmissionOptions -> Form
forall a. ToForm a => a -> Form
toForm SubmissionOptions
os
        VideoPost UploadURL
url UploadURL
thmb Bool
videogif SubmissionOptions
os ->
            [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList [ (Text
"kind", Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"video" Text
"videogif" Bool
videogif)
                     , (Text
"url", UploadURL -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam UploadURL
url)
                     , (Text
"video_poster_url", UploadURL -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam UploadURL
thmb)
                     ]
            Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> SubmissionOptions -> Form
forall a. ToForm a => a -> Form
toForm SubmissionOptions
os
mkSubmissionOptions :: SubredditName -> Title -> SubmissionOptions
mkSubmissionOptions :: SubredditName -> Text -> SubmissionOptions
mkSubmissionOptions SubredditName
subreddit Text
title = SubmissionOptions :: Text
-> SubredditName
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> Maybe Text
-> Maybe FlairText
-> SubmissionOptions
SubmissionOptions
    { $sel:nsfw:SubmissionOptions :: Bool
nsfw         = Bool
False
    , $sel:sendreplies:SubmissionOptions :: Bool
sendreplies  = Bool
True
    , $sel:resubmit:SubmissionOptions :: Bool
resubmit     = Bool
True
    , $sel:spoiler:SubmissionOptions :: Bool
spoiler      = Bool
False
    , $sel:collectionID:SubmissionOptions :: Maybe Text
collectionID = Maybe Text
forall a. Maybe a
Nothing
    , $sel:flairID:SubmissionOptions :: Maybe Text
flairID      = Maybe Text
forall a. Maybe a
Nothing
    , $sel:flairText:SubmissionOptions :: Maybe FlairText
flairText    = Maybe FlairText
forall a. Maybe a
Nothing
    , Text
SubredditName
title :: Text
subreddit :: SubredditName
$sel:subreddit:SubmissionOptions :: SubredditName
$sel:title:SubmissionOptions :: Text
..
    }
data S3UploadLease = S3UploadLease
    { S3UploadLease -> Text
action       :: URL
      
    , S3UploadLease -> HashMap Text Text
fields       :: HashMap Text Text
      
    , S3UploadLease -> Text
key          :: Text
    , S3UploadLease -> Text
websocketURL :: URL
    , S3UploadLease -> UploadURL
assetID      :: UploadURL
    }
    deriving stock ( Int -> S3UploadLease -> ShowS
[S3UploadLease] -> ShowS
S3UploadLease -> String
(Int -> S3UploadLease -> ShowS)
-> (S3UploadLease -> String)
-> ([S3UploadLease] -> ShowS)
-> Show S3UploadLease
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [S3UploadLease] -> ShowS
$cshowList :: [S3UploadLease] -> ShowS
show :: S3UploadLease -> String
$cshow :: S3UploadLease -> String
showsPrec :: Int -> S3UploadLease -> ShowS
$cshowsPrec :: Int -> S3UploadLease -> ShowS
Show, S3UploadLease -> S3UploadLease -> Bool
(S3UploadLease -> S3UploadLease -> Bool)
-> (S3UploadLease -> S3UploadLease -> Bool) -> Eq S3UploadLease
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: S3UploadLease -> S3UploadLease -> Bool
$c/= :: S3UploadLease -> S3UploadLease -> Bool
== :: S3UploadLease -> S3UploadLease -> Bool
$c== :: S3UploadLease -> S3UploadLease -> Bool
Eq, (forall x. S3UploadLease -> Rep S3UploadLease x)
-> (forall x. Rep S3UploadLease x -> S3UploadLease)
-> Generic S3UploadLease
forall x. Rep S3UploadLease x -> S3UploadLease
forall x. S3UploadLease -> Rep S3UploadLease x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep S3UploadLease x -> S3UploadLease
$cfrom :: forall x. S3UploadLease -> Rep S3UploadLease x
Generic )
instance FromJSON S3UploadLease where
    parseJSON :: Value -> Parser S3UploadLease
parseJSON = String
-> (Object -> Parser S3UploadLease)
-> Value
-> Parser S3UploadLease
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"S3UploadLease" ((Object -> Parser S3UploadLease) -> Value -> Parser S3UploadLease)
-> (Object -> Parser S3UploadLease)
-> Value
-> Parser S3UploadLease
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        Object
lease <- Object
o Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"args"
        
        Text
action <- (Text
"https:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> Parser Text -> Parser Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
lease Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"action"
        HashMap Text Text
fields <- Value -> Parser (HashMap Text Text)
fieldsP (Value -> Parser (HashMap Text Text))
-> Parser Value -> Parser (HashMap Text Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
lease Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"fields"
        Text
key <- Parser Text -> (Text -> Parser Text) -> Maybe Text -> Parser Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser Text
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Missing key") Text -> Parser Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Text -> Parser Text) -> Maybe Text -> Parser Text
forall a b. (a -> b) -> a -> b
$ Text -> HashMap Text Text -> Maybe Text
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup Text
"key" HashMap Text Text
fields
        Text
websocketURL <- (Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"websocket_url") (Object -> Parser Text) -> Parser Object -> Parser Text
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
"asset"
        UploadURL
assetID <- (Object -> Text -> Parser UploadURL
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"asset_id") (Object -> Parser UploadURL) -> Parser Object -> Parser UploadURL
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
"asset"
        S3UploadLease -> Parser S3UploadLease
forall (f :: * -> *) a. Applicative f => a -> f a
pure S3UploadLease :: Text
-> HashMap Text Text -> Text -> Text -> UploadURL -> S3UploadLease
S3UploadLease { Text
HashMap Text Text
UploadURL
assetID :: UploadURL
websocketURL :: Text
key :: Text
fields :: HashMap Text Text
action :: Text
$sel:assetID:S3UploadLease :: UploadURL
$sel:websocketURL:S3UploadLease :: Text
$sel:key:S3UploadLease :: Text
$sel:fields:S3UploadLease :: HashMap Text Text
$sel:action:S3UploadLease :: Text
.. }
      where
        fieldsP :: Value -> Parser (HashMap Text Text)
fieldsP = String
-> (Array -> Parser (HashMap Text Text))
-> Value
-> Parser (HashMap Text Text)
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray String
"S3UploadLease.fields"
            ((Array -> Parser (HashMap Text Text))
 -> Value -> Parser (HashMap Text Text))
-> (Array -> Parser (HashMap Text Text))
-> Value
-> Parser (HashMap Text Text)
forall a b. (a -> b) -> a -> b
$ ([(Text, Text)] -> HashMap Text Text)
-> Parser [(Text, Text)] -> Parser (HashMap Text Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(Text, Text)] -> HashMap Text Text
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList (Parser [(Text, Text)] -> Parser (HashMap Text Text))
-> (Array -> Parser [(Text, Text)])
-> Array
-> Parser (HashMap Text Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> Parser (Text, Text)) -> [Value] -> Parser [(Text, Text)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Value -> Parser (Text, Text)
fieldP ([Value] -> Parser [(Text, Text)])
-> (Array -> [Value]) -> Array -> Parser [(Text, Text)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> [Value]
forall l. IsList l => l -> [Item l]
toList
        fieldP :: Value -> Parser (Text, Text)
fieldP  = String
-> (Object -> Parser (Text, Text)) -> Value -> Parser (Text, Text)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"S3UploadLease.fields.field"
            ((Object -> Parser (Text, Text)) -> Value -> Parser (Text, Text))
-> (Object -> Parser (Text, Text)) -> Value -> Parser (Text, Text)
forall a b. (a -> b) -> a -> b
$ \Object
o -> (,) (Text -> Text -> (Text, Text))
-> Parser Text -> Parser (Text -> (Text, Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"name" Parser (Text -> (Text, Text)) -> Parser Text -> Parser (Text, Text)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"value"
data UploadType
    = SelfPostUpload
    | LinkUpload
    | GalleryUpload
    deriving stock ( Int -> UploadType -> ShowS
[UploadType] -> ShowS
UploadType -> String
(Int -> UploadType -> ShowS)
-> (UploadType -> String)
-> ([UploadType] -> ShowS)
-> Show UploadType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadType] -> ShowS
$cshowList :: [UploadType] -> ShowS
show :: UploadType -> String
$cshow :: UploadType -> String
showsPrec :: Int -> UploadType -> ShowS
$cshowsPrec :: Int -> UploadType -> ShowS
Show, UploadType -> UploadType -> Bool
(UploadType -> UploadType -> Bool)
-> (UploadType -> UploadType -> Bool) -> Eq UploadType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadType -> UploadType -> Bool
$c/= :: UploadType -> UploadType -> Bool
== :: UploadType -> UploadType -> Bool
$c== :: UploadType -> UploadType -> Bool
Eq, (forall x. UploadType -> Rep UploadType x)
-> (forall x. Rep UploadType x -> UploadType) -> Generic UploadType
forall x. Rep UploadType x -> UploadType
forall x. UploadType -> Rep UploadType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadType x -> UploadType
$cfrom :: forall x. UploadType -> Rep UploadType x
Generic )
data UploadResult = UploadResult { UploadResult -> Text
resultType :: Text, UploadResult -> Text
redirectURL :: URL }
    deriving stock ( Int -> UploadResult -> ShowS
[UploadResult] -> ShowS
UploadResult -> String
(Int -> UploadResult -> ShowS)
-> (UploadResult -> String)
-> ([UploadResult] -> ShowS)
-> Show UploadResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadResult] -> ShowS
$cshowList :: [UploadResult] -> ShowS
show :: UploadResult -> String
$cshow :: UploadResult -> String
showsPrec :: Int -> UploadResult -> ShowS
$cshowsPrec :: Int -> UploadResult -> ShowS
Show, UploadResult -> UploadResult -> Bool
(UploadResult -> UploadResult -> Bool)
-> (UploadResult -> UploadResult -> Bool) -> Eq UploadResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadResult -> UploadResult -> Bool
$c/= :: UploadResult -> UploadResult -> Bool
== :: UploadResult -> UploadResult -> Bool
$c== :: UploadResult -> UploadResult -> Bool
Eq, (forall x. UploadResult -> Rep UploadResult x)
-> (forall x. Rep UploadResult x -> UploadResult)
-> Generic UploadResult
forall x. Rep UploadResult x -> UploadResult
forall x. UploadResult -> Rep UploadResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadResult x -> UploadResult
$cfrom :: forall x. UploadResult -> Rep UploadResult x
Generic )
instance FromJSON UploadResult where
    parseJSON :: Value -> Parser UploadResult
parseJSON = String
-> (Object -> Parser UploadResult) -> Value -> Parser UploadResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UploadResult" ((Object -> Parser UploadResult) -> Value -> Parser UploadResult)
-> (Object -> Parser UploadResult) -> Value -> Parser UploadResult
forall a b. (a -> b) -> a -> b
$ \Object
o -> Text -> Text -> UploadResult
UploadResult (Text -> Text -> UploadResult)
-> Parser Text -> Parser (Text -> UploadResult)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"type"
        Parser (Text -> UploadResult) -> Parser Text -> Parser UploadResult
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"redirect") (Object -> Parser Text) -> Parser Object -> Parser Text
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
"payload")
data CrosspostOptions = CrosspostOptions
    { CrosspostOptions -> SubredditName
subreddit   :: SubredditName
    , CrosspostOptions -> Text
title       :: Title
    , CrosspostOptions -> Bool
nsfw        :: Bool
    , CrosspostOptions -> Bool
sendreplies :: Bool
    , CrosspostOptions -> Bool
spoiler     :: Bool
    , CrosspostOptions -> Maybe Text
flairID     :: Maybe FlairID
      
      
      
      
      
      
    , CrosspostOptions -> Maybe FlairText
flairText   :: Maybe FlairText
    }
    deriving stock ( Int -> CrosspostOptions -> ShowS
[CrosspostOptions] -> ShowS
CrosspostOptions -> String
(Int -> CrosspostOptions -> ShowS)
-> (CrosspostOptions -> String)
-> ([CrosspostOptions] -> ShowS)
-> Show CrosspostOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CrosspostOptions] -> ShowS
$cshowList :: [CrosspostOptions] -> ShowS
show :: CrosspostOptions -> String
$cshow :: CrosspostOptions -> String
showsPrec :: Int -> CrosspostOptions -> ShowS
$cshowsPrec :: Int -> CrosspostOptions -> ShowS
Show, CrosspostOptions -> CrosspostOptions -> Bool
(CrosspostOptions -> CrosspostOptions -> Bool)
-> (CrosspostOptions -> CrosspostOptions -> Bool)
-> Eq CrosspostOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CrosspostOptions -> CrosspostOptions -> Bool
$c/= :: CrosspostOptions -> CrosspostOptions -> Bool
== :: CrosspostOptions -> CrosspostOptions -> Bool
$c== :: CrosspostOptions -> CrosspostOptions -> Bool
Eq, (forall x. CrosspostOptions -> Rep CrosspostOptions x)
-> (forall x. Rep CrosspostOptions x -> CrosspostOptions)
-> Generic CrosspostOptions
forall x. Rep CrosspostOptions x -> CrosspostOptions
forall x. CrosspostOptions -> Rep CrosspostOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CrosspostOptions x -> CrosspostOptions
$cfrom :: forall x. CrosspostOptions -> Rep CrosspostOptions x
Generic )
instance ToForm CrosspostOptions where
    toForm :: CrosspostOptions -> Form
toForm CrosspostOptions { Bool
Maybe Text
Maybe FlairText
Text
SubredditName
flairText :: Maybe FlairText
flairID :: Maybe Text
spoiler :: Bool
sendreplies :: Bool
nsfw :: Bool
title :: Text
subreddit :: SubredditName
$sel:flairText:CrosspostOptions :: CrosspostOptions -> Maybe FlairText
$sel:flairID:CrosspostOptions :: CrosspostOptions -> Maybe Text
$sel:spoiler:CrosspostOptions :: CrosspostOptions -> Bool
$sel:sendreplies:CrosspostOptions :: CrosspostOptions -> Bool
$sel:nsfw:CrosspostOptions :: CrosspostOptions -> Bool
$sel:title:CrosspostOptions :: CrosspostOptions -> Text
$sel:subreddit:CrosspostOptions :: CrosspostOptions -> SubredditName
.. } = [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList
        ([Item Form] -> Form) -> [Item Form] -> Form
forall a b. (a -> b) -> a -> b
$ [ (Text
"sr", SubredditName -> Text
forall s t a b. Wrapped s t a b => s -> a
wrappedTo SubredditName
subreddit)
          , (Text
"title", Text
title)
          , (Text
"nsfw", Bool -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Bool
nsfw)
          , (Text
"spoiler", Bool -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Bool
spoiler)
          , (Text
"sendreplies", Bool -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Bool
sendreplies)
          , (Text
"kind", Text
"crosspost")
          , (Text
"api_type", Text
"json")
          ]
        [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> [Maybe (Text, Text)] -> [(Text, Text)]
forall a. [Maybe a] -> [a]
catMaybes [ (Text
"flair_id", ) (Text -> (Text, Text)) -> Maybe Text -> Maybe (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
flairID
                     , (Text
"flair_text", ) (Text -> (Text, Text))
-> (FlairText -> Text) -> FlairText -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlairText -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam (FlairText -> (Text, Text))
-> Maybe FlairText -> Maybe (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FlairText
flairText
                     ]
newtype PostedCrosspost = PostedCrosspost SubmissionID
    deriving stock ( Int -> PostedCrosspost -> ShowS
[PostedCrosspost] -> ShowS
PostedCrosspost -> String
(Int -> PostedCrosspost -> ShowS)
-> (PostedCrosspost -> String)
-> ([PostedCrosspost] -> ShowS)
-> Show PostedCrosspost
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostedCrosspost] -> ShowS
$cshowList :: [PostedCrosspost] -> ShowS
show :: PostedCrosspost -> String
$cshow :: PostedCrosspost -> String
showsPrec :: Int -> PostedCrosspost -> ShowS
$cshowsPrec :: Int -> PostedCrosspost -> ShowS
Show, (forall x. PostedCrosspost -> Rep PostedCrosspost x)
-> (forall x. Rep PostedCrosspost x -> PostedCrosspost)
-> Generic PostedCrosspost
forall x. Rep PostedCrosspost x -> PostedCrosspost
forall x. PostedCrosspost -> Rep PostedCrosspost x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PostedCrosspost x -> PostedCrosspost
$cfrom :: forall x. PostedCrosspost -> Rep PostedCrosspost x
Generic )
instance FromJSON PostedCrosspost where
    parseJSON :: Value -> Parser PostedCrosspost
parseJSON = String
-> (Object -> Parser PostedCrosspost)
-> Value
-> Parser PostedCrosspost
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PostedLiveThread"
        ((Object -> Parser PostedCrosspost)
 -> Value -> Parser PostedCrosspost)
-> (Object -> Parser PostedCrosspost)
-> Value
-> Parser PostedCrosspost
forall a b. (a -> b) -> a -> b
$ (SubmissionID -> PostedCrosspost)
-> Parser SubmissionID -> Parser PostedCrosspost
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SubmissionID -> PostedCrosspost
PostedCrosspost (Parser SubmissionID -> Parser PostedCrosspost)
-> (Object -> Parser SubmissionID)
-> Object
-> Parser PostedCrosspost
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Object -> Text -> Parser SubmissionID
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id") (Object -> Parser SubmissionID)
-> (Object -> Parser Object) -> Object -> Parser SubmissionID
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") (Object -> Parser Object)
-> (Object -> Parser Object) -> Object -> Parser Object
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
"json"))
mkCrosspostOptions :: SubredditName -> Title -> CrosspostOptions
mkCrosspostOptions :: SubredditName -> Text -> CrosspostOptions
mkCrosspostOptions SubredditName
subreddit Text
title = CrosspostOptions :: SubredditName
-> Text
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> Maybe FlairText
-> CrosspostOptions
CrosspostOptions
    { $sel:nsfw:CrosspostOptions :: Bool
nsfw        = Bool
False
    , $sel:sendreplies:CrosspostOptions :: Bool
sendreplies = Bool
True
    , $sel:spoiler:CrosspostOptions :: Bool
spoiler     = Bool
False
    , $sel:flairID:CrosspostOptions :: Maybe Text
flairID     = Maybe Text
forall a. Maybe a
Nothing
    , $sel:flairText:CrosspostOptions :: Maybe FlairText
flairText   = Maybe FlairText
forall a. Maybe a
Nothing
    , Text
SubredditName
title :: Text
subreddit :: SubredditName
$sel:title:CrosspostOptions :: Text
$sel:subreddit:CrosspostOptions :: SubredditName
..
    }
data Poll t = Poll
    { 
      Poll t -> t Text
options  :: t Text
      
    , Poll t -> Word
duration :: Word
      
    , Poll t -> Maybe Text
selftext :: Maybe Body
    }
    deriving stock ( (forall x. Poll t -> Rep (Poll t) x)
-> (forall x. Rep (Poll t) x -> Poll t) -> Generic (Poll t)
forall x. Rep (Poll t) x -> Poll t
forall x. Poll t -> Rep (Poll t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (t :: * -> *) x. Rep (Poll t) x -> Poll t
forall (t :: * -> *) x. Poll t -> Rep (Poll t) x
$cto :: forall (t :: * -> *) x. Rep (Poll t) x -> Poll t
$cfrom :: forall (t :: * -> *) x. Poll t -> Rep (Poll t) x
Generic )
deriving stock instance (Show (t Text)) => Show (Poll t)
deriving stock instance (Eq (t Text)) => Eq (Poll t)
data PollSubmission t = PollSubmission (Poll t) SubmissionOptions
    deriving stock ( (forall x. PollSubmission t -> Rep (PollSubmission t) x)
-> (forall x. Rep (PollSubmission t) x -> PollSubmission t)
-> Generic (PollSubmission t)
forall x. Rep (PollSubmission t) x -> PollSubmission t
forall x. PollSubmission t -> Rep (PollSubmission t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (t :: * -> *) x.
Rep (PollSubmission t) x -> PollSubmission t
forall (t :: * -> *) x.
PollSubmission t -> Rep (PollSubmission t) x
$cto :: forall (t :: * -> *) x.
Rep (PollSubmission t) x -> PollSubmission t
$cfrom :: forall (t :: * -> *) x.
PollSubmission t -> Rep (PollSubmission t) x
Generic )
instance Foldable t => ToJSON (PollSubmission t) where
    toJSON :: PollSubmission t -> Value
toJSON (PollSubmission Poll { t Text
Maybe Text
Word
selftext :: Maybe Text
duration :: Word
options :: t Text
$sel:selftext:Poll :: forall (t :: * -> *). Poll t -> Maybe Text
$sel:duration:Poll :: forall (t :: * -> *). Poll t -> Word
$sel:options:Poll :: forall (t :: * -> *). Poll t -> t Text
.. } SubmissionOptions { Bool
Maybe Text
Maybe FlairText
Text
SubredditName
flairText :: Maybe FlairText
flairID :: Maybe Text
collectionID :: Maybe Text
spoiler :: Bool
resubmit :: Bool
sendreplies :: Bool
nsfw :: Bool
subreddit :: SubredditName
title :: Text
$sel:flairText:SubmissionOptions :: SubmissionOptions -> Maybe FlairText
$sel:flairID:SubmissionOptions :: SubmissionOptions -> Maybe Text
$sel:collectionID:SubmissionOptions :: SubmissionOptions -> Maybe Text
$sel:spoiler:SubmissionOptions :: SubmissionOptions -> Bool
$sel:resubmit:SubmissionOptions :: SubmissionOptions -> Bool
$sel:sendreplies:SubmissionOptions :: SubmissionOptions -> Bool
$sel:nsfw:SubmissionOptions :: SubmissionOptions -> Bool
$sel:subreddit:SubmissionOptions :: SubmissionOptions -> SubredditName
$sel:title:SubmissionOptions :: SubmissionOptions -> Text
.. }) =
        [Pair] -> Value
object [ Text
"sr" Text -> SubredditName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= SubredditName
subreddit
               , Text
"title" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
title
               , Text
"resubmit" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
resubmit
               , Text
"sendreplies" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
sendreplies
               , Text
"nsfw" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
nsfw
               , Text
"spoiler" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
spoiler
               , Text
"options" Text -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= t Text -> [Text]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList t Text
options
               , Text
"duration" Text -> Word -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Word
duration
               , Text
"text" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty Maybe Text
selftext
               ]
mkPoll :: (Foldable t, MonadThrow m) => t Text -> Word -> m (Poll t)
mkPoll :: t Text -> Word -> m (Poll t)
mkPoll t Text
options Word
duration
    | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Word, Word) -> Word -> Bool
forall a. Ix a => (a, a) -> a -> Bool
inRange (Word
1, Word
7) Word
duration =
        ClientException -> m (Poll t)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ClientException -> m (Poll t)) -> ClientException -> m (Poll t)
forall a b. (a -> b) -> a -> b
$ Text -> ClientException
OtherError Text
"mkPoll: duration must be between 1 and 7"
    | Bool -> Bool
not (Bool -> Bool) -> (Int -> Bool) -> Int -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Int) -> Int -> Bool
forall a. Ix a => (a, a) -> a -> Bool
inRange (Int
2, Int
6) (Int -> Bool) -> Int -> Bool
forall a b. (a -> b) -> a -> b
$ t Text -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t Text
options = ClientException -> m (Poll t)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM
        (ClientException -> m (Poll t)) -> ClientException -> m (Poll t)
forall a b. (a -> b) -> a -> b
$ Text -> ClientException
OtherError Text
"mkPoll: number of options must be between 2 and 6"
    | Bool
otherwise = Poll t -> m (Poll t)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Poll t -> m (Poll t)) -> Poll t -> m (Poll t)
forall a b. (a -> b) -> a -> b
$ Poll :: forall (t :: * -> *). t Text -> Word -> Maybe Text -> Poll t
Poll { $sel:selftext:Poll :: Maybe Text
selftext = Maybe Text
forall a. Maybe a
Nothing, t Text
Word
duration :: Word
options :: t Text
$sel:duration:Poll :: Word
$sel:options:Poll :: t Text
.. }
data GalleryImage = GalleryImage
    { GalleryImage -> String
imagePath   :: FilePath
      
    , GalleryImage -> Maybe Text
caption     :: Maybe Body
      
    , GalleryImage -> Maybe Text
outboundURL :: Maybe URL
    }
    deriving stock ( Int -> GalleryImage -> ShowS
[GalleryImage] -> ShowS
GalleryImage -> String
(Int -> GalleryImage -> ShowS)
-> (GalleryImage -> String)
-> ([GalleryImage] -> ShowS)
-> Show GalleryImage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GalleryImage] -> ShowS
$cshowList :: [GalleryImage] -> ShowS
show :: GalleryImage -> String
$cshow :: GalleryImage -> String
showsPrec :: Int -> GalleryImage -> ShowS
$cshowsPrec :: Int -> GalleryImage -> ShowS
Show, GalleryImage -> GalleryImage -> Bool
(GalleryImage -> GalleryImage -> Bool)
-> (GalleryImage -> GalleryImage -> Bool) -> Eq GalleryImage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GalleryImage -> GalleryImage -> Bool
$c/= :: GalleryImage -> GalleryImage -> Bool
== :: GalleryImage -> GalleryImage -> Bool
$c== :: GalleryImage -> GalleryImage -> Bool
Eq, (forall x. GalleryImage -> Rep GalleryImage x)
-> (forall x. Rep GalleryImage x -> GalleryImage)
-> Generic GalleryImage
forall x. Rep GalleryImage x -> GalleryImage
forall x. GalleryImage -> Rep GalleryImage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GalleryImage x -> GalleryImage
$cfrom :: forall x. GalleryImage -> Rep GalleryImage x
Generic )
mkGalleryImage :: FilePath -> GalleryImage
mkGalleryImage :: String -> GalleryImage
mkGalleryImage String
imagePath =
    GalleryImage :: String -> Maybe Text -> Maybe Text -> GalleryImage
GalleryImage { $sel:caption:GalleryImage :: Maybe Text
caption = Maybe Text
forall a. Maybe a
Nothing, $sel:outboundURL:GalleryImage :: Maybe Text
outboundURL = Maybe Text
forall a. Maybe a
Nothing, String
imagePath :: String
$sel:imagePath:GalleryImage :: String
.. }
data GalleryUploadImage = GalleryUploadImage
    { GalleryUploadImage -> Text
caption     :: Body
    , GalleryUploadImage -> Text
outboundURL :: URL
      
    , GalleryUploadImage -> UploadURL
mediaID     :: UploadURL
    }
    deriving stock ( (forall x. GalleryUploadImage -> Rep GalleryUploadImage x)
-> (forall x. Rep GalleryUploadImage x -> GalleryUploadImage)
-> Generic GalleryUploadImage
forall x. Rep GalleryUploadImage x -> GalleryUploadImage
forall x. GalleryUploadImage -> Rep GalleryUploadImage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GalleryUploadImage x -> GalleryUploadImage
$cfrom :: forall x. GalleryUploadImage -> Rep GalleryUploadImage x
Generic )
instance ToJSON GalleryUploadImage where
    toJSON :: GalleryUploadImage -> Value
toJSON = Options -> GalleryUploadImage -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions { ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier }
      where
        fieldLabelModifier :: ShowS
fieldLabelModifier = \case
            String
"mediaID"     -> String
"media_id"
            String
"outboundURL" -> String
"outbound_url"
            String
s             -> String
s
galleryImageToUpload :: GalleryImage -> UploadURL -> GalleryUploadImage
galleryImageToUpload :: GalleryImage -> UploadURL -> GalleryUploadImage
galleryImageToUpload GalleryImage { String
Maybe Text
outboundURL :: Maybe Text
caption :: Maybe Text
imagePath :: String
$sel:outboundURL:GalleryImage :: GalleryImage -> Maybe Text
$sel:caption:GalleryImage :: GalleryImage -> Maybe Text
$sel:imagePath:GalleryImage :: GalleryImage -> String
.. } UploadURL
mediaID = GalleryUploadImage :: Text -> Text -> UploadURL -> GalleryUploadImage
GalleryUploadImage
    { $sel:caption:GalleryUploadImage :: Text
caption     = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty Maybe Text
caption
    , $sel:outboundURL:GalleryUploadImage :: Text
outboundURL = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty Maybe Text
outboundURL
    , UploadURL
mediaID :: UploadURL
$sel:mediaID:GalleryUploadImage :: UploadURL
..
    }
data GallerySubmission t =
    GallerySubmission (t GalleryUploadImage) SubmissionOptions
    deriving stock ( (forall x. GallerySubmission t -> Rep (GallerySubmission t) x)
-> (forall x. Rep (GallerySubmission t) x -> GallerySubmission t)
-> Generic (GallerySubmission t)
forall x. Rep (GallerySubmission t) x -> GallerySubmission t
forall x. GallerySubmission t -> Rep (GallerySubmission t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (t :: * -> *) x.
Rep (GallerySubmission t) x -> GallerySubmission t
forall (t :: * -> *) x.
GallerySubmission t -> Rep (GallerySubmission t) x
$cto :: forall (t :: * -> *) x.
Rep (GallerySubmission t) x -> GallerySubmission t
$cfrom :: forall (t :: * -> *) x.
GallerySubmission t -> Rep (GallerySubmission t) x
Generic )
instance Foldable t => ToJSON (GallerySubmission t) where
    toJSON :: GallerySubmission t -> Value
toJSON (GallerySubmission t GalleryUploadImage
items SubmissionOptions { Bool
Maybe Text
Maybe FlairText
Text
SubredditName
flairText :: Maybe FlairText
flairID :: Maybe Text
collectionID :: Maybe Text
spoiler :: Bool
resubmit :: Bool
sendreplies :: Bool
nsfw :: Bool
subreddit :: SubredditName
title :: Text
$sel:flairText:SubmissionOptions :: SubmissionOptions -> Maybe FlairText
$sel:flairID:SubmissionOptions :: SubmissionOptions -> Maybe Text
$sel:collectionID:SubmissionOptions :: SubmissionOptions -> Maybe Text
$sel:spoiler:SubmissionOptions :: SubmissionOptions -> Bool
$sel:resubmit:SubmissionOptions :: SubmissionOptions -> Bool
$sel:sendreplies:SubmissionOptions :: SubmissionOptions -> Bool
$sel:nsfw:SubmissionOptions :: SubmissionOptions -> Bool
$sel:subreddit:SubmissionOptions :: SubmissionOptions -> SubredditName
$sel:title:SubmissionOptions :: SubmissionOptions -> Text
.. }) =
        [Pair] -> Value
object [ Text
"sr" Text -> SubredditName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= SubredditName
subreddit
               , Text
"title" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
title
               , Text
"sendreplies" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
sendreplies
               , Text
"nsfw" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
nsfw
               , Text
"spoiler" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
spoiler
               , Text
"items" Text -> [GalleryUploadImage] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= t GalleryUploadImage -> [GalleryUploadImage]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList t GalleryUploadImage
items
               , Text
"show_error_list" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Bool
True
               , Text
"api_type" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"json" :: Text)
               ]
data InlineMedia = InlineMedia
    { InlineMedia -> InlineMediaType
mediaType :: InlineMediaType
      
      
    , InlineMedia -> String
mediaPath :: FilePath
      
      
      
      
      
      
    , InlineMedia -> Text
key       :: Text
      
    , InlineMedia -> Maybe Text
caption   :: Maybe Body
    }
    deriving stock ( Int -> InlineMedia -> ShowS
[InlineMedia] -> ShowS
InlineMedia -> String
(Int -> InlineMedia -> ShowS)
-> (InlineMedia -> String)
-> ([InlineMedia] -> ShowS)
-> Show InlineMedia
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineMedia] -> ShowS
$cshowList :: [InlineMedia] -> ShowS
show :: InlineMedia -> String
$cshow :: InlineMedia -> String
showsPrec :: Int -> InlineMedia -> ShowS
$cshowsPrec :: Int -> InlineMedia -> ShowS
Show, InlineMedia -> InlineMedia -> Bool
(InlineMedia -> InlineMedia -> Bool)
-> (InlineMedia -> InlineMedia -> Bool) -> Eq InlineMedia
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineMedia -> InlineMedia -> Bool
$c/= :: InlineMedia -> InlineMedia -> Bool
== :: InlineMedia -> InlineMedia -> Bool
$c== :: InlineMedia -> InlineMedia -> Bool
Eq, (forall x. InlineMedia -> Rep InlineMedia x)
-> (forall x. Rep InlineMedia x -> InlineMedia)
-> Generic InlineMedia
forall x. Rep InlineMedia x -> InlineMedia
forall x. InlineMedia -> Rep InlineMedia x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineMedia x -> InlineMedia
$cfrom :: forall x. InlineMedia -> Rep InlineMedia x
Generic )
data InlineMediaType
    = InlineImage
    | InlineGIF
    | InlineVideo
    deriving stock ( Int -> InlineMediaType -> ShowS
[InlineMediaType] -> ShowS
InlineMediaType -> String
(Int -> InlineMediaType -> ShowS)
-> (InlineMediaType -> String)
-> ([InlineMediaType] -> ShowS)
-> Show InlineMediaType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineMediaType] -> ShowS
$cshowList :: [InlineMediaType] -> ShowS
show :: InlineMediaType -> String
$cshow :: InlineMediaType -> String
showsPrec :: Int -> InlineMediaType -> ShowS
$cshowsPrec :: Int -> InlineMediaType -> ShowS
Show, InlineMediaType -> InlineMediaType -> Bool
(InlineMediaType -> InlineMediaType -> Bool)
-> (InlineMediaType -> InlineMediaType -> Bool)
-> Eq InlineMediaType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineMediaType -> InlineMediaType -> Bool
$c/= :: InlineMediaType -> InlineMediaType -> Bool
== :: InlineMediaType -> InlineMediaType -> Bool
$c== :: InlineMediaType -> InlineMediaType -> Bool
Eq, (forall x. InlineMediaType -> Rep InlineMediaType x)
-> (forall x. Rep InlineMediaType x -> InlineMediaType)
-> Generic InlineMediaType
forall x. Rep InlineMediaType x -> InlineMediaType
forall x. InlineMediaType -> Rep InlineMediaType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineMediaType x -> InlineMediaType
$cfrom :: forall x. InlineMediaType -> Rep InlineMediaType x
Generic )
instance ToHttpApiData InlineMediaType where
    toQueryParam :: InlineMediaType -> Text
toQueryParam = \case
        InlineMediaType
InlineImage -> Text
"img"
        InlineMediaType
InlineGIF   -> Text
"gif"
        InlineMediaType
InlineVideo -> Text
"video"
data InlineMediaUpload = InlineMediaUpload
    { InlineMediaUpload -> InlineMediaType
mediaType :: InlineMediaType
    , InlineMediaUpload -> UploadURL
mediaID   :: UploadURL 
    , InlineMediaUpload -> Text
caption   :: Body
    , InlineMediaUpload -> Text
key       :: Text
    }
    deriving stock ( Int -> InlineMediaUpload -> ShowS
[InlineMediaUpload] -> ShowS
InlineMediaUpload -> String
(Int -> InlineMediaUpload -> ShowS)
-> (InlineMediaUpload -> String)
-> ([InlineMediaUpload] -> ShowS)
-> Show InlineMediaUpload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineMediaUpload] -> ShowS
$cshowList :: [InlineMediaUpload] -> ShowS
show :: InlineMediaUpload -> String
$cshow :: InlineMediaUpload -> String
showsPrec :: Int -> InlineMediaUpload -> ShowS
$cshowsPrec :: Int -> InlineMediaUpload -> ShowS
Show, InlineMediaUpload -> InlineMediaUpload -> Bool
(InlineMediaUpload -> InlineMediaUpload -> Bool)
-> (InlineMediaUpload -> InlineMediaUpload -> Bool)
-> Eq InlineMediaUpload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineMediaUpload -> InlineMediaUpload -> Bool
$c/= :: InlineMediaUpload -> InlineMediaUpload -> Bool
== :: InlineMediaUpload -> InlineMediaUpload -> Bool
$c== :: InlineMediaUpload -> InlineMediaUpload -> Bool
Eq, (forall x. InlineMediaUpload -> Rep InlineMediaUpload x)
-> (forall x. Rep InlineMediaUpload x -> InlineMediaUpload)
-> Generic InlineMediaUpload
forall x. Rep InlineMediaUpload x -> InlineMediaUpload
forall x. InlineMediaUpload -> Rep InlineMediaUpload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineMediaUpload x -> InlineMediaUpload
$cfrom :: forall x. InlineMediaUpload -> Rep InlineMediaUpload x
Generic )
inlineMediaToUpload :: InlineMedia -> UploadURL -> InlineMediaUpload
inlineMediaToUpload :: InlineMedia -> UploadURL -> InlineMediaUpload
inlineMediaToUpload InlineMedia { String
Maybe Text
Text
InlineMediaType
caption :: Maybe Text
key :: Text
mediaPath :: String
mediaType :: InlineMediaType
$sel:caption:InlineMedia :: InlineMedia -> Maybe Text
$sel:key:InlineMedia :: InlineMedia -> Text
$sel:mediaPath:InlineMedia :: InlineMedia -> String
$sel:mediaType:InlineMedia :: InlineMedia -> InlineMediaType
.. } UploadURL
mediaID =
    InlineMediaUpload :: InlineMediaType -> UploadURL -> Text -> Text -> InlineMediaUpload
InlineMediaUpload { $sel:caption:InlineMediaUpload :: Text
caption = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty Maybe Text
caption, Text
UploadURL
InlineMediaType
mediaID :: UploadURL
key :: Text
mediaType :: InlineMediaType
$sel:key:InlineMediaUpload :: Text
$sel:mediaID:InlineMediaUpload :: UploadURL
$sel:mediaType:InlineMediaUpload :: InlineMediaType
.. }
writeInlineMedia :: InlineMediaUpload -> Body
writeInlineMedia :: InlineMediaUpload -> Text
writeInlineMedia InlineMediaUpload { Text
UploadURL
InlineMediaType
key :: Text
caption :: Text
mediaID :: UploadURL
mediaType :: InlineMediaType
$sel:key:InlineMediaUpload :: InlineMediaUpload -> Text
$sel:caption:InlineMediaUpload :: InlineMediaUpload -> Text
$sel:mediaID:InlineMediaUpload :: InlineMediaUpload -> UploadURL
$sel:mediaType:InlineMediaUpload :: InlineMediaUpload -> InlineMediaType
.. } =
    [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"\n\n"
            , Text
"!["
            , InlineMediaType -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam InlineMediaType
mediaType
            , Text
"]"
            , Text
"("
            , UploadURL -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam UploadURL
mediaID
            , Text
" "
            , Text
"\""
            , Text
caption
            , Text
"\""
            , Text
")"
            , Text
"\n\n"
            ]
newtype Fancypants = Fancypants Object
    deriving stock ( Int -> Fancypants -> ShowS
[Fancypants] -> ShowS
Fancypants -> String
(Int -> Fancypants -> ShowS)
-> (Fancypants -> String)
-> ([Fancypants] -> ShowS)
-> Show Fancypants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Fancypants] -> ShowS
$cshowList :: [Fancypants] -> ShowS
show :: Fancypants -> String
$cshow :: Fancypants -> String
showsPrec :: Int -> Fancypants -> ShowS
$cshowsPrec :: Int -> Fancypants -> ShowS
Show, (forall x. Fancypants -> Rep Fancypants x)
-> (forall x. Rep Fancypants x -> Fancypants) -> Generic Fancypants
forall x. Rep Fancypants x -> Fancypants
forall x. Fancypants -> Rep Fancypants x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Fancypants x -> Fancypants
$cfrom :: forall x. Fancypants -> Rep Fancypants x
Generic )
    deriving newtype ( Fancypants -> Fancypants -> Bool
(Fancypants -> Fancypants -> Bool)
-> (Fancypants -> Fancypants -> Bool) -> Eq Fancypants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Fancypants -> Fancypants -> Bool
$c/= :: Fancypants -> Fancypants -> Bool
== :: Fancypants -> Fancypants -> Bool
$c== :: Fancypants -> Fancypants -> Bool
Eq, [Fancypants] -> Encoding
[Fancypants] -> Value
Fancypants -> Encoding
Fancypants -> Value
(Fancypants -> Value)
-> (Fancypants -> Encoding)
-> ([Fancypants] -> Value)
-> ([Fancypants] -> Encoding)
-> ToJSON Fancypants
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Fancypants] -> Encoding
$ctoEncodingList :: [Fancypants] -> Encoding
toJSONList :: [Fancypants] -> Value
$ctoJSONList :: [Fancypants] -> Value
toEncoding :: Fancypants -> Encoding
$ctoEncoding :: Fancypants -> Encoding
toJSON :: Fancypants -> Value
$ctoJSON :: Fancypants -> Value
ToJSON )
instance FromJSON Fancypants where
    parseJSON :: Value -> Parser Fancypants
parseJSON = String
-> (Object -> Parser Fancypants) -> Value -> Parser Fancypants
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Fancypants" ((Object -> Parser Fancypants) -> Value -> Parser Fancypants)
-> (Object -> Parser Fancypants) -> Value -> Parser Fancypants
forall a b. (a -> b) -> a -> b
$ (Object -> Fancypants) -> Parser Object -> Parser Fancypants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Object -> Fancypants
Fancypants (Parser Object -> Parser Fancypants)
-> (Object -> Parser Object) -> Object -> Parser Fancypants
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"output")
newtype PostedSubmission = PostedSubmission URL
    deriving stock ( Int -> PostedSubmission -> ShowS
[PostedSubmission] -> ShowS
PostedSubmission -> String
(Int -> PostedSubmission -> ShowS)
-> (PostedSubmission -> String)
-> ([PostedSubmission] -> ShowS)
-> Show PostedSubmission
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostedSubmission] -> ShowS
$cshowList :: [PostedSubmission] -> ShowS
show :: PostedSubmission -> String
$cshow :: PostedSubmission -> String
showsPrec :: Int -> PostedSubmission -> ShowS
$cshowsPrec :: Int -> PostedSubmission -> ShowS
Show, (forall x. PostedSubmission -> Rep PostedSubmission x)
-> (forall x. Rep PostedSubmission x -> PostedSubmission)
-> Generic PostedSubmission
forall x. Rep PostedSubmission x -> PostedSubmission
forall x. PostedSubmission -> Rep PostedSubmission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PostedSubmission x -> PostedSubmission
$cfrom :: forall x. PostedSubmission -> Rep PostedSubmission x
Generic )
instance FromJSON PostedSubmission where
    parseJSON :: Value -> Parser PostedSubmission
parseJSON = String
-> (Object -> Parser PostedSubmission)
-> Value
-> Parser PostedSubmission
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PostedSubmission"
        ((Object -> Parser PostedSubmission)
 -> Value -> Parser PostedSubmission)
-> (Object -> Parser PostedSubmission)
-> Value
-> Parser PostedSubmission
forall a b. (a -> b) -> a -> b
$ (Text -> PostedSubmission)
-> Parser Text -> Parser PostedSubmission
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> PostedSubmission
PostedSubmission (Parser Text -> Parser PostedSubmission)
-> (Object -> Parser Text) -> Object -> Parser PostedSubmission
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"url") (Object -> Parser Text)
-> (Object -> Parser Object) -> Object -> Parser Text
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") (Object -> Parser Object)
-> (Object -> Parser Object) -> Object -> Parser Object
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
"json"))
data Search = Search
    { 
      Search -> Text
q         :: Text
      
    , Search -> Maybe SubredditName
subreddit :: Maybe SubredditName
      
    , Search -> Maybe SearchSyntax
syntax    :: Maybe SearchSyntax
    }
    deriving stock ( Int -> Search -> ShowS
[Search] -> ShowS
Search -> String
(Int -> Search -> ShowS)
-> (Search -> String) -> ([Search] -> ShowS) -> Show Search
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Search] -> ShowS
$cshowList :: [Search] -> ShowS
show :: Search -> String
$cshow :: Search -> String
showsPrec :: Int -> Search -> ShowS
$cshowsPrec :: Int -> Search -> ShowS
Show, Search -> Search -> Bool
(Search -> Search -> Bool)
-> (Search -> Search -> Bool) -> Eq Search
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Search -> Search -> Bool
$c/= :: Search -> Search -> Bool
== :: Search -> Search -> Bool
$c== :: Search -> Search -> Bool
Eq, (forall x. Search -> Rep Search x)
-> (forall x. Rep Search x -> Search) -> Generic Search
forall x. Rep Search x -> Search
forall x. Search -> Rep Search x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Search x -> Search
$cfrom :: forall x. Search -> Rep Search x
Generic )
instance ToForm Search where
    toForm :: Search -> Form
toForm Search { Maybe SubredditName
Maybe SearchSyntax
Text
syntax :: Maybe SearchSyntax
subreddit :: Maybe SubredditName
q :: Text
$sel:syntax:Search :: Search -> Maybe SearchSyntax
$sel:subreddit:Search :: Search -> Maybe SubredditName
$sel:q:Search :: Search -> Text
.. } =
        [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList [ (Text
"q", Text
q)
                 , (Text
"syntax", SearchSyntax -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam (SearchSyntax -> Text) -> SearchSyntax -> Text
forall a b. (a -> b) -> a -> b
$ SearchSyntax -> Maybe SearchSyntax -> SearchSyntax
forall a. a -> Maybe a -> a
fromMaybe SearchSyntax
Lucene Maybe SearchSyntax
syntax)
                 , (Text
"restrict_sr", Bool -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam (Bool -> Text) -> Bool -> Text
forall a b. (a -> b) -> a -> b
$ Maybe SubredditName -> Bool
forall a. Maybe a -> Bool
isJust Maybe SubredditName
subreddit)
                 ]
instance Paginable Search where
    type PaginateOptions Search = SearchOpts
    type PaginateThing Search = Text
    defaultOpts :: PaginateOptions Search
defaultOpts = SearchOpts :: SearchSort -> Time -> Maybe SearchCategory -> SearchOpts
SearchOpts
        { $sel:searchSort:SearchOpts :: SearchSort
searchSort = SearchSort
ByRelevance, $sel:searchTime:SearchOpts :: Time
searchTime = Time
AllTime, $sel:category:SearchOpts :: Maybe SearchCategory
category = Maybe SearchCategory
forall a. Maybe a
Nothing }
mkSearch :: Text -> Search
mkSearch :: Text -> Search
mkSearch Text
q = Search :: Text -> Maybe SubredditName -> Maybe SearchSyntax -> Search
Search { $sel:subreddit:Search :: Maybe SubredditName
subreddit = Maybe SubredditName
forall a. Maybe a
Nothing, $sel:syntax:Search :: Maybe SearchSyntax
syntax = Maybe SearchSyntax
forall a. Maybe a
Nothing, Text
q :: Text
$sel:q:Search :: Text
.. }
data SearchOpts = SearchOpts
    { SearchOpts -> SearchSort
searchSort :: SearchSort
    , SearchOpts -> Time
searchTime :: Time
    , SearchOpts -> Maybe SearchCategory
category   :: Maybe SearchCategory
    }
    deriving stock ( Int -> SearchOpts -> ShowS
[SearchOpts] -> ShowS
SearchOpts -> String
(Int -> SearchOpts -> ShowS)
-> (SearchOpts -> String)
-> ([SearchOpts] -> ShowS)
-> Show SearchOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchOpts] -> ShowS
$cshowList :: [SearchOpts] -> ShowS
show :: SearchOpts -> String
$cshow :: SearchOpts -> String
showsPrec :: Int -> SearchOpts -> ShowS
$cshowsPrec :: Int -> SearchOpts -> ShowS
Show, SearchOpts -> SearchOpts -> Bool
(SearchOpts -> SearchOpts -> Bool)
-> (SearchOpts -> SearchOpts -> Bool) -> Eq SearchOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchOpts -> SearchOpts -> Bool
$c/= :: SearchOpts -> SearchOpts -> Bool
== :: SearchOpts -> SearchOpts -> Bool
$c== :: SearchOpts -> SearchOpts -> Bool
Eq, (forall x. SearchOpts -> Rep SearchOpts x)
-> (forall x. Rep SearchOpts x -> SearchOpts) -> Generic SearchOpts
forall x. Rep SearchOpts x -> SearchOpts
forall x. SearchOpts -> Rep SearchOpts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchOpts x -> SearchOpts
$cfrom :: forall x. SearchOpts -> Rep SearchOpts x
Generic )
instance ToForm SearchOpts where
    toForm :: SearchOpts -> Form
toForm SearchOpts { Maybe SearchCategory
Time
SearchSort
category :: Maybe SearchCategory
searchTime :: Time
searchSort :: SearchSort
$sel:category:SearchOpts :: SearchOpts -> Maybe SearchCategory
$sel:searchTime:SearchOpts :: SearchOpts -> Time
$sel:searchSort:SearchOpts :: SearchOpts -> SearchSort
.. } = [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList
        ([Item Form] -> Form) -> [Item Form] -> Form
forall a b. (a -> b) -> a -> b
$ [ (Text
"sort", SearchSort -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam SearchSort
searchSort)
          , (Text
"t", Time -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Time
searchTime)
          ]
        [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> ((Text, Text) -> [(Text, Text)])
-> Maybe (Text, Text) -> [(Text, Text)]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Text, Text) -> [(Text, Text)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Text
"category", ) (Text -> (Text, Text))
-> (SearchCategory -> Text) -> SearchCategory -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SearchCategory -> Text
coerce (SearchCategory -> (Text, Text))
-> Maybe SearchCategory -> Maybe (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe SearchCategory
category)
data SearchSort
    = ByRelevance
    | ByNew
    | ByHot
    | ByTop
    | 
    deriving stock ( Int -> SearchSort -> ShowS
[SearchSort] -> ShowS
SearchSort -> String
(Int -> SearchSort -> ShowS)
-> (SearchSort -> String)
-> ([SearchSort] -> ShowS)
-> Show SearchSort
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchSort] -> ShowS
$cshowList :: [SearchSort] -> ShowS
show :: SearchSort -> String
$cshow :: SearchSort -> String
showsPrec :: Int -> SearchSort -> ShowS
$cshowsPrec :: Int -> SearchSort -> ShowS
Show, SearchSort -> SearchSort -> Bool
(SearchSort -> SearchSort -> Bool)
-> (SearchSort -> SearchSort -> Bool) -> Eq SearchSort
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchSort -> SearchSort -> Bool
$c/= :: SearchSort -> SearchSort -> Bool
== :: SearchSort -> SearchSort -> Bool
$c== :: SearchSort -> SearchSort -> Bool
Eq, (forall x. SearchSort -> Rep SearchSort x)
-> (forall x. Rep SearchSort x -> SearchSort) -> Generic SearchSort
forall x. Rep SearchSort x -> SearchSort
forall x. SearchSort -> Rep SearchSort x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchSort x -> SearchSort
$cfrom :: forall x. SearchSort -> Rep SearchSort x
Generic )
instance ToHttpApiData SearchSort where
    toQueryParam :: SearchSort -> Text
toQueryParam = Int -> Text -> Text
T.drop Int
2 (Text -> Text) -> (SearchSort -> Text) -> SearchSort -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SearchSort -> Text
forall a. Show a => a -> Text
showTextData
newtype SearchCategory = SearchCategory Text
    deriving stock ( Int -> SearchCategory -> ShowS
[SearchCategory] -> ShowS
SearchCategory -> String
(Int -> SearchCategory -> ShowS)
-> (SearchCategory -> String)
-> ([SearchCategory] -> ShowS)
-> Show SearchCategory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchCategory] -> ShowS
$cshowList :: [SearchCategory] -> ShowS
show :: SearchCategory -> String
$cshow :: SearchCategory -> String
showsPrec :: Int -> SearchCategory -> ShowS
$cshowsPrec :: Int -> SearchCategory -> ShowS
Show, (forall x. SearchCategory -> Rep SearchCategory x)
-> (forall x. Rep SearchCategory x -> SearchCategory)
-> Generic SearchCategory
forall x. Rep SearchCategory x -> SearchCategory
forall x. SearchCategory -> Rep SearchCategory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchCategory x -> SearchCategory
$cfrom :: forall x. SearchCategory -> Rep SearchCategory x
Generic )
    deriving newtype ( SearchCategory -> SearchCategory -> Bool
(SearchCategory -> SearchCategory -> Bool)
-> (SearchCategory -> SearchCategory -> Bool) -> Eq SearchCategory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchCategory -> SearchCategory -> Bool
$c/= :: SearchCategory -> SearchCategory -> Bool
== :: SearchCategory -> SearchCategory -> Bool
$c== :: SearchCategory -> SearchCategory -> Bool
Eq )
mkSearchCategory :: MonadThrow m => Text -> m SearchCategory
mkSearchCategory :: Text -> m SearchCategory
mkSearchCategory Text
txt
    | Text -> Int
T.length Text
txt Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
5 =
        ClientException -> m SearchCategory
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ClientException -> m SearchCategory)
-> ClientException -> m SearchCategory
forall a b. (a -> b) -> a -> b
$ Text -> ClientException
OtherError Text
"mkSearchCategory: length must be <= 5 characters"
    | Bool
otherwise = SearchCategory -> m SearchCategory
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SearchCategory -> m SearchCategory)
-> SearchCategory -> m SearchCategory
forall a b. (a -> b) -> a -> b
$ Text -> SearchCategory
SearchCategory Text
txt
data SearchSyntax
    = Lucene
    | Cloudsearch
    | PlainSyntax
    deriving stock ( Int -> SearchSyntax -> ShowS
[SearchSyntax] -> ShowS
SearchSyntax -> String
(Int -> SearchSyntax -> ShowS)
-> (SearchSyntax -> String)
-> ([SearchSyntax] -> ShowS)
-> Show SearchSyntax
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchSyntax] -> ShowS
$cshowList :: [SearchSyntax] -> ShowS
show :: SearchSyntax -> String
$cshow :: SearchSyntax -> String
showsPrec :: Int -> SearchSyntax -> ShowS
$cshowsPrec :: Int -> SearchSyntax -> ShowS
Show, SearchSyntax -> SearchSyntax -> Bool
(SearchSyntax -> SearchSyntax -> Bool)
-> (SearchSyntax -> SearchSyntax -> Bool) -> Eq SearchSyntax
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchSyntax -> SearchSyntax -> Bool
$c/= :: SearchSyntax -> SearchSyntax -> Bool
== :: SearchSyntax -> SearchSyntax -> Bool
$c== :: SearchSyntax -> SearchSyntax -> Bool
Eq, (forall x. SearchSyntax -> Rep SearchSyntax x)
-> (forall x. Rep SearchSyntax x -> SearchSyntax)
-> Generic SearchSyntax
forall x. Rep SearchSyntax x -> SearchSyntax
forall x. SearchSyntax -> Rep SearchSyntax x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchSyntax x -> SearchSyntax
$cfrom :: forall x. SearchSyntax -> Rep SearchSyntax x
Generic )
instance ToHttpApiData SearchSyntax where
    toQueryParam :: SearchSyntax -> Text
toQueryParam = \case
        SearchSyntax
PlainSyntax -> Text
"plain"
        SearchSyntax
s           -> SearchSyntax -> Text
forall a. Show a => a -> Text
showTextData SearchSyntax
s
newtype ResultID = ResultID SubmissionID
    deriving stock ( Int -> ResultID -> ShowS
[ResultID] -> ShowS
ResultID -> String
(Int -> ResultID -> ShowS)
-> (ResultID -> String) -> ([ResultID] -> ShowS) -> Show ResultID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResultID] -> ShowS
$cshowList :: [ResultID] -> ShowS
show :: ResultID -> String
$cshow :: ResultID -> String
showsPrec :: Int -> ResultID -> ShowS
$cshowsPrec :: Int -> ResultID -> ShowS
Show, (forall x. ResultID -> Rep ResultID x)
-> (forall x. Rep ResultID x -> ResultID) -> Generic ResultID
forall x. Rep ResultID x -> ResultID
forall x. ResultID -> Rep ResultID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResultID x -> ResultID
$cfrom :: forall x. ResultID -> Rep ResultID x
Generic )
    deriving newtype ( Value -> Parser [ResultID]
Value -> Parser ResultID
(Value -> Parser ResultID)
-> (Value -> Parser [ResultID]) -> FromJSON ResultID
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ResultID]
$cparseJSONList :: Value -> Parser [ResultID]
parseJSON :: Value -> Parser ResultID
$cparseJSON :: Value -> Parser ResultID
FromJSON, ResultID -> Text
(ResultID -> Text) -> Thing ResultID
forall a. (a -> Text) -> Thing a
fullname :: ResultID -> Text
$cfullname :: ResultID -> Text
Thing )