{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
module Network.Reddit.Subreddit
(
getSubreddit
, getSubredditRules
, getPostRequirements
, getHotSubmissions
, getNewSubmissions
, getRandomRisingSubmissions
, getControversialSubmissions
, getRisingSubmissions
, getTopSubmissions
, getRandomSubmission
, getStickiedSubmission
, subscribe
, unsubscribe
, quarantineOptIn
, quarantineOptOut
, getDefaultSubreddits
, getNewSubreddits
, getPopularSubreddits
, getPremiumSubreddits
, getGoldSubreddits
, searchSubreddits
, searchSubredditsByName
, getRecommendedSubreddits
, followCollection
, unfollowCollection
, getCollections
, getCollectionsWithName
, getCollection
, getCollectionByPermalink
, getUserFlairTemplates
, getSubmissionFlairTemplates
, getNewSubmissionFlairChoices
, getUserFlairChoices
, getSubmissionFlairChoices
, getWikiPage
, getWikiPages
, getWikiPageRevision
, getWikiPageRevisions
, editWikiPage
, createWikiPage
, getSubredditWidgets
, getAllSubredditWidgets
, getSubredditEmojis
, module M
) where
import Control.Monad.Catch ( MonadCatch(catch)
, MonadThrow(throwM)
)
import Data.Aeson ( FromJSON )
import Data.ByteString ( ByteString )
import Data.Generics.Wrapped ( wrappedTo )
import Data.Maybe ( fromMaybe )
import Data.Sequence ( Seq((:<|)) )
import Data.Text ( Text )
import qualified Data.Text.Encoding as T
import Lens.Micro ( (&), (<&>) )
import qualified Network.HTTP.Client.Conduit as H
import Network.Reddit.Internal
import Network.Reddit.Types
import Network.Reddit.Types.Emoji
import Network.Reddit.Types.Emoji as M
( Emoji(Emoji)
, EmojiName
, mkEmoji
, mkEmojiName
)
import Network.Reddit.Types.Flair
import Network.Reddit.Types.Flair as M
( AssignedFlair(AssignedFlair)
, CSSClass
, CurrentUserFlair
, FlairChoice(FlairChoice)
, FlairChoiceList
, FlairContent(..)
, FlairID
, FlairList(FlairList)
, FlairResult(FlairResult)
, FlairSelection(FlairSelection)
, FlairTemplate(FlairTemplate)
, FlairText
, FlairType(..)
, ForegroundColor(..)
, PostedFlairTemplate
, UserFlair(UserFlair)
, defaultFlairTemplate
, flairlistToListing
, mkFlairText
)
import Network.Reddit.Types.Item
import Network.Reddit.Types.Submission
import Network.Reddit.Types.Subreddit
import Network.Reddit.Types.Subreddit as M
( BodyRestriction(..)
, NewSubredditRule(NewSubredditRule)
, PostRequirements(PostRequirements)
, PostedSubredditRule
, RuleType(..)
, Subreddit(Subreddit)
, SubredditID(SubredditID)
, SubredditName
, SubredditRule(SubredditRule)
, mkSubredditName
)
import Network.Reddit.Types.Widget
import Network.Reddit.Types.Widget as M
( Button(..)
, ButtonHover(..)
, ButtonImage(ButtonImage)
, ButtonText(ButtonText)
, ButtonWidget(ButtonWidget)
, CalendarConfig(CalendarConfig)
, CalendarWidget(CalendarWidget)
, CommunityInfo(CommunityInfo)
, CommunityListWidget(CommunityListWidget)
, CustomWidget(CustomWidget)
, IDCardWidget(IDCardWidget)
, Image(Image)
, ImageData(ImageData)
, ImageHover(ImageHover)
, ImageWidget(ImageWidget)
, MenuChild(..)
, MenuLink(MenuLink)
, MenuWidget(MenuWidget)
, ModInfo(ModInfo)
, ModeratorsWidget(ModeratorsWidget)
, PostFlairInfo(PostFlairInfo)
, PostFlairWidget(PostFlairWidget)
, PostFlairWidgetDisplay(..)
, RulesDisplay(..)
, RulesWidget(RulesWidget)
, ShortName
, Submenu(Submenu)
, SubredditWidgets(SubredditWidgets)
, TextAreaWidget(TextAreaWidget)
, TextHover(TextHover)
, Widget(..)
, WidgetID(WidgetID)
, WidgetSection(..)
, WidgetStyles(WidgetStyles)
, defaultCalendarConfig
, mkCommunityInfo
, mkPostFlairWidget
, mkShortName
, mkTextAreaWidget
)
import Network.Reddit.Types.Wiki as M
( WikiPage(WikiPage)
, WikiPageListing
, WikiPageName
, WikiPageSettings(WikiPageSettings)
, WikiPermLevel(..)
, WikiRevision(WikiRevision)
, WikiRevisionID
, mkWikiPageName
)
import Network.Reddit.Utils
import Web.FormUrlEncoded ( Form )
import Web.HttpApiData ( ToHttpApiData(..) )
import Web.Internal.FormUrlEncoded ( ToForm(toForm) )
getSubreddit :: MonadReddit m => SubredditName -> m Subreddit
getSubreddit :: SubredditName -> m Subreddit
getSubreddit SubredditName
sname = m Subreddit -> m Subreddit
forall (m :: * -> *) a. MonadReddit m => m a -> m a
catchEmptyListing
(m Subreddit -> m Subreddit) -> m Subreddit -> m Subreddit
forall a b. (a -> b) -> a -> b
$ APIAction Subreddit -> m Subreddit
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"r", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"about" ] }
getSubredditRules :: MonadReddit m => SubredditName -> m (Seq SubredditRule)
getSubredditRules :: SubredditName -> m (Seq SubredditRule)
getSubredditRules SubredditName
sname = APIAction RuleList -> m RuleList
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @RuleList APIAction RuleList
forall a. APIAction a
r m RuleList
-> (RuleList -> Seq SubredditRule) -> m (Seq SubredditRule)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> RuleList -> Seq SubredditRule
forall s t a b. Wrapped s t a b => s -> a
wrappedTo
where
r :: APIAction a
r = APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"r", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"about", PathSegment
"rules" ] }
getPostRequirements :: MonadReddit m => SubredditName -> m PostRequirements
getPostRequirements :: SubredditName -> m PostRequirements
getPostRequirements SubredditName
sname =
APIAction PostRequirements -> m PostRequirements
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments =
[ PathSegment
"api", PathSegment
"v1", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"post_requirements" ]
}
getHotSubmissions, getNewSubmissions, getRandomRisingSubmissions
:: MonadReddit m
=> SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
getHotSubmissions :: SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
getHotSubmissions = PathSegment
-> SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
forall (m :: * -> *) a.
(MonadReddit m, Thing a, FromJSON a) =>
PathSegment
-> SubredditName
-> Paginator a Submission
-> m (Listing a Submission)
submissions PathSegment
"hot"
getNewSubmissions :: SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
getNewSubmissions = PathSegment
-> SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
forall (m :: * -> *) a.
(MonadReddit m, Thing a, FromJSON a) =>
PathSegment
-> SubredditName
-> Paginator a Submission
-> m (Listing a Submission)
submissions PathSegment
"new"
getControversialSubmissions, getRisingSubmissions, getTopSubmissions
:: MonadReddit m
=> SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
getControversialSubmissions :: SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
getControversialSubmissions = PathSegment
-> SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
forall (m :: * -> *) a.
(MonadReddit m, Thing a, FromJSON a) =>
PathSegment
-> SubredditName
-> Paginator a Submission
-> m (Listing a Submission)
submissions PathSegment
"controversial"
getRisingSubmissions :: SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
getRisingSubmissions = PathSegment
-> SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
forall (m :: * -> *) a.
(MonadReddit m, Thing a, FromJSON a) =>
PathSegment
-> SubredditName
-> Paginator a Submission
-> m (Listing a Submission)
submissions PathSegment
"rising"
getTopSubmissions :: SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
getTopSubmissions = PathSegment
-> SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
forall (m :: * -> *) a.
(MonadReddit m, Thing a, FromJSON a) =>
PathSegment
-> SubredditName
-> Paginator a Submission
-> m (Listing a Submission)
submissions PathSegment
"top"
getRandomRisingSubmissions :: SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
getRandomRisingSubmissions = PathSegment
-> SubredditName
-> Paginator SubmissionID Submission
-> m (Listing SubmissionID Submission)
forall (m :: * -> *) a.
(MonadReddit m, Thing a, FromJSON a) =>
PathSegment
-> SubredditName
-> Paginator a Submission
-> m (Listing a Submission)
submissions PathSegment
"randomrising"
submissions :: (MonadReddit m, Thing a, FromJSON a)
=> Text
-> SubredditName
-> Paginator a Submission
-> m (Listing a Submission)
submissions :: PathSegment
-> SubredditName
-> Paginator a Submission
-> m (Listing a Submission)
submissions PathSegment
txt SubredditName
sname Paginator a Submission
paginator =
APIAction (Listing a Submission) -> m (Listing a Submission)
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"r", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
txt ]
, $sel:requestData:APIAction :: WithData
requestData = Paginator a Submission -> WithData
forall t a. (Thing t, Paginable a) => Paginator t a -> WithData
paginatorToFormData Paginator a Submission
paginator
}
getRandomSubmission :: MonadReddit m => SubredditName -> m Submission
getRandomSubmission :: SubredditName -> m Submission
getRandomSubmission SubredditName
sname =
PathSegment
-> m Submission
-> ([ByteString] -> m [Listing ItemID Item])
-> m Submission
forall (m :: * -> *) t.
MonadCatch m =>
PathSegment
-> m Submission
-> ([ByteString] -> m [Listing t Item])
-> m Submission
catchRedirected PathSegment
"getRandomSubmission" m Submission
action [ByteString] -> m [Listing ItemID Item]
forall (m :: * -> *).
(MonadUnliftIO m, MonadCatch m, MonadReader Client m) =>
[ByteString] -> m [Listing ItemID Item]
handler
where
action :: m Submission
action =
APIAction Submission -> m Submission
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"r", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"random" ]
, $sel:followRedirects:APIAction :: Bool
followRedirects = Bool
False
}
handler :: [ByteString] -> m [Listing ItemID Item]
handler [ByteString]
ps =
APIAction [Listing ItemID Item] -> m [Listing ItemID Item]
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @[Listing ItemID Item]
APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = ByteString -> PathSegment
T.decodeUtf8 (ByteString -> PathSegment) -> [ByteString] -> [PathSegment]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ByteString]
ps, $sel:needsAuth:APIAction :: Bool
needsAuth = Bool
False }
getStickiedSubmission
:: MonadReddit m
=> Maybe Word
-> SubredditName
-> m Submission
getStickiedSubmission :: Maybe Word -> SubredditName -> m Submission
getStickiedSubmission Maybe Word
num SubredditName
sname =
PathSegment
-> m Submission
-> ([ByteString] -> m [Listing ItemID Item])
-> m Submission
forall (m :: * -> *) t.
MonadCatch m =>
PathSegment
-> m Submission
-> ([ByteString] -> m [Listing t Item])
-> m Submission
catchRedirected PathSegment
"getStickiedSubmission" m Submission
action [ByteString] -> m [Listing ItemID Item]
forall (m :: * -> *).
(MonadUnliftIO m, MonadCatch m, MonadReader Client m) =>
[ByteString] -> m [Listing ItemID Item]
handler
where
action :: m Submission
action =
APIAction Submission -> m Submission
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = SubredditName -> PathSegment -> [PathSegment]
subAboutPath SubredditName
sname PathSegment
"sticky"
, $sel:followRedirects:APIAction :: Bool
followRedirects = Bool
False
, $sel:requestData:APIAction :: WithData
requestData =
[(PathSegment, PathSegment)] -> WithData
mkTextFormData [ ( PathSegment
"num"
, Word -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam (Word -> PathSegment) -> Word -> PathSegment
forall a b. (a -> b) -> a -> b
$ Word -> Maybe Word -> Word
forall a. a -> Maybe a -> a
fromMaybe Word
1 Maybe Word
num
)
]
}
handler :: [ByteString] -> m [Listing ItemID Item]
handler [ByteString]
ps =
APIAction [Listing ItemID Item] -> m [Listing ItemID Item]
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @[Listing ItemID Item]
APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = ByteString -> PathSegment
T.decodeUtf8 (ByteString -> PathSegment) -> [ByteString] -> [PathSegment]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ByteString]
ps, $sel:needsAuth:APIAction :: Bool
needsAuth = Bool
False }
catchRedirected :: MonadCatch m
=> Text
-> m Submission
-> ([ByteString] -> m [Listing t Item])
-> m Submission
catchRedirected :: PathSegment
-> m Submission
-> ([ByteString] -> m [Listing t Item])
-> m Submission
catchRedirected PathSegment
func m Submission
action [ByteString] -> m [Listing t Item]
handler = m Submission -> (APIException -> m Submission) -> m Submission
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
catch @_ @APIException m Submission
action ((APIException -> m Submission) -> m Submission)
-> (APIException -> m Submission) -> m Submission
forall a b. (a -> b) -> a -> b
$ \case
Redirected (Just Request
req) -> case Request
req Request -> (Request -> ByteString) -> ByteString
forall a b. a -> (a -> b) -> b
& Request -> ByteString
H.path ByteString -> (ByteString -> [ByteString]) -> [ByteString]
forall a b. a -> (a -> b) -> b
& ByteString -> [ByteString]
splitPath of
[ r :: ByteString
r@ByteString
"r", ByteString
sub, c :: ByteString
c@ByteString
"comments", ByteString
path, ByteString
t, j :: ByteString
j@ByteString
".json" ] ->
[ByteString] -> m [Listing t Item]
handler [ ByteString
r, ByteString
sub, ByteString
c, ByteString
path, ByteString
t, ByteString
j ] m [Listing t Item]
-> ([Listing t Item] -> m Submission) -> m Submission
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Listing { Seq Item
$sel:children:Listing :: forall t a. Listing t a -> Seq a
children :: Seq Item
children } : [Listing t Item]
_ -> Seq Item -> m Submission
handleChildren Seq Item
children
[Listing t Item]
_ -> m Submission
forall a. m a
noResults
[ByteString]
_ -> ClientException -> m Submission
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ClientException -> m Submission)
-> (PathSegment -> ClientException) -> PathSegment -> m Submission
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PathSegment -> ClientException
InvalidResponse
(PathSegment -> m Submission) -> PathSegment -> m Submission
forall a b. (a -> b) -> a -> b
$ PathSegment
func PathSegment -> PathSegment -> PathSegment
forall a. Semigroup a => a -> a -> a
<> PathSegment
": Could not parse redirect URL"
APIException
e -> APIException -> m Submission
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM APIException
e
where
noResults :: m a
noResults = ClientException -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ClientException -> m a)
-> (PathSegment -> ClientException) -> PathSegment -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PathSegment -> ClientException
InvalidResponse (PathSegment -> m a) -> PathSegment -> m a
forall a b. (a -> b) -> a -> b
$ PathSegment
func PathSegment -> PathSegment -> PathSegment
forall a. Semigroup a => a -> a -> a
<> PathSegment
": No results"
handleChildren :: Seq Item -> m Submission
handleChildren = \case
SubmissionItem Submission
s :<| Seq Item
_ -> Submission -> m Submission
forall (f :: * -> *) a. Applicative f => a -> f a
pure Submission
s
Seq Item
_ -> m Submission
forall a. m a
noResults
subscribe :: MonadReddit m => SubredditName -> m ()
subscribe :: SubredditName -> m ()
subscribe SubredditName
sname =
APIAction () -> m ()
forall (m :: * -> *). MonadReddit m => APIAction () -> m ()
runAction_ APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"subscribe" ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData =
[(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"sr_name", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam SubredditName
sname)
, (PathSegment
"action", PathSegment
"sub")
, ( PathSegment
"skip_initial_defaults"
, Bool -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam Bool
True
)
]
}
unsubscribe :: MonadReddit m => SubredditName -> m ()
unsubscribe :: SubredditName -> m ()
unsubscribe SubredditName
sname =
APIAction () -> m ()
forall (m :: * -> *). MonadReddit m => APIAction () -> m ()
runAction_ APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"subscribe" ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData =
[(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"sr_name", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam SubredditName
sname)
, (PathSegment
"action", PathSegment
"unsub")
]
}
quarantineOptIn :: MonadReddit m => SubredditName -> m ()
quarantineOptIn :: SubredditName -> m ()
quarantineOptIn = PathSegment -> SubredditName -> m ()
forall (m :: * -> *).
MonadReddit m =>
PathSegment -> SubredditName -> m ()
quarantineOpt PathSegment
"quarantine_opt_in"
quarantineOptOut :: MonadReddit m => SubredditName -> m ()
quarantineOptOut :: SubredditName -> m ()
quarantineOptOut = PathSegment -> SubredditName -> m ()
forall (m :: * -> *).
MonadReddit m =>
PathSegment -> SubredditName -> m ()
quarantineOpt PathSegment
"quarantine_opt_out"
quarantineOpt :: MonadReddit m => PathSegment -> SubredditName -> m ()
quarantineOpt :: PathSegment -> SubredditName -> m ()
quarantineOpt PathSegment
path SubredditName
sname =
APIAction () -> m ()
forall (m :: * -> *). MonadReddit m => APIAction () -> m ()
runAction_ APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
path ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData =
[(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"sr_name", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam SubredditName
sname) ]
}
getDefaultSubreddits, getNewSubreddits, getPopularSubreddits
:: MonadReddit m
=> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
getDefaultSubreddits :: Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
getDefaultSubreddits = PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
forall (m :: * -> *).
MonadReddit m =>
PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
subredditListing PathSegment
"default"
getNewSubreddits :: Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
getNewSubreddits = PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
forall (m :: * -> *).
MonadReddit m =>
PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
subredditListing PathSegment
"new"
getPopularSubreddits :: Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
getPopularSubreddits = PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
forall (m :: * -> *).
MonadReddit m =>
PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
subredditListing PathSegment
"popular"
getPremiumSubreddits, getGoldSubreddits
:: MonadReddit m
=> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
getPremiumSubreddits :: Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
getPremiumSubreddits = PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
forall (m :: * -> *).
MonadReddit m =>
PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
subredditListing PathSegment
"premium"
getGoldSubreddits :: Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
getGoldSubreddits = Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
forall (m :: * -> *).
MonadReddit m =>
Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
getPremiumSubreddits
searchSubreddits :: MonadReddit m
=> Text
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
searchSubreddits :: PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
searchSubreddits PathSegment
query Paginator SubredditID Subreddit
paginator =
APIAction (Listing SubredditID Subreddit)
-> m (Listing SubredditID Subreddit)
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"subreddits", PathSegment
"search" ]
, $sel:requestData:APIAction :: WithData
requestData =
Form -> WithData
WithForm (Form -> WithData) -> Form -> WithData
forall a b. (a -> b) -> a -> b
$ Paginator SubredditID Subreddit -> Form
forall a. ToForm a => a -> Form
toForm Paginator SubredditID Subreddit
paginator Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> [(PathSegment, PathSegment)] -> Form
mkTextForm [ (PathSegment
"q", PathSegment
query) ]
}
searchSubredditsByName
:: MonadReddit m
=> Maybe Bool
-> Maybe Bool
-> Text
-> m (Seq SubredditName)
searchSubredditsByName :: Maybe Bool -> Maybe Bool -> PathSegment -> m (Seq SubredditName)
searchSubredditsByName Maybe Bool
withNSFW Maybe Bool
exact PathSegment
query =
APIAction NameSearchResults -> m NameSearchResults
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @NameSearchResults APIAction NameSearchResults
forall a. APIAction a
r m NameSearchResults
-> (NameSearchResults -> Seq SubredditName)
-> m (Seq SubredditName)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> NameSearchResults -> Seq SubredditName
forall s t a b. Wrapped s t a b => s -> a
wrappedTo
where
r :: APIAction a
r = APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"search_reddit_names" ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData =
[(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"query", PathSegment
query)
, (PathSegment
"exact", Bool -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam (Bool -> PathSegment) -> Bool -> PathSegment
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False Maybe Bool
exact)
, ( PathSegment
"include_over_18"
, Bool -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam (Bool -> PathSegment) -> Bool -> PathSegment
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
True Maybe Bool
withNSFW
)
]
}
getRecommendedSubreddits
:: (MonadReddit m, Foldable t)
=> Maybe (t SubredditName)
-> t SubredditName
-> m (Seq SubredditName)
getRecommendedSubreddits :: Maybe (t SubredditName) -> t SubredditName -> m (Seq SubredditName)
getRecommendedSubreddits Maybe (t SubredditName)
omit t SubredditName
snames = APIAction RecsList -> m RecsList
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @RecsList APIAction RecsList
forall a. APIAction a
r m RecsList
-> (RecsList -> Seq SubredditName) -> m (Seq SubredditName)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> RecsList -> Seq SubredditName
forall s t a b. Wrapped s t a b => s -> a
wrappedTo
where
r :: APIAction a
r = APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"recommend", PathSegment
"sr", t SubredditName -> PathSegment
forall (t :: * -> *) a.
(Foldable t, ToHttpApiData a) =>
t a -> PathSegment
joinParams t SubredditName
snames ]
, $sel:requestData:APIAction :: WithData
requestData =
[(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"omit", PathSegment
-> (t SubredditName -> PathSegment)
-> Maybe (t SubredditName)
-> PathSegment
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PathSegment
forall a. Monoid a => a
mempty t SubredditName -> PathSegment
forall (t :: * -> *) a.
(Foldable t, ToHttpApiData a) =>
t a -> PathSegment
joinParams Maybe (t SubredditName)
omit) ]
}
subredditListing :: MonadReddit m
=> PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
subredditListing :: PathSegment
-> Paginator SubredditID Subreddit
-> m (Listing SubredditID Subreddit)
subredditListing PathSegment
path Paginator SubredditID Subreddit
paginator =
APIAction (Listing SubredditID Subreddit)
-> m (Listing SubredditID Subreddit)
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"subreddits", PathSegment
path ]
, $sel:requestData:APIAction :: WithData
requestData = Paginator SubredditID Subreddit -> WithData
forall t a. (Thing t, Paginable a) => Paginator t a -> WithData
paginatorToFormData Paginator SubredditID Subreddit
paginator
}
getCollections :: MonadReddit m => SubredditID -> m (Seq Collection)
getCollections :: SubredditID -> m (Seq Collection)
getCollections SubredditID
sid =
APIAction (Seq Collection) -> m (Seq Collection)
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = PathSegment -> [PathSegment]
collectionsPath PathSegment
"subreddit_collections"
, $sel:requestData:APIAction :: WithData
requestData =
[(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"sr_fullname", SubredditID -> PathSegment
forall a. Thing a => a -> PathSegment
fullname SubredditID
sid) ]
}
getCollectionsWithName :: MonadReddit m => SubredditName -> m (Seq Collection)
getCollectionsWithName :: SubredditName -> m (Seq Collection)
getCollectionsWithName SubredditName
sname = do
Subreddit { SubredditID
$sel:subredditID:Subreddit :: Subreddit -> SubredditID
subredditID :: SubredditID
subredditID } <- SubredditName -> m Subreddit
forall (m :: * -> *). MonadReddit m => SubredditName -> m Subreddit
getSubreddit SubredditName
sname
SubredditID -> m (Seq Collection)
forall (m :: * -> *).
MonadReddit m =>
SubredditID -> m (Seq Collection)
getCollections SubredditID
subredditID
getCollection :: MonadReddit m => CollectionID -> m Collection
getCollection :: PathSegment -> m Collection
getCollection PathSegment
cid = m Collection -> (APIException -> m Collection) -> m Collection
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
catch @_ @APIException m Collection
action ((APIException -> m Collection) -> m Collection)
-> (APIException -> m Collection) -> m Collection
forall a b. (a -> b) -> a -> b
$ \case
ErrorWithMessage ErrorMessage
EmptyError -> APIException -> m Collection
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (APIException -> m Collection)
-> (StatusMessage -> APIException) -> StatusMessage -> m Collection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StatusMessage -> APIException
ErrorWithStatus
(StatusMessage -> m Collection) -> StatusMessage -> m Collection
forall a b. (a -> b) -> a -> b
$ StatusCode -> PathSegment -> StatusMessage
StatusMessage StatusCode
404 PathSegment
"getCollection: Collection does not exist"
APIException
e -> APIException -> m Collection
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM APIException
e
where
action :: m Collection
action =
APIAction Collection -> m Collection
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = PathSegment -> [PathSegment]
collectionsPath PathSegment
"collection"
, $sel:requestData:APIAction :: WithData
requestData = [(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"collection_id", PathSegment
cid)
, (PathSegment
"include_links", PathSegment
"true")
]
}
getCollectionByPermalink :: MonadReddit m => URL -> m Collection
getCollectionByPermalink :: PathSegment -> m Collection
getCollectionByPermalink PathSegment
pl = PathSegment -> m (ByteString, [PathSegment])
forall (m :: * -> *).
MonadThrow m =>
PathSegment -> m (ByteString, [PathSegment])
splitURL PathSegment
pl m (ByteString, [PathSegment])
-> ((ByteString, [PathSegment]) -> m Collection) -> m Collection
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
(ByteString
_, [ PathSegment
"r", PathSegment
_, PathSegment
"collection", PathSegment
cid ]) -> PathSegment -> m Collection
forall (m :: * -> *). MonadReddit m => PathSegment -> m Collection
getCollection PathSegment
cid
(ByteString, [PathSegment])
_ -> ClientException -> m Collection
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM
(ClientException -> m Collection)
-> ClientException -> m Collection
forall a b. (a -> b) -> a -> b
$ PathSegment -> ClientException
InvalidRequest PathSegment
"getCollectionByPermalink: invalid permalink provided"
followCollection :: MonadReddit m => CollectionID -> m ()
followCollection :: PathSegment -> m ()
followCollection = Bool -> PathSegment -> m ()
forall (m :: * -> *). MonadReddit m => Bool -> PathSegment -> m ()
followUnfollow Bool
True
unfollowCollection :: MonadReddit m => CollectionID -> m ()
unfollowCollection :: PathSegment -> m ()
unfollowCollection = Bool -> PathSegment -> m ()
forall (m :: * -> *). MonadReddit m => Bool -> PathSegment -> m ()
followUnfollow Bool
False
followUnfollow :: MonadReddit m => Bool -> CollectionID -> m ()
followUnfollow :: Bool -> PathSegment -> m ()
followUnfollow Bool
follow PathSegment
cid =
APIAction () -> m ()
forall (m :: * -> *). MonadReddit m => APIAction () -> m ()
runAction_ APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = PathSegment -> [PathSegment]
collectionsPath PathSegment
"follow_collection"
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData =
[(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"collection_id", PathSegment
cid)
, (PathSegment
"follow", Bool -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam Bool
follow)
]
}
collectionsPath :: PathSegment -> [PathSegment]
collectionsPath :: PathSegment -> [PathSegment]
collectionsPath PathSegment
path = [ PathSegment
"api", PathSegment
"v1", PathSegment
"collections", PathSegment
path ]
getUserFlairTemplates
:: MonadReddit m => SubredditName -> m (Seq FlairTemplate)
getUserFlairTemplates :: SubredditName -> m (Seq FlairTemplate)
getUserFlairTemplates = PathSegment -> SubredditName -> m (Seq FlairTemplate)
forall (m :: * -> *).
MonadReddit m =>
PathSegment -> SubredditName -> m (Seq FlairTemplate)
v2Flair PathSegment
"user"
getSubmissionFlairTemplates
:: MonadReddit m => SubredditName -> m (Seq FlairTemplate)
getSubmissionFlairTemplates :: SubredditName -> m (Seq FlairTemplate)
getSubmissionFlairTemplates = PathSegment -> SubredditName -> m (Seq FlairTemplate)
forall (m :: * -> *).
MonadReddit m =>
PathSegment -> SubredditName -> m (Seq FlairTemplate)
v2Flair PathSegment
"link"
v2Flair :: MonadReddit m => Text -> SubredditName -> m (Seq FlairTemplate)
v2Flair :: PathSegment -> SubredditName -> m (Seq FlairTemplate)
v2Flair PathSegment
path SubredditName
sname =
APIAction (Seq FlairTemplate) -> m (Seq FlairTemplate)
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = SubredditName -> PathSegment -> [PathSegment]
subAPIPath SubredditName
sname (PathSegment -> [PathSegment]) -> PathSegment -> [PathSegment]
forall a b. (a -> b) -> a -> b
$ PathSegment
path PathSegment -> PathSegment -> PathSegment
forall a. Semigroup a => a -> a -> a
<> PathSegment
"_flair_v2" }
getNewSubmissionFlairChoices
:: MonadReddit m => SubredditName -> m (Seq FlairChoice)
getNewSubmissionFlairChoices :: SubredditName -> m (Seq FlairChoice)
getNewSubmissionFlairChoices =
Form -> SubredditName -> m (Seq FlairChoice)
forall (m :: * -> *).
MonadReddit m =>
Form -> SubredditName -> m (Seq FlairChoice)
flairChoices ([(PathSegment, PathSegment)] -> Form
mkTextForm [ (PathSegment
"is_newlink", Bool -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam Bool
True) ])
getSubmissionFlairChoices
:: MonadReddit m => SubredditName -> SubmissionID -> m (Seq FlairChoice)
getSubmissionFlairChoices :: SubredditName -> SubmissionID -> m (Seq FlairChoice)
getSubmissionFlairChoices SubredditName
sname SubmissionID
sid = Form -> SubredditName -> m (Seq FlairChoice)
forall (m :: * -> *).
MonadReddit m =>
Form -> SubredditName -> m (Seq FlairChoice)
flairChoices Form
form SubredditName
sname
where
form :: Form
form = [(PathSegment, PathSegment)] -> Form
mkTextForm [ (PathSegment
"link", SubmissionID -> PathSegment
forall a. Thing a => a -> PathSegment
fullname SubmissionID
sid) ]
getUserFlairChoices :: MonadReddit m => SubredditName -> m (Seq FlairChoice)
getUserFlairChoices :: SubredditName -> m (Seq FlairChoice)
getUserFlairChoices = Form -> SubredditName -> m (Seq FlairChoice)
forall (m :: * -> *).
MonadReddit m =>
Form -> SubredditName -> m (Seq FlairChoice)
flairChoices ([(PathSegment, PathSegment)] -> Form
mkTextForm [(PathSegment, PathSegment)]
forall a. Monoid a => a
mempty)
flairChoices :: MonadReddit m => Form -> SubredditName -> m (Seq FlairChoice)
flairChoices :: Form -> SubredditName -> m (Seq FlairChoice)
flairChoices Form
form SubredditName
sname = APIAction FlairChoiceList -> m FlairChoiceList
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @FlairChoiceList APIAction FlairChoiceList
forall a. APIAction a
r m FlairChoiceList
-> (FlairChoiceList -> Seq FlairChoice) -> m (Seq FlairChoice)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> FlairChoiceList -> Seq FlairChoice
forall s t a b. Wrapped s t a b => s -> a
wrappedTo
where
r :: APIAction a
r = APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = SubredditName -> PathSegment -> [PathSegment]
subAPIPath SubredditName
sname PathSegment
"flairselector"
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData = Form -> WithData
WithForm Form
form
}
getWikiPage :: MonadReddit m => SubredditName -> WikiPageName -> m WikiPage
getWikiPage :: SubredditName -> WikiPageName -> m WikiPage
getWikiPage SubredditName
sname WikiPageName
wpage =
APIAction WikiPage -> m WikiPage
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments =
[ PathSegment
"r", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"wiki", WikiPageName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece WikiPageName
wpage ]
}
getWikiPages :: MonadReddit m => SubredditName -> m (Seq WikiPageName)
getWikiPages :: SubredditName -> m (Seq WikiPageName)
getWikiPages SubredditName
sname = APIAction WikiPageListing -> m WikiPageListing
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @WikiPageListing APIAction WikiPageListing
forall a. APIAction a
r m WikiPageListing
-> (WikiPageListing -> Seq WikiPageName) -> m (Seq WikiPageName)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> WikiPageListing -> Seq WikiPageName
forall s t a b. Wrapped s t a b => s -> a
wrappedTo
where
r :: APIAction a
r = APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"r", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"wiki", PathSegment
"pages" ] }
getWikiPageRevision :: MonadReddit m
=> SubredditName
-> WikiPageName
-> WikiRevisionID
-> m WikiPage
SubredditName
sname WikiPageName
wpage WikiRevisionID
wr =
APIAction WikiPage -> m WikiPage
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments =
[ PathSegment
"r", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"wiki", WikiPageName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece WikiPageName
wpage ]
, $sel:requestData:APIAction :: WithData
requestData = [(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"v", WikiRevisionID -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam WikiRevisionID
wr) ]
}
getWikiPageRevisions
:: MonadReddit m
=> SubredditName
-> WikiPageName
-> Paginator WikiRevisionID WikiRevision
-> m (Listing WikiRevisionID WikiRevision)
SubredditName
sname WikiPageName
wpage Paginator WikiRevisionID WikiRevision
paginator =
APIAction (Listing WikiRevisionID WikiRevision)
-> m (Listing WikiRevisionID WikiRevision)
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"r"
, SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname
, PathSegment
"wiki"
, PathSegment
"revisions"
, WikiPageName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece WikiPageName
wpage
]
, $sel:requestData:APIAction :: WithData
requestData = Paginator WikiRevisionID WikiRevision -> WithData
forall t a. (Thing t, Paginable a) => Paginator t a -> WithData
paginatorToFormData Paginator WikiRevisionID WikiRevision
paginator
}
editWikiPage :: MonadReddit m
=> SubredditName
-> WikiPageName
-> Maybe Text
-> Body
-> m ()
editWikiPage :: SubredditName
-> WikiPageName -> Maybe PathSegment -> PathSegment -> m ()
editWikiPage SubredditName
sname WikiPageName
wpage Maybe PathSegment
r PathSegment
txt =
APIAction () -> m ()
forall (m :: * -> *). MonadReddit m => APIAction () -> m ()
runAction_ APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments =
[ PathSegment
"r", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"api", PathSegment
"wiki", PathSegment
"edit" ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData = [(PathSegment, PathSegment)] -> WithData
mkTextFormData
([(PathSegment, PathSegment)] -> WithData)
-> [(PathSegment, PathSegment)] -> WithData
forall a b. (a -> b) -> a -> b
$ [ (PathSegment
"page", WikiPageName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam WikiPageName
wpage), (PathSegment
"content", PathSegment
txt) ]
[(PathSegment, PathSegment)]
-> [(PathSegment, PathSegment)] -> [(PathSegment, PathSegment)]
forall a. Semigroup a => a -> a -> a
<> ((PathSegment, PathSegment) -> [(PathSegment, PathSegment)])
-> Maybe (PathSegment, PathSegment) -> [(PathSegment, PathSegment)]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (PathSegment, PathSegment) -> [(PathSegment, PathSegment)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((PathSegment
"reason", ) (PathSegment -> (PathSegment, PathSegment))
-> Maybe PathSegment -> Maybe (PathSegment, PathSegment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe PathSegment
r)
}
createWikiPage :: MonadReddit m
=> SubredditName
-> WikiPageName
-> Maybe Text
-> Body
-> m ()
createWikiPage :: SubredditName
-> WikiPageName -> Maybe PathSegment -> PathSegment -> m ()
createWikiPage = SubredditName
-> WikiPageName -> Maybe PathSegment -> PathSegment -> m ()
forall (m :: * -> *).
MonadReddit m =>
SubredditName
-> WikiPageName -> Maybe PathSegment -> PathSegment -> m ()
editWikiPage
getSubredditWidgets :: MonadReddit m => SubredditName -> m SubredditWidgets
getSubredditWidgets :: SubredditName -> m SubredditWidgets
getSubredditWidgets SubredditName
sname = m SubredditWidgets -> m SubredditWidgets
forall (m :: * -> *) a. MonadReddit m => m a -> m a
catchEmptyListing
(m SubredditWidgets -> m SubredditWidgets)
-> m SubredditWidgets -> m SubredditWidgets
forall a b. (a -> b) -> a -> b
$ APIAction SubredditWidgets -> m SubredditWidgets
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction { $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = SubredditName -> PathSegment -> [PathSegment]
subAPIPath SubredditName
sname PathSegment
"widgets" }
getAllSubredditWidgets :: MonadReddit m => SubredditName -> m (Seq Widget)
getAllSubredditWidgets :: SubredditName -> m (Seq Widget)
getAllSubredditWidgets SubredditName
sname =
m (Seq Widget) -> m (Seq Widget)
forall (m :: * -> *) a. MonadReddit m => m a -> m a
catchEmptyListing (m (Seq Widget) -> m (Seq Widget))
-> m (Seq Widget) -> m (Seq Widget)
forall a b. (a -> b) -> a -> b
$ APIAction WidgetList -> m WidgetList
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @WidgetList APIAction WidgetList
forall a. APIAction a
r m WidgetList -> (WidgetList -> Seq Widget) -> m (Seq Widget)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> WidgetList -> Seq Widget
forall s t a b. Wrapped s t a b => s -> a
wrappedTo
where
r :: APIAction a
r = APIAction Any
forall a. APIAction a
defaultAPIAction { $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = SubredditName -> PathSegment -> [PathSegment]
subAPIPath SubredditName
sname PathSegment
"widgets" }
getSubredditEmojis :: MonadReddit m => SubredditName -> m (Seq Emoji)
getSubredditEmojis :: SubredditName -> m (Seq Emoji)
getSubredditEmojis SubredditName
sname = APIAction EmojiList -> m EmojiList
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @EmojiList APIAction EmojiList
forall a. APIAction a
r m EmojiList -> (EmojiList -> Seq Emoji) -> m (Seq Emoji)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> EmojiList -> Seq Emoji
forall s t a b. Wrapped s t a b => s -> a
wrappedTo
where
r :: APIAction a
r = APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"v1", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"emojis", PathSegment
"all" ] }