| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Contents
Description
This module should be most of what you need to operate the library.
It exports functionality for running built RedditT actions, as well
as re-exporting a few helpful types from around the library. Not every
type is exported, however, due to clashing record fields. It's recommended
to import modules from Reddit.Types.* qualified so that you can use all
the record fields without having to deal with ambiguous functions.
Synopsis
- runReddit :: MonadIO m => Text -> Text -> ClientParams -> RedditT m a -> m (Either (APIError RedditError) a)
- runRedditAnon :: MonadIO m => RedditT m a -> m (Either (APIError RedditError) a)
- runRedditWith :: MonadIO m => RedditOptions -> RedditT m a -> m (Either (APIError RedditError) a)
- runResumeRedditWith :: MonadIO m => RedditOptions -> RedditT m a -> m (Either (APIError RedditError, Maybe (RedditT m a)) a)
- interpretIO :: MonadIO m => RedditState -> RedditT m a -> m (Either (APIError RedditError, Maybe (RedditT m a)) a)
- data RedditOptions = RedditOptions {}
- defaultRedditOptions :: RedditOptions
- data LoginMethod
- data APIError a
- module Reddit.Actions
- module Reddit.Types
- module Reddit.Types.Error
- data ClientParams = ClientParams Text Text
- data RateLimitInfo = RateLimitInfo {}
- type ShouldRateLimit = Bool
- data RateLimits = RateLimits ShouldRateLimit (Maybe RateLimitInfo)
- newtype POSTWrapped a = POSTWrapped a
- data LoginDetails = LoginDetails Modhash CookieJar
- newtype Modhash = Modhash Text
- newtype RedditT m a = RedditT (FreeT (RedditF m) m a)
- data RedditF m a where
- FailWith :: APIError RedditError -> RedditF m a
- Nest :: RedditT m b -> (Either (APIError RedditError) b -> a) -> RedditF m a
- NestResuming :: RedditT m b -> (Either (APIError RedditError, Maybe (RedditT m b)) b -> a) -> RedditF m a
- ReceiveRoute :: Receivable b => Route -> (b -> a) -> RedditF m a
- RunRoute :: FromJSON b => Route -> (b -> a) -> RedditF m a
- WithBaseURL :: Text -> RedditT m b -> (b -> a) -> RedditF m a
- WithHeaders :: ([Header] -> [Header]) -> RedditT m b -> (b -> a) -> RedditF m a
- type Reddit a = RedditT IO a
- runRoute :: (FromJSON a, Monad m) => Route -> RedditT m a
- receiveRoute :: (Receivable a, Monad m) => Route -> RedditT m a
- nest :: Monad m => RedditT m a -> RedditT m (Either (APIError RedditError) a)
- withBaseURL :: Monad m => Text -> RedditT m a -> RedditT m a
- withHeaders :: Monad m => ([Header] -> [Header]) -> RedditT m a -> RedditT m a
- failWith :: Monad m => APIError RedditError -> RedditT m a
- headersToRateLimitInfo :: ResponseHeaders -> UTCTime -> Maybe RateLimitInfo
- mkClientParamsHeader :: ClientParams -> (HeaderName, ByteString)
- addAPIType :: Route -> Route
- mainBaseURL :: Text
- loginBaseURL :: Text
Documentation
runReddit :: MonadIO m => Text -> Text -> ClientParams -> RedditT m a -> m (Either (APIError RedditError) a) Source #
Run a Reddit action (or a RedditT transformer action). This uses the default logged-in settings
for RedditOptions: rate limiting enabled, default manager, login via username and password, and
the default user-agent. You should change the user agent if you're making anything more complex than
a basic script, since Reddit's API policy says that you should have a uniquely identifiable user agent.
runRedditAnon :: MonadIO m => RedditT m a -> m (Either (APIError RedditError) a) Source #
Run a Reddit action (or a RedditT transformer action). This uses the default logged-out settings, so
you won't be able to do anything that requires authentication (like checking messages or making a post).
At the moment, authentication isn't statically checked, so it'll return a runtime error if you try to do
anything you don't have permissions for.
runRedditWith :: MonadIO m => RedditOptions -> RedditT m a -> m (Either (APIError RedditError) a) Source #
runResumeRedditWith :: MonadIO m => RedditOptions -> RedditT m a -> m (Either (APIError RedditError, Maybe (RedditT m a)) a) Source #
interpretIO :: MonadIO m => RedditState -> RedditT m a -> m (Either (APIError RedditError, Maybe (RedditT m a)) a) Source #
data RedditOptions Source #
Options for how we should run the Reddit action.
rateLimitingEnabled:Trueif the connection should be automatically rate-limited and should pause when we hit the limit,Falseotherwise. Default isTrue.connectionManager:if the connection should use theJustxManagerx,Nothingif we should create a new one for the connection. Default isNothing.loginMethod: The method we should use for authentication, described inLoginMethod. Default isAnonymous.customUserAgent:if the connection should use the user agentJust"string""string",if it should use the default agent. Default isNothingNothing.
Constructors
| RedditOptions | |
Fields | |
Instances
| Default RedditOptions Source # | |
Defined in Reddit Methods def :: RedditOptions # | |
defaultRedditOptions :: RedditOptions Source #
The default set of options
data LoginMethod Source #
Should we log in to Reddit? If so, should we use a stored set of credentials or get a new fresh set?
Constructors
| Anonymous | Don't login, instead use an anonymous account |
| Credentials Text Text ClientParams | Login using the specified username and password |
| StoredDetails LoginDetails | Login using a stored set of credentials. Usually the best way to get
these is to do |
Instances
| Show LoginMethod Source # | |
Defined in Reddit Methods showsPrec :: Int -> LoginMethod -> ShowS # show :: LoginMethod -> String # showList :: [LoginMethod] -> ShowS # | |
| Default LoginMethod Source # | |
Defined in Reddit Methods def :: LoginMethod # | |
Re-exports
Error type for the API, where a is the type that should be returned when
something goes wrong on the other end - i.e. any error that isn't directly related
to this library.
Constructors
| APIError a | A type that represents any error that happens on the API end.
Define your own custom type with a |
| HTTPError HttpException | Something went wrong when we tried to do a HTTP operation. |
| InvalidURLError | You're trying to create an invalid URL somewhere - check your
|
| ParseError String | Failed when parsing the response, and it wasn't an error on their end. |
| EmptyError | Empty error to serve as a zero element for Monoid. |
module Reddit.Actions
module Reddit.Types
module Reddit.Types.Error
data ClientParams Source #
Constructors
| ClientParams Text Text |
Instances
| Eq ClientParams Source # | |
Defined in Reddit.Types.Reddit | |
| Ord ClientParams Source # | |
Defined in Reddit.Types.Reddit Methods compare :: ClientParams -> ClientParams -> Ordering # (<) :: ClientParams -> ClientParams -> Bool # (<=) :: ClientParams -> ClientParams -> Bool # (>) :: ClientParams -> ClientParams -> Bool # (>=) :: ClientParams -> ClientParams -> Bool # max :: ClientParams -> ClientParams -> ClientParams # min :: ClientParams -> ClientParams -> ClientParams # | |
| Read ClientParams Source # | |
Defined in Reddit.Types.Reddit Methods readsPrec :: Int -> ReadS ClientParams # readList :: ReadS [ClientParams] # | |
| Show ClientParams Source # | |
Defined in Reddit.Types.Reddit Methods showsPrec :: Int -> ClientParams -> ShowS # show :: ClientParams -> String # showList :: [ClientParams] -> ShowS # | |
data RateLimitInfo Source #
Instances
| Eq RateLimitInfo Source # | |
Defined in Reddit.Types.Reddit Methods (==) :: RateLimitInfo -> RateLimitInfo -> Bool # (/=) :: RateLimitInfo -> RateLimitInfo -> Bool # | |
| Read RateLimitInfo Source # | |
Defined in Reddit.Types.Reddit Methods readsPrec :: Int -> ReadS RateLimitInfo # readList :: ReadS [RateLimitInfo] # | |
| Show RateLimitInfo Source # | |
Defined in Reddit.Types.Reddit Methods showsPrec :: Int -> RateLimitInfo -> ShowS # show :: RateLimitInfo -> String # showList :: [RateLimitInfo] -> ShowS # | |
type ShouldRateLimit = Bool Source #
data RateLimits Source #
Constructors
| RateLimits ShouldRateLimit (Maybe RateLimitInfo) |
Instances
| Eq RateLimits Source # | |
Defined in Reddit.Types.Reddit | |
| Read RateLimits Source # | |
Defined in Reddit.Types.Reddit Methods readsPrec :: Int -> ReadS RateLimits # readList :: ReadS [RateLimits] # readPrec :: ReadPrec RateLimits # readListPrec :: ReadPrec [RateLimits] # | |
| Show RateLimits Source # | |
Defined in Reddit.Types.Reddit Methods showsPrec :: Int -> RateLimits -> ShowS # show :: RateLimits -> String # showList :: [RateLimits] -> ShowS # | |
newtype POSTWrapped a Source #
Constructors
| POSTWrapped a |
Instances
data LoginDetails Source #
Constructors
| LoginDetails Modhash CookieJar |
Instances
| Show LoginDetails Source # | |
Defined in Reddit.Types.Reddit Methods showsPrec :: Int -> LoginDetails -> ShowS # show :: LoginDetails -> String # showList :: [LoginDetails] -> ShowS # | |
| Receivable LoginDetails Source # | |
Defined in Reddit.Types.Reddit Methods receive :: ErrorReceivable e => Response ByteString -> Either (APIError e) LoginDetails # | |
data RedditF m a where Source #
Constructors
| FailWith :: APIError RedditError -> RedditF m a | |
| Nest :: RedditT m b -> (Either (APIError RedditError) b -> a) -> RedditF m a | |
| NestResuming :: RedditT m b -> (Either (APIError RedditError, Maybe (RedditT m b)) b -> a) -> RedditF m a | |
| ReceiveRoute :: Receivable b => Route -> (b -> a) -> RedditF m a | |
| RunRoute :: FromJSON b => Route -> (b -> a) -> RedditF m a | |
| WithBaseURL :: Text -> RedditT m b -> (b -> a) -> RedditF m a | |
| WithHeaders :: ([Header] -> [Header]) -> RedditT m b -> (b -> a) -> RedditF m a |
receiveRoute :: (Receivable a, Monad m) => Route -> RedditT m a Source #
addAPIType :: Route -> Route Source #
mainBaseURL :: Text Source #
loginBaseURL :: Text Source #