Copyright | (c) 2021 Rory Tyler Hayford |
---|---|
License | BSD-3-Clause |
Maintainer | rory.hayford@protonmail.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- newClient :: (MonadUnliftIO m, MonadThrow m) => AuthConfig -> m Client
- newClientWithManager :: (MonadUnliftIO m, MonadCatch m) => TokenManager -> AuthConfig -> m Client
- loadClient :: (MonadUnliftIO m, MonadThrow m) => Maybe ClientSite -> m Client
- getAuthURL :: Foldable t => URL -> TokenDuration -> t Scope -> ClientID -> Text -> URL
- runReddit :: (MonadCatch m, MonadIO m) => Client -> RedditT m a -> m a
- runRedditT :: Client -> RedditT m a -> m a
- tryReddit :: forall e a m. (Exception e, MonadCatch m, MonadIO m) => Client -> RedditT m a -> m (Either e a)
- getRateLimits :: MonadReddit m => m (Maybe RateLimits)
- withRateLimitDelay :: MonadReddit m => m a -> m a
- fileTokenManager :: Exception e => e -> FilePath -> TokenManager
- firstPage :: (MonadReddit m, Paginable a) => (Paginator t a -> m (Listing t a)) -> m (Seq a)
- nextPage :: forall t a. Paginable a => Maybe (Paginator t a) -> Listing t a -> Paginator t a
- emptyPaginator :: forall t a. Paginable a => Paginator t a
- stream :: forall m t a. (MonadReddit m, Paginable a, t ~ PaginateThing a) => Maybe Bool -> (Paginator t a -> m (Listing t a)) -> ConduitT () a m ()
- type MonadReddit m = (MonadUnliftIO m, MonadThrow m, MonadCatch m, MonadReader Client m)
- data RedditT m a
- data Client = Client AuthConfig Manager (IORef ClientState) (Maybe TokenManager)
- data RateLimits = RateLimits Integer Integer POSIXTime POSIXTime
- data Listing t a = Listing (Maybe t) (Maybe t) (Seq a)
- data Paginator t a = Paginator (Maybe t) (Maybe t) Word Bool Bool (PaginateOptions a)
- class Paginable a
- data ItemOpts = ItemOpts (Maybe ItemSort) (Maybe ItemType) (Maybe Time) (Maybe Word)
- defaultItemOpts :: ItemOpts
- data ItemSort
- = Hot
- | New
- | Top
- | Controversial
- | Old
- | Random
- | QA
- | Live
- | Confidence
- data ItemReport = ItemReport Text Word
- data Distinction
- data Time
- data ItemType
- data UploadURL
- type Body = Text
- type Title = Text
- type URL = Text
- type Subject = Text
- type RGBText = Text
- type Name = Text
- type Domain = Text
- type Modifier = [Char] -> [Char]
- data RedditException
- data ClientException
- data APIException
- data OAauthError = OAauthError Text (Maybe Text)
- data ErrorMessage
- data StatusMessage = StatusMessage StatusCode Text
- type StatusCode = Int
- data POSTError = POSTError [Text] Text Text Text
- data ClientState
- data AppType
- data AuthConfig = AuthConfig ClientID AppType UserAgent
- data UserAgent = UserAgent Text Text Text Text
- data AccessToken = AccessToken Token NominalDiffTime [Scope] (Maybe Token)
- type Token = Text
- type Code = Text
- data Scope
- data PasswordFlow = PasswordFlow Text Text
- data CodeFlow = CodeFlow URL Code
- type ClientID = Text
- type ClientSecret = Text
- data TokenDuration
- module Network.Reddit.User
- module Network.Reddit.Subreddit
- module Network.Reddit.Submission
- module Network.Reddit.Me
- module Network.Reddit.Comment
Documentation
newClient :: (MonadUnliftIO m, MonadThrow m) => AuthConfig -> m Client Source #
Create a new Client
for API access, given an AuthConfig
. This client is
required to run all actions in this library.
See loadClient
if you have a ScriptApp
or ApplicationOnly
app and would
like to load your auth details from an ini file
newClientWithManager :: (MonadUnliftIO m, MonadCatch m) => TokenManager -> AuthConfig -> m Client Source #
Create a new client with an existing refresh token, for WebApp
s and
InstalledApp
s. The initial refresh token is provided with a TokenManager
that will also handle saving and loading refresh tokens over the life of
the new Client
loadClient :: (MonadUnliftIO m, MonadThrow m) => Maybe ClientSite -> m Client Source #
Load a client from saved credentials, which are stored in an ini file. Files should conform to the following formats:
For ScriptApp
s:
[NAME] id = <clientID> secret = <clientSecret> username = <username> password = <password> agent = <platform>,<appID>,<version>,<author>
For ApplicationOnly
apps without a user context:
[NAME] id = <clientID> secret = <clientSecret> agent = <platform>,<appID>,<version>,<author>
Where NAME corresponds to a ClientSite
that you pass to this function.
You can have various different distinct sites in a single ini file. When
invoking this function, if the provided client site is Nothing
, a section
labeled [DEFAULT]
will be used. If none is provided, an exception will be
thrown. Note that all section labels are case-insensitive.
The following locations are searched for an ini file, in order:
- $PWD/auth.ini
- $XDG_CONFIG_HOME/heddit/auth.ini
Note: Only ScriptApp
s and ApplicationOnly
are supported via this method
:: Foldable t | |
=> URL | A redirect URI, which must exactly match the one registered with Reddit when creating your application |
-> TokenDuration | |
-> t Scope | The OAuth scopes to request authorization for |
-> ClientID | |
-> Text | Text that is embedded in the callback URI when the client completes the request. It must be composed of printable ASCII characters and should be unique for the client |
-> URL |
Get the URL required to authorize your application, for WebApp
s and
InstalledApp
s
runReddit :: (MonadCatch m, MonadIO m) => Client -> RedditT m a -> m a Source #
Run an action with your Reddit Client
. This will catch any exceptions
related to POST rate-limiting for you. After sleeping for the indicated
duration, it will attempt to re-run the action that triggered the exception.
If you do not wish to catch these exceptions, or would like to handle them
in a different way, use runRedditT
, which simply runs the provided action
Note: Confusingly, Reddit uses two different rate-limiting mechanisms.
This action only catches rate limiting applied to POST requests. Another form
of rate limiting is applied to API requests in general. This library does not
automatically deal with this second type. If you wish to deal with this
yourself, see the action withRateLimitDelay
, which automatically applies a
delay based on the most recent rate limit headers returned from Reddit
tryReddit :: forall e a m. (Exception e, MonadCatch m, MonadIO m) => Client -> RedditT m a -> m (Either e a) Source #
Run an action with your Reddit Client
, catching the exception specified and
returning an Either
in case of failure. It may be best to use TypeApplications
to specify the exception type.
For example, to try to see the user FlairTemplate
s for a subreddit which may or
may not allow user flair:
>>>
tryReddit @APIException c $ getUserFlairTemplates =<< mkSubredditName "haskell"
Left (ErrorWithStatus (StatusMessage {statusCode = 403, message = "Forbidden"}))
getRateLimits :: MonadReddit m => m (Maybe RateLimits) Source #
Get current information on rate limiting, if any
withRateLimitDelay :: MonadReddit m => m a -> m a Source #
Run the provided MonadReddit
action with a delay, if rate-limiting
information is currently available
:: Exception e | |
=> e | An exception that will be thrown when Reddit doesn't return a new refresh token |
-> FilePath | The location of the stored tokens |
-> TokenManager |
This is an example TokenManager
that can be used to store and retrieve
OAUth refresh tokens, which could be used with newClientWithManager
. For
a real application, you would probably want to use a more sophisticated
manager
Actions
firstPage :: (MonadReddit m, Paginable a) => (Paginator t a -> m (Listing t a)) -> m (Seq a) Source #
Convenience wrapper for actions taking a Paginator
and which return a
Listing
. This runs the action with a default initial paginator, and extracts
the children
from the returned Listing
. This discards all of the pagination
controls that are returned in the Listing
. This is useful if you only care
about the child contents of the first "page" of results
For example, to get only the first page of results for a user's comments, you could use the following:
runReddit yourClient . firstPage $ getUserComments someUsername
nextPage :: forall t a. Paginable a => Maybe (Paginator t a) -> Listing t a -> Paginator t a Source #
Update a Paginator
with a Listing
to make a query for the next "page"
of content. If the first argument is Nothing
, defaults will be used for
the options, partially depending on the type of paginator
Note: You cannot supply both the before
and after
fields when making
requests to API endpoints. If both fields are Just
in the Paginator
you
get back from this function, the after
field will take precedence. If you
want to use before
in such a scenario, make sure to set it to Nothing
before using the paginator in an action
Example:
>>>
best1 <- runReddit yourClient $ getBest emptyPaginator
>>>
best2 <- runReddit yourClient . getBest $ nextPage Nothing best1
emptyPaginator :: forall t a. Paginable a => Paginator t a Source #
An empty, default Paginator
. Includes the default PaginateOptions
for
the type a
:: forall m t a. (MonadReddit m, Paginable a, t ~ PaginateThing a) | |
=> Maybe Bool | When |
-> (Paginator t a -> m (Listing t a)) | |
-> ConduitT () a m () |
Transform an action producing a Listing
of items into an infinite stream.
Items are pushed to the stream as they are fetched, with oldest items yielded
first. New items are fetched in 100-item batches. If nothing new arrives in
the stream, a jittered exponential backoff is applied, up to a cap of ~16s,
resetting once new items arrive again.
For example, to fetch new submissions published to "r/haskell", as they are created, and print their IDs to the console:
>>>
import Conduit
>>>
subName <- mkSubredditName "haskell"
>>>
action = getNewSubmissions subName
>>>
printTitle = liftIO . print . (^. #title)
>>>
runReddit c . runConduit $ stream Nothing action .| mapM_C printTitle
SubmissionID "o6948i" SubmissionID "o6b0w0" SubmissionID "o6cqof" SubmissionID "o6ddl9" SubmissionID "o6dlas" ...
Basic types
type MonadReddit m = (MonadUnliftIO m, MonadThrow m, MonadCatch m, MonadReader Client m) Source #
Synonym for constraints that RedditT
actions must satisfy
The monad tranformer in which Reddit API transactions can be executed
Instances
Monad m => MonadReader Client (RedditT m) Source # | |
Monad m => Monad (RedditT m) Source # | |
Functor m => Functor (RedditT m) Source # | |
Applicative m => Applicative (RedditT m) Source # | |
MonadIO m => MonadIO (RedditT m) Source # | |
Defined in Network.Reddit.Types | |
MonadUnliftIO m => MonadUnliftIO (RedditT m) Source # | |
Defined in Network.Reddit.Types | |
MonadThrow m => MonadThrow (RedditT m) Source # | |
Defined in Network.Reddit.Types | |
MonadCatch m => MonadCatch (RedditT m) Source # | |
A client facilitating access to Reddit's API
Instances
Generic Client Source # | |
HasHttpManager Client Source # | |
Defined in Network.Reddit.Types getHttpManager :: Client -> Manager # | |
Monad m => MonadReader Client (RedditT m) Source # | |
type Rep Client Source # | |
Defined in Network.Reddit.Types type Rep Client = D1 ('MetaData "Client" "Network.Reddit.Types" "heddit-0.1-70ReOU8uVjwHwPvCNnDeID" 'False) (C1 ('MetaCons "Client" 'PrefixI 'True) ((S1 ('MetaSel ('Just "authConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AuthConfig) :*: S1 ('MetaSel ('Just "manager") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Manager)) :*: (S1 ('MetaSel ('Just "clientState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IORef ClientState)) :*: S1 ('MetaSel ('Just "tokenManager") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe TokenManager))))) |
data RateLimits Source #
Rate limit info
Instances
Certain API endpoints are listings
, which can be paginated and filtered
using a Paginator
Instances
(Eq t, Eq a) => Eq (Listing t a) Source # | |
(Show t, Show a) => Show (Listing t a) Source # | |
Generic (Listing t a) Source # | |
Ord t => Semigroup (Listing t a) Source # | |
Ord t => Monoid (Listing t a) Source # | |
(FromJSON a, FromJSON t) => FromJSON (Listing t a) Source # | |
type Rep (Listing t a) Source # | |
Defined in Network.Reddit.Types.Internal type Rep (Listing t a) = D1 ('MetaData "Listing" "Network.Reddit.Types.Internal" "heddit-0.1-70ReOU8uVjwHwPvCNnDeID" 'False) (C1 ('MetaCons "Listing" 'PrefixI 'True) (S1 ('MetaSel ('Just "before") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe t)) :*: (S1 ('MetaSel ('Just "after") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe t)) :*: S1 ('MetaSel ('Just "children") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq a))))) |
This represents the protocol that Reddit uses to control paginating and
filtering entries. These can be applied to Listing
endpoints. The first
four fields below are common parameters that are applied to each Listing
.
The opts
field takes extended PaginateOptions
based on the second type
parameter
Instances
Represents requests that can take additional options in a Paginator
. This
can be used to filter/sort Listing
endpoints
Instances
Options that can be applied to comments or submissions
Instances
Eq ItemOpts Source # | |
Show ItemOpts Source # | |
Generic ItemOpts Source # | |
ToForm ItemOpts Source # | |
Defined in Network.Reddit.Types.Internal | |
type Rep ItemOpts Source # | |
Defined in Network.Reddit.Types.Internal type Rep ItemOpts = D1 ('MetaData "ItemOpts" "Network.Reddit.Types.Internal" "heddit-0.1-70ReOU8uVjwHwPvCNnDeID" 'False) (C1 ('MetaCons "ItemOpts" 'PrefixI 'True) ((S1 ('MetaSel ('Just "itemSort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ItemSort)) :*: S1 ('MetaSel ('Just "itemType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ItemType))) :*: (S1 ('MetaSel ('Just "itemTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Time)) :*: S1 ('MetaSel ('Just "context") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Word))))) |
defaultItemOpts :: ItemOpts Source #
Defaults for fetching items, like comments or submissions
How to sort items in certain Listing
s. Not every option is guaranteed to
be accepted by a given endpoint
Instances
data ItemReport Source #
A user- or moderator-generated report on a submission
Instances
data Distinction Source #
Sigils that a moderator can add to distinguish comments or submissions. Note
that the Admin
and Special
distinctions require special privileges to use
Moderator | Adds "[M]" |
Undistinguished | Removes an existing distinction when sent |
Admin | Adds "[A]" |
Special | User-specific distinction |
Instances
Time range when fetching comments or submissions
Instances
Eq Time Source # | |
Show Time Source # | |
Generic Time Source # | |
ToHttpApiData Time Source # | |
Defined in Network.Reddit.Types.Internal toUrlPiece :: Time -> Text # toEncodedUrlPiece :: Time -> Builder # toHeader :: Time -> ByteString # toQueryParam :: Time -> Text # | |
type Rep Time Source # | |
Defined in Network.Reddit.Types.Internal type Rep Time = D1 ('MetaData "Time" "Network.Reddit.Types.Internal" "heddit-0.1-70ReOU8uVjwHwPvCNnDeID" 'False) ((C1 ('MetaCons "Hour" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Day" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Week" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Month" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Year" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllTime" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Type of comments, for filtering in Listing
s
Instances
Eq ItemType Source # | |
Show ItemType Source # | |
Generic ItemType Source # | |
ToHttpApiData ItemType Source # | |
Defined in Network.Reddit.Types.Internal toUrlPiece :: ItemType -> Text # toEncodedUrlPiece :: ItemType -> Builder # toHeader :: ItemType -> ByteString # toQueryParam :: ItemType -> Text # | |
type Rep ItemType Source # | |
A URL pointing to a resource hosted by Reddit. These should only be obtained
by parsing the JSON of existing resources or through particular actions that
perform the upload transaction and return the URL, e.g.
uploadWidgetImage
Instances
Eq UploadURL Source # | |
Show UploadURL Source # | |
Generic UploadURL Source # | |
ToJSON UploadURL Source # | |
Defined in Network.Reddit.Types.Internal | |
FromJSON UploadURL Source # | |
ToHttpApiData UploadURL Source # | |
Defined in Network.Reddit.Types.Internal toUrlPiece :: UploadURL -> Text # toEncodedUrlPiece :: UploadURL -> Builder # toHeader :: UploadURL -> ByteString # toQueryParam :: UploadURL -> Text # | |
type Rep UploadURL Source # | |
Defined in Network.Reddit.Types.Internal |
Exceptions
data RedditException Source #
Base exception type for Reddit API client
Instances
Show RedditException Source # | |
Defined in Network.Reddit.Types.Internal showsPrec :: Int -> RedditException -> ShowS # show :: RedditException -> String # showList :: [RedditException] -> ShowS # | |
Exception RedditException Source # | |
Defined in Network.Reddit.Types.Internal |
data ClientException Source #
Exceptions generated within the Reddit API client
InvalidRequest Text | |
InvalidResponse Text | |
MalformedCredentials Text | |
OtherError Text | |
ConfigurationError Text |
Instances
data APIException Source #
Exceptions returned from API endpoints
ErrorWithStatus StatusMessage | |
ErrorWithMessage ErrorMessage | |
InvalidCredentials OAauthError | |
InvalidPOST POSTError | Sent if errors occur when posting JSON |
JSONParseError Text ByteString | With the response body, for further debugging |
Redirected (Maybe Request) | If the API action should not allow automatic redirects, this error returns the possible redirected request |
WebsocketError Text SomeException | Thrown when exceptions occur during websocket handling |
UploadFailed | When an error occurs uploading media to Reddit's servers |
Instances
data OAauthError Source #
An error which occurs when attempting to authenticate via OAuth
Instances
data ErrorMessage Source #
A specific error message
Instances
data StatusMessage Source #
Details about a non-200 HTTP response
Instances
type StatusCode = Int Source #
Type synonym for status codes in responses
Details about a non-200 response when sending a POST request
Instances
Eq POSTError Source # | |
Show POSTError Source # | |
Generic POSTError Source # | |
FromJSON POSTError Source # | |
type Rep POSTError Source # | |
Defined in Network.Reddit.Types.Internal type Rep POSTError = D1 ('MetaData "POSTError" "Network.Reddit.Types.Internal" "heddit-0.1-70ReOU8uVjwHwPvCNnDeID" 'False) (C1 ('MetaCons "POSTError" 'PrefixI 'True) ((S1 ('MetaSel ('Just "fields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "explanation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))) |
Auth
data ClientState Source #
Stateful data that may be updated over the course of a Client
lifetime
Instances
The three forms of application that may use the Reddit API, each having different API access patterns
ScriptApp ClientSecret PasswordFlow | The simplest type of application. May only be used by the developer who owns the account. This requires supplying the usernme and password associated with the account |
WebApp ClientSecret CodeFlow | For applications running on a server backend |
InstalledApp CodeFlow | For applications installed on devices that the developer does not own (e.g., a mobile application) |
ApplicationOnly ClientSecret |
Instances
data AuthConfig Source #
A configuration
Instances
A unique user agent to identify your application; Reddit applies rate-limiting to common agents, and actively bans misleading ones
Instances
Eq UserAgent Source # | |
Show UserAgent Source # | |
Generic UserAgent Source # | |
type Rep UserAgent Source # | |
Defined in Network.Reddit.Types type Rep UserAgent = D1 ('MetaData "UserAgent" "Network.Reddit.Types" "heddit-0.1-70ReOU8uVjwHwPvCNnDeID" 'False) (C1 ('MetaCons "UserAgent" 'PrefixI 'True) ((S1 ('MetaSel ('Just "platform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "appID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))) |
data AccessToken Source #
Token received after authentication
Instances
Type synonym for the text of codes returned from auth URLs, for WebApp
s
and InstalledApp
s
Represents a specific Reddit functionality that must be explicitly requested
Accounts | Corresponds to "account" in text form |
Creddits | |
Edit | |
Flair | |
History | |
Identity | |
LiveManage | |
ModConfig | |
ModContributors | |
ModFlair | |
ModLog | |
ModMail | |
ModOthers | |
ModPosts | |
ModSelf | |
ModTraffic | |
ModWiki | |
MySubreddits | |
PrivateMessages | |
Read | |
Report | |
Save | |
StructuredStyles | |
Submit | |
Subscribe | |
Vote | |
WikiEdit | |
WikiRead | |
Unlimited | For all scopes, corresponds to "*" |
Instances
data PasswordFlow Source #
Simple user credentials for authenticating via ScriptApp
s
Note: These credentials will be kept in memory!
Instances
Details for OAuth "code flow", for WebApp
s and InstalledApp
s
Instances
Eq CodeFlow Source # | |
Show CodeFlow Source # | |
Generic CodeFlow Source # | |
ToForm CodeFlow Source # | |
Defined in Network.Reddit.Types | |
type Rep CodeFlow Source # | |
Defined in Network.Reddit.Types type Rep CodeFlow = D1 ('MetaData "CodeFlow" "Network.Reddit.Types" "heddit-0.1-70ReOU8uVjwHwPvCNnDeID" 'False) (C1 ('MetaCons "CodeFlow" 'PrefixI 'True) (S1 ('MetaSel ('Just "redirectURI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "code") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Code))) |
type ClientSecret = Text Source #
Type synonym for client secrets
data TokenDuration Source #
The duration of the access token for WebApp
s and InstalledApp
s
Temporary | Generates one-hour access tokens without a refresh token |
Permanent | Generates a one-hour access tokens with a refresh token that can be used to indefinitely obtain new access tokens |
Instances
Eq TokenDuration Source # | |
Defined in Network.Reddit.Types (==) :: TokenDuration -> TokenDuration -> Bool # (/=) :: TokenDuration -> TokenDuration -> Bool # | |
Show TokenDuration Source # | |
Defined in Network.Reddit.Types showsPrec :: Int -> TokenDuration -> ShowS # show :: TokenDuration -> String # showList :: [TokenDuration] -> ShowS # | |
Generic TokenDuration Source # | |
Defined in Network.Reddit.Types type Rep TokenDuration :: Type -> Type # from :: TokenDuration -> Rep TokenDuration x # to :: Rep TokenDuration x -> TokenDuration # | |
ToHttpApiData TokenDuration Source # | |
Defined in Network.Reddit.Types toUrlPiece :: TokenDuration -> Text # toEncodedUrlPiece :: TokenDuration -> Builder # toHeader :: TokenDuration -> ByteString # toQueryParam :: TokenDuration -> Text # | |
type Rep TokenDuration Source # | |
Re-exports
Only modules covering basic functionality are re-exported, including those for users, subreddits, submissions, comments, and actions for the authenticated user. For actions and types touching on moderation, collections, live threads, and more, import the respective modules directly
module Network.Reddit.User
module Network.Reddit.Subreddit
module Network.Reddit.Submission
module Network.Reddit.Me
module Network.Reddit.Comment