| Copyright | (c) 2021 Rory Tyler Hayford |
|---|---|
| License | BSD-3-Clause |
| Maintainer | rory.hayford@protonmail.com |
| Stability | experimental |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Network.Reddit.Types
Contents
Description
Synopsis
- data RedditT m a
- runRedditT :: Client -> RedditT m a -> m a
- type MonadReddit m = (MonadUnliftIO m, MonadThrow m, MonadCatch m, MonadReader Client m)
- data UserAgent = UserAgent {}
- type ClientSite = Text
- data Client = Client {}
- data ClientState = ClientState {}
- readClientState :: MonadReddit m => Lens' ClientState a -> m a
- data WithData
- data RateLimits = RateLimits {}
- readRateLimits :: POSIXTime -> ResponseHeaders -> Maybe RateLimits
- data AppType
- data AuthConfig = AuthConfig {}
- data AccessToken = AccessToken {
- token :: Token
- expiresIn :: NominalDiffTime
- scope :: [Scope]
- refreshToken :: Maybe Token
- type Token = Text
- type Code = Text
- data Scope
- data PasswordFlow = PasswordFlow {}
- data CodeFlow = CodeFlow {
- redirectURI :: URL
- code :: Code
- type ClientID = Text
- type ClientSecret = Text
- data TokenDuration
- data TokenManager = TokenManager {
- loadToken :: forall m. (MonadIO m, MonadThrow m) => m Token
- putToken :: forall m. (MonadIO m, MonadThrow m) => Maybe Token -> m ()
- data APIAction a = APIAction {
- method :: Method
- pathSegments :: [PathSegment]
- requestData :: WithData
- needsAuth :: Bool
- followRedirects :: Bool
- rawJSON :: Bool
- checkResponse :: Request -> Response BodyReader -> IO ()
- data Method
- type PathSegment = Text
- module Network.Reddit.Types.Internal
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 # | |
type MonadReddit m = (MonadUnliftIO m, MonadThrow m, MonadCatch m, MonadReader Client m) Source #
Synonym for constraints that RedditT actions must satisfy
A unique user agent to identify your application; Reddit applies rate-limiting to common agents, and actively bans misleading ones
Constructors
| UserAgent | |
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.0.1-76ROQ5tOAm3CpLSaFw8ccb" '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)))) | |
type ClientSite = Text Source #
A client site corresponds to a field in your auth configuration ini file
A client facilitating access to Reddit's API
Constructors
| Client | |
Fields | |
Instances
| Generic Client Source # | |
| HasHttpManager Client Source # | |
Defined in Network.Reddit.Types Methods 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.0.1-76ROQ5tOAm3CpLSaFw8ccb" '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 ClientState Source #
Stateful data that may be updated over the course of a Client lifetime
Constructors
| ClientState | |
Fields
| |
Instances
| Eq ClientState Source # | |
Defined in Network.Reddit.Types | |
| Show ClientState Source # | |
Defined in Network.Reddit.Types Methods showsPrec :: Int -> ClientState -> ShowS # show :: ClientState -> String # showList :: [ClientState] -> ShowS # | |
| Generic ClientState Source # | |
Defined in Network.Reddit.Types Associated Types type Rep ClientState :: Type -> Type # | |
| type Rep ClientState Source # | |
Defined in Network.Reddit.Types type Rep ClientState = D1 ('MetaData "ClientState" "Network.Reddit.Types" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" '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))))) | |
readClientState :: MonadReddit m => Lens' ClientState a -> m a Source #
For conveniently reading some field from the IORef ClientState inside
a Client
Data, either as JSON or URL-encoded form, to be attached to requests
Instances
| Show WithData Source # | |
| Generic WithData Source # | |
| type Rep WithData Source # | |
Defined in Network.Reddit.Types type Rep WithData = D1 ('MetaData "WithData" "Network.Reddit.Types" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) ((C1 ('MetaCons "WithJSON" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value)) :+: C1 ('MetaCons "WithForm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Form))) :+: (C1 ('MetaCons "WithMultipart" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Part])) :+: C1 ('MetaCons "NoData" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data RateLimits Source #
Rate limit info
Constructors
| RateLimits | |
Fields
| |
Instances
readRateLimits :: POSIXTime -> ResponseHeaders -> Maybe RateLimits Source #
Extract rate limit info from response headers. This should only be called after making a request
Auth
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
data AuthConfig Source #
A configuration
Constructors
| AuthConfig | |
Instances
| Eq AuthConfig Source # | |
Defined in Network.Reddit.Types | |
| Show AuthConfig Source # | |
Defined in Network.Reddit.Types Methods showsPrec :: Int -> AuthConfig -> ShowS # show :: AuthConfig -> String # showList :: [AuthConfig] -> ShowS # | |
| Generic AuthConfig Source # | |
Defined in Network.Reddit.Types Associated Types type Rep AuthConfig :: Type -> Type # | |
| type Rep AuthConfig Source # | |
Defined in Network.Reddit.Types type Rep AuthConfig = D1 ('MetaData "AuthConfig" "Network.Reddit.Types" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" '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 AccessToken Source #
Token received after authentication
Constructors
| AccessToken | |
Fields
| |
Instances
Type synonym for the text of codes returned from auth URLs, for WebApps
and InstalledApps
Represents a specific Reddit functionality that must be explicitly requested
Constructors
| 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 ScriptApps
Note: These credentials will be kept in memory!
Constructors
| PasswordFlow | |
Instances
| Eq PasswordFlow Source # | |
Defined in Network.Reddit.Types | |
| Show PasswordFlow Source # | |
Defined in Network.Reddit.Types Methods showsPrec :: Int -> PasswordFlow -> ShowS # show :: PasswordFlow -> String # showList :: [PasswordFlow] -> ShowS # | |
| Generic PasswordFlow Source # | |
Defined in Network.Reddit.Types Associated Types type Rep PasswordFlow :: Type -> Type # | |
| ToForm PasswordFlow Source # | |
Defined in Network.Reddit.Types Methods toForm :: PasswordFlow -> Form # | |
| type Rep PasswordFlow Source # | |
Defined in Network.Reddit.Types type Rep PasswordFlow = D1 ('MetaData "PasswordFlow" "Network.Reddit.Types" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "PasswordFlow" 'PrefixI 'True) (S1 ('MetaSel ('Just "username") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "password") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) | |
Details for OAuth "code flow", for WebApps and InstalledApps
Constructors
| CodeFlow | |
Fields
| |
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.0.1-76ROQ5tOAm3CpLSaFw8ccb" '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 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
| Eq TokenDuration Source # | |
Defined in Network.Reddit.Types Methods (==) :: TokenDuration -> TokenDuration -> Bool # (/=) :: TokenDuration -> TokenDuration -> Bool # | |
| Show TokenDuration Source # | |
Defined in Network.Reddit.Types Methods showsPrec :: Int -> TokenDuration -> ShowS # show :: TokenDuration -> String # showList :: [TokenDuration] -> ShowS # | |
| Generic TokenDuration Source # | |
Defined in Network.Reddit.Types Associated Types type Rep TokenDuration :: Type -> Type # | |
| ToHttpApiData TokenDuration Source # | |
Defined in Network.Reddit.Types Methods toUrlPiece :: TokenDuration -> Text # toEncodedUrlPiece :: TokenDuration -> Builder # toHeader :: TokenDuration -> ByteString # toQueryParam :: TokenDuration -> Text # | |
| type Rep TokenDuration Source # | |
data TokenManager Source #
Monadic actions to load and save Tokens, specifically refresh tokens, when
creating new Clients for WebApps and InstalledApps
Constructors
| TokenManager | |
Fields
| |
Requests
An API request parameterized by the type it evaluates to when executed
Constructors
| APIAction | |
Fields
| |
Instances
HTTP method, excluding those not used in the Reddit API
Instances
| Eq Method Source # | |
| Show Method Source # | |
| Generic Method Source # | |
| type Rep Method Source # | |
Defined in Network.Reddit.Types type Rep Method = D1 ('MetaData "Method" "Network.Reddit.Types" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) ((C1 ('MetaCons "GET" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "POST" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DELETE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PUT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PATCH" 'PrefixI 'False) (U1 :: Type -> Type)))) | |
type PathSegment = Text Source #
Type synonym for a segment of a URL path