heddit-0.2: Reddit API bindings
Copyright(c) 2021 Rory Tyler Hayford
LicenseBSD-3-Clause
Maintainerrory.hayford@protonmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Network.Reddit

Description

heddit provides Haskell bindings to Reddit's API. It aims to be as feature- rich and comprehensive as libraries such as praw for Python.

This module exports most of the functionality you will need to get started with heddit, including authentication and actions/types to work with users, subreddits, submissions, and comments. For a more in-depth introduction, please see the README in this repository or at https://gitlab.com/ngua/heddit

Synopsis

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 WebApps and InstalledApps. 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 ScriptApps:

[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 ScriptApps and ApplicationOnly are supported via this method

getAuthURL Source #

Arguments

:: 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 WebApps and InstalledApps

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

runRedditT :: Client -> RedditT m a -> m a Source #

Run a RedditT action

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 FlairTemplates 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

withReadOnly :: MonadReddit m => m a -> m a Source #

Run a MonadReddit action in a read-only context, as if you were using an ApplicationOnly client

Note: To avoid cases where the current AccessToken expires while running an action in this environment, the token will be refreshed before running the provided action

fileTokenManager Source #

Arguments

:: 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

stream Source #

Arguments

:: forall m t a. (MonadReddit m, Paginable a, t ~ PaginateThing a) 
=> Maybe Bool

When True, will only yield items that have newly arrived, thus skipping items from the first request that already existed

-> (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

data RedditT m a Source #

The monad tranformer in which Reddit API transactions can be executed

Instances

Instances details
Monad m => MonadReader Client (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

ask :: RedditT m Client #

local :: (Client -> Client) -> RedditT m a -> RedditT m a #

reader :: (Client -> a) -> RedditT m a #

Monad m => Monad (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

(>>=) :: RedditT m a -> (a -> RedditT m b) -> RedditT m b #

(>>) :: RedditT m a -> RedditT m b -> RedditT m b #

return :: a -> RedditT m a #

Functor m => Functor (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

fmap :: (a -> b) -> RedditT m a -> RedditT m b #

(<$) :: a -> RedditT m b -> RedditT m a #

Applicative m => Applicative (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

pure :: a -> RedditT m a #

(<*>) :: RedditT m (a -> b) -> RedditT m a -> RedditT m b #

liftA2 :: (a -> b -> c) -> RedditT m a -> RedditT m b -> RedditT m c #

(*>) :: RedditT m a -> RedditT m b -> RedditT m b #

(<*) :: RedditT m a -> RedditT m b -> RedditT m a #

MonadIO m => MonadIO (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

liftIO :: IO a -> RedditT m a #

MonadUnliftIO m => MonadUnliftIO (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

withRunInIO :: ((forall a. RedditT m a -> IO a) -> IO b) -> RedditT m b #

MonadThrow m => MonadThrow (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

throwM :: Exception e => e -> RedditT m a #

MonadCatch m => MonadCatch (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

catch :: Exception e => RedditT m a -> (e -> RedditT m a) -> RedditT m a #

data Client Source #

A client facilitating access to Reddit's API

Instances

Instances details
Generic Client Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep Client :: Type -> Type #

Methods

from :: Client -> Rep Client x #

to :: Rep Client x -> Client #

HasHttpManager Client Source # 
Instance details

Defined in Network.Reddit.Types

Monad m => MonadReader Client (RedditT m) Source # 
Instance details

Defined in Network.Reddit.Types

Methods

ask :: RedditT m Client #

local :: (Client -> Client) -> RedditT m a -> RedditT m a #

reader :: (Client -> a) -> RedditT m a #

type Rep Client Source # 
Instance details

Defined in Network.Reddit.Types

data RateLimits Source #

Rate limit info

Instances

Instances details
Eq RateLimits Source # 
Instance details

Defined in Network.Reddit.Types

Show RateLimits Source # 
Instance details

Defined in Network.Reddit.Types

Generic RateLimits Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep RateLimits :: Type -> Type #

type Rep RateLimits Source # 
Instance details

Defined in Network.Reddit.Types

data Listing t a Source #

Certain API endpoints are listings, which can be paginated and filtered using a Paginator

Constructors

Listing (Maybe t) (Maybe t) (Seq a) 

Instances

Instances details
(Eq t, Eq a) => Eq (Listing t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

(==) :: Listing t a -> Listing t a -> Bool #

(/=) :: Listing t a -> Listing t a -> Bool #

(Show t, Show a) => Show (Listing t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

showsPrec :: Int -> Listing t a -> ShowS #

show :: Listing t a -> String #

showList :: [Listing t a] -> ShowS #

Generic (Listing t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep (Listing t a) :: Type -> Type #

Methods

from :: Listing t a -> Rep (Listing t a) x #

to :: Rep (Listing t a) x -> Listing t a #

Ord t => Semigroup (Listing t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

(<>) :: Listing t a -> Listing t a -> Listing t a #

sconcat :: NonEmpty (Listing t a) -> Listing t a #

stimes :: Integral b => b -> Listing t a -> Listing t a #

Ord t => Monoid (Listing t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

mempty :: Listing t a #

mappend :: Listing t a -> Listing t a -> Listing t a #

mconcat :: [Listing t a] -> Listing t a #

(FromJSON a, FromJSON t) => FromJSON (Listing t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep (Listing t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep (Listing t a) = D1 ('MetaData "Listing" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" '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)))))

data Paginator t a Source #

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

Constructors

Paginator (Maybe t) (Maybe t) Word Bool Bool (PaginateOptions a) 

Instances

Instances details
(HasField' name (Paginator t a) s, a ~ b, s ~ u) => HasField name (Paginator t a) (Paginator t b) s u Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

field :: Lens (Paginator t a) (Paginator t b) s u #

(Eq t, Eq (PaginateOptions a)) => Eq (Paginator t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

(==) :: Paginator t a -> Paginator t a -> Bool #

(/=) :: Paginator t a -> Paginator t a -> Bool #

(Show t, Show (PaginateOptions a)) => Show (Paginator t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

showsPrec :: Int -> Paginator t a -> ShowS #

show :: Paginator t a -> String #

showList :: [Paginator t a] -> ShowS #

Generic (Paginator t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep (Paginator t a) :: Type -> Type #

Methods

from :: Paginator t a -> Rep (Paginator t a) x #

to :: Rep (Paginator t a) x -> Paginator t a #

(Thing t, Paginable a) => ToForm (Paginator t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

toForm :: Paginator t a -> Form #

type Rep (Paginator t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

class Paginable a Source #

Represents requests that can take additional options in a Paginator. This can be used to filter/sort Listing endpoints

Minimal complete definition

defaultOpts

Instances

Instances details
Paginable Subreddit Source # 
Instance details

Defined in Network.Reddit.Types.Subreddit

Paginable Account Source # 
Instance details

Defined in Network.Reddit.Types.Account

Paginable LiveUpdate Source # 
Instance details

Defined in Network.Reddit.Types.Live

Paginable LiveThread Source # 
Instance details

Defined in Network.Reddit.Types.Live

Paginable AssignedFlair Source # 
Instance details

Defined in Network.Reddit.Types.Flair

Paginable Search Source # 
Instance details

Defined in Network.Reddit.Types.Submission

Paginable Submission Source # 
Instance details

Defined in Network.Reddit.Types.Submission

Paginable Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Paginable Message Source # 
Instance details

Defined in Network.Reddit.Types.Message

Paginable Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

Paginable ModAction Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Paginable Ban Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Associated Types

type PaginateOptions Ban Source #

type PaginateThing Ban Source #

Paginable MuteInfo Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Paginable RelInfo Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Paginable ModItem Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Paginable WikiRevision Source # 
Instance details

Defined in Network.Reddit.Types.Wiki

pattern DeletedUser :: Username Source #

Pattern for "[deleted]" username

isUserDeleted :: Username -> Bool Source #

Test if a user has the "[deleted]" username. Also see the DeletedUser pattern synonym

data ItemOpts Source #

Options that can be applied to comments or submissions

Instances

Instances details
Eq ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ItemOpts :: Type -> Type #

Methods

from :: ItemOpts -> Rep ItemOpts x #

to :: Rep ItemOpts x -> ItemOpts #

ToForm ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

toForm :: ItemOpts -> Form #

type Rep ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemOpts = D1 ('MetaData "ItemOpts" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" '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

data ItemSort Source #

How to sort items in certain Listings. Not every option is guaranteed to be accepted by a given endpoint

Instances

Instances details
Eq ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ItemSort :: Type -> Type #

Methods

from :: ItemSort -> Rep ItemSort x #

to :: Rep ItemSort x -> ItemSort #

ToJSON ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

FromJSON ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

ToHttpApiData ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemSort = D1 ('MetaData "ItemSort" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (((C1 ('MetaCons "Hot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "New" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Top" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Controversial" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Old" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Random" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Live" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Confidence" 'PrefixI 'False) (U1 :: Type -> Type)))))

data ItemReport Source #

A user- or moderator-generated report on a submission

Constructors

ItemReport Text Word 

Instances

Instances details
Eq ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ItemReport :: Type -> Type #

FromJSON ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemReport = D1 ('MetaData "ItemReport" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "ItemReport" 'PrefixI 'True) (S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "count") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word)))

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

Constructors

Moderator

Adds "[M]"

Undistinguished

Removes an existing distinction when sent

Admin

Adds "[A]"

Special

User-specific distinction

Instances

Instances details
Eq Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep Distinction :: Type -> Type #

FromJSON Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

ToHttpApiData Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep Distinction = D1 ('MetaData "Distinction" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) ((C1 ('MetaCons "Moderator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Undistinguished" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Admin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Special" 'PrefixI 'False) (U1 :: Type -> Type)))

data Time Source #

Time range when fetching comments or submissions

Constructors

Hour 
Day 
Week 
Month 
Year 
AllTime 

Instances

Instances details
Eq Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Show Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Generic Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep Time :: Type -> Type #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

ToHttpApiData Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep Time = D1 ('MetaData "Time" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" '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))))

data ItemType Source #

Type of comments, for filtering in Listings

Constructors

Comments 
Submissions 

Instances

Instances details
Eq ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ItemType :: Type -> Type #

Methods

from :: ItemType -> Rep ItemType x #

to :: Rep ItemType x -> ItemType #

ToHttpApiData ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemType = D1 ('MetaData "ItemType" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "Comments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Submissions" 'PrefixI 'False) (U1 :: Type -> Type))

data UploadURL 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

Instances details
Eq UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep UploadURL :: Type -> Type #

ToJSON UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

FromJSON UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

ToHttpApiData UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep UploadURL = D1 ('MetaData "UploadURL" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'True) (C1 ('MetaCons "UploadURL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URL)))

type Body = Text Source #

Type synonym for bodies of submissions, comments, messages, etc...

type Title = Text Source #

Type synonym for titles of submissions, etc...

type URL = Text Source #

Type synonym for URLs

type Subject = Text Source #

Type synonym for subjects of messages, etc...

type RGBText = Text Source #

Type synonym RGB color strings

type Name = Text Source #

Type synonym for names of items

type Domain = Text Source #

Type synonym for domains

type Modifier = [Char] -> [Char] Source #

Type synonym for fieldLabelModifiers in FromJSON instances

Exceptions

data ClientException Source #

Exceptions generated within the Reddit API client

Instances

Instances details
Eq ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ClientException :: Type -> Type #

Exception ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

data APIException Source #

Exceptions returned from API endpoints

Constructors

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

UserIsBanned BannedUser

Thrown when attempting to get account information on a banned user

WebsocketError Text SomeException

Thrown when exceptions occur during websocket handling

UploadFailed

When an error occurs uploading media to Reddit's servers

Instances

Instances details
Show APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep APIException :: Type -> Type #

FromJSON APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Exception APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep APIException = D1 ('MetaData "APIException" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (((C1 ('MetaCons "ErrorWithStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StatusMessage)) :+: C1 ('MetaCons "ErrorWithMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ErrorMessage))) :+: (C1 ('MetaCons "InvalidCredentials" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OAauthError)) :+: C1 ('MetaCons "InvalidPOST" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 POSTError)))) :+: ((C1 ('MetaCons "JSONParseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "Redirected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Request)))) :+: (C1 ('MetaCons "UserIsBanned" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BannedUser)) :+: (C1 ('MetaCons "WebsocketError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SomeException)) :+: C1 ('MetaCons "UploadFailed" 'PrefixI 'False) (U1 :: Type -> Type)))))

data OAauthError Source #

An error which occurs when attempting to authenticate via OAuth

Constructors

OAauthError Text (Maybe Text) 

Instances

Instances details
Eq OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep OAauthError :: Type -> Type #

FromJSON OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep OAauthError = D1 ('MetaData "OAauthError" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "OAauthError" 'PrefixI 'True) (S1 ('MetaSel ('Just "errorType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))))

data ErrorMessage Source #

A specific error message

Instances

Instances details
Eq ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ErrorMessage :: Type -> Type #

FromJSON ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ErrorMessage = D1 ('MetaData "ErrorMessage" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (((C1 ('MetaCons "EmptyError" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OtherErrorMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Value])) :+: C1 ('MetaCons "Ratelimited" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))) :+: ((C1 ('MetaCons "CommentDeleted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BadSRName" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SubredditNotExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SubredditRequired" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "AlreadySubmitted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoURL" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NoName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoText" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TooShort" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BadCaptcha" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UserRequired" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InsufficientCoins" 'PrefixI 'False) (U1 :: Type -> Type)))))

data StatusMessage Source #

Details about a non-200 HTTP response

Instances

Instances details
Eq StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep StatusMessage :: Type -> Type #

FromJSON StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep StatusMessage = D1 ('MetaData "StatusMessage" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "StatusMessage" 'PrefixI 'True) (S1 ('MetaSel ('Just "statusCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StatusCode) :*: S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))

type StatusCode = Int Source #

Type synonym for status codes in responses

data POSTError Source #

Details about a non-200 response when sending a POST request

Constructors

POSTError [Text] Text Text Text 

Instances

Instances details
Eq POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep POSTError :: Type -> Type #

FromJSON POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep POSTError = D1 ('MetaData "POSTError" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" '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))))

data BannedUser Source #

Information about a banned user

Instances

Instances details
Eq BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep BannedUser :: Type -> Type #

FromJSON BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep BannedUser = D1 ('MetaData "BannedUser" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "BannedUser" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Username) :*: (S1 ('MetaSel ('Just "totalKarma") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "isSuspended") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

Auth

data ClientState Source #

Stateful data that may be updated over the course of a Client lifetime

Instances

Instances details
Eq ClientState Source # 
Instance details

Defined in Network.Reddit.Types

Show ClientState Source # 
Instance details

Defined in Network.Reddit.Types

Generic ClientState Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep ClientState :: Type -> Type #

type Rep ClientState Source # 
Instance details

Defined in Network.Reddit.Types

type Rep ClientState = D1 ('MetaData "ClientState" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "ClientState" 'PrefixI 'True) (S1 ('MetaSel ('Just "accessToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccessToken) :*: (S1 ('MetaSel ('Just "tokenObtained") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 POSIXTime) :*: S1 ('MetaSel ('Just "limits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RateLimits)))))

data AppType Source #

The three forms of application that may use the Reddit API, each having different API access patterns

Constructors

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

Instances details
Eq AppType Source # 
Instance details

Defined in Network.Reddit.Types

Methods

(==) :: AppType -> AppType -> Bool #

(/=) :: AppType -> AppType -> Bool #

Show AppType Source # 
Instance details

Defined in Network.Reddit.Types

Generic AppType Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep AppType :: Type -> Type #

Methods

from :: AppType -> Rep AppType x #

to :: Rep AppType x -> AppType #

ToForm AppType Source # 
Instance details

Defined in Network.Reddit.Types

Methods

toForm :: AppType -> Form #

type Rep AppType Source # 
Instance details

Defined in Network.Reddit.Types

data AuthConfig Source #

A configuration

Instances

Instances details
Eq AuthConfig Source # 
Instance details

Defined in Network.Reddit.Types

Show AuthConfig Source # 
Instance details

Defined in Network.Reddit.Types

Generic AuthConfig Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep AuthConfig :: Type -> Type #

type Rep AuthConfig Source # 
Instance details

Defined in Network.Reddit.Types

type Rep AuthConfig = D1 ('MetaData "AuthConfig" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "AuthConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "clientID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ClientID) :*: (S1 ('MetaSel ('Just "appType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AppType) :*: S1 ('MetaSel ('Just "userAgent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UserAgent))))

data UserAgent Source #

A unique user agent to identify your application; Reddit applies rate-limiting to common agents, and actively bans misleading ones

Constructors

UserAgent Text Text Text Text 

Instances

Instances details
Eq UserAgent Source # 
Instance details

Defined in Network.Reddit.Types

Show UserAgent Source # 
Instance details

Defined in Network.Reddit.Types

Generic UserAgent Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep UserAgent :: Type -> Type #

type Rep UserAgent Source # 
Instance details

Defined in Network.Reddit.Types

type Rep UserAgent = D1 ('MetaData "UserAgent" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" '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

Instances details
Eq AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

Show AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

Generic AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep AccessToken :: Type -> Type #

FromJSON AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

type Rep AccessToken Source # 
Instance details

Defined in Network.Reddit.Types

type Rep AccessToken = D1 ('MetaData "AccessToken" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "AccessToken" 'PrefixI 'True) ((S1 ('MetaSel ('Just "token") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Token) :*: S1 ('MetaSel ('Just "expiresIn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NominalDiffTime)) :*: (S1 ('MetaSel ('Just "scope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Scope]) :*: S1 ('MetaSel ('Just "refreshToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Token)))))

type Token = Text Source #

Type synonym for the text of a token

type Code = Text Source #

Type synonym for the text of codes returned from auth URLs, for WebApps and InstalledApps

data Scope Source #

Represents a specific Reddit functionality that must be explicitly requested

Instances

Instances details
Enum Scope Source # 
Instance details

Defined in Network.Reddit.Types

Eq Scope Source # 
Instance details

Defined in Network.Reddit.Types

Methods

(==) :: Scope -> Scope -> Bool #

(/=) :: Scope -> Scope -> Bool #

Ord Scope Source # 
Instance details

Defined in Network.Reddit.Types

Methods

compare :: Scope -> Scope -> Ordering #

(<) :: Scope -> Scope -> Bool #

(<=) :: Scope -> Scope -> Bool #

(>) :: Scope -> Scope -> Bool #

(>=) :: Scope -> Scope -> Bool #

max :: Scope -> Scope -> Scope #

min :: Scope -> Scope -> Scope #

Show Scope Source # 
Instance details

Defined in Network.Reddit.Types

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Generic Scope Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep Scope :: Type -> Type #

Methods

from :: Scope -> Rep Scope x #

to :: Rep Scope x -> Scope #

FromJSON Scope Source # 
Instance details

Defined in Network.Reddit.Types

ToHttpApiData Scope Source # 
Instance details

Defined in Network.Reddit.Types

type Rep Scope Source # 
Instance details

Defined in Network.Reddit.Types

type Rep Scope = D1 ('MetaData "Scope" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) ((((C1 ('MetaCons "Accounts" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Creddits" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Edit" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Flair" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "History" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Identity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiveManage" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ModConfig" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModContributors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModFlair" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ModLog" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModMail" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ModOthers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModPosts" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ModSelf" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModTraffic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModWiki" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MySubreddits" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PrivateMessages" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Read" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Report" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Save" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StructuredStyles" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Submit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Subscribe" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Vote" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WikiEdit" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WikiRead" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unlimited" 'PrefixI 'False) (U1 :: Type -> Type))))))

data PasswordFlow Source #

Simple user credentials for authenticating via ScriptApps

Note: These credentials will be kept in memory!

Constructors

PasswordFlow Text Text 

Instances

Instances details
Eq PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

Show PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

Generic PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep PasswordFlow :: Type -> Type #

ToForm PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

Methods

toForm :: PasswordFlow -> Form #

type Rep PasswordFlow Source # 
Instance details

Defined in Network.Reddit.Types

type Rep PasswordFlow = D1 ('MetaData "PasswordFlow" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "PasswordFlow" 'PrefixI 'True) (S1 ('MetaSel ('Just "username") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "password") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))

data CodeFlow Source #

Details for OAuth "code flow", for WebApps and InstalledApps

Constructors

CodeFlow URL Code 

Instances

Instances details
Eq CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

Show CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

Generic CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep CodeFlow :: Type -> Type #

Methods

from :: CodeFlow -> Rep CodeFlow x #

to :: Rep CodeFlow x -> CodeFlow #

ToForm CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

Methods

toForm :: CodeFlow -> Form #

type Rep CodeFlow Source # 
Instance details

Defined in Network.Reddit.Types

type Rep CodeFlow = D1 ('MetaData "CodeFlow" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" '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 ClientID = Text Source #

Type synonym for client IDs

type ClientSecret = Text Source #

Type synonym for client secrets

data TokenDuration Source #

The duration of the access token for WebApps and InstalledApps

Constructors

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

Instances details
Eq TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

Show TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

Generic TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

Associated Types

type Rep TokenDuration :: Type -> Type #

ToHttpApiData TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

type Rep TokenDuration Source # 
Instance details

Defined in Network.Reddit.Types

type Rep TokenDuration = D1 ('MetaData "TokenDuration" "Network.Reddit.Types" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "Temporary" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Permanent" 'PrefixI 'False) (U1 :: Type -> Type))

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