Copyright | (c) 2021 The closed eye of love |
---|---|
License | BSD-3-Clause |
Maintainer | Poscat <poscat@mail.poscat.moe>, berberman <berberman@yandex.com> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Web.Pixiv.Types.PixivT
Description
The core monad of this library. PixivT
maintains a pixiv login state,
and provides an environment to perform computations created by servant.
Synopsis
- newtype ClientT m a = ClientT {
- unClientT :: ReaderT ClientEnv (ExceptT ClientError m) a
- runClientT :: ClientEnv -> ClientT m a -> m (Either ClientError a)
- mkDefaultClientEnv :: Manager -> IO ClientEnv
- class (RunClient m, MonadIO m) => MonadPixiv m where
- takePixivState :: m PixivState
- putPixivState :: PixivState -> m ()
- readPixivState :: m PixivState
- data PixivState = PixivState {}
- newtype PixivT m a = PixivT {
- unPixivT :: ReaderT (MVar PixivState) (ClientT m) a
- liftC :: Monad m => ClientT m a -> PixivT m a
- runPixivT :: MonadIO m => Manager -> Credential -> PixivT m a -> m (Either ClientError a)
- runPixivT' :: MonadIO m => Credential -> PixivT m a -> m (Either ClientError a)
- data TokenState = TokenState {}
- computeTokenState :: Manager -> Credential -> UTCTime -> IO TokenState
- getAccessToken :: MonadPixiv m => m Token
- getAccessTokenWithAccpetLanguage :: MonadPixiv m => m (Token, Maybe Text)
ClientT monad transformer
Instances
runClientT :: ClientEnv -> ClientT m a -> m (Either ClientError a) Source #
Executes a computation in the client monad.
mkDefaultClientEnv :: Manager -> IO ClientEnv Source #
Given Manager
, creates a ClientEnv
using https://app-api.pixiv.net as base url.
MonadPixiv class
class (RunClient m, MonadIO m) => MonadPixiv m where Source #
The mtl-style class of pixiv monad.
Methods
takePixivState :: m PixivState Source #
Reads the stored PixivState
, when used in a multithreaded setting, this should block
all other thread from reading the PixivState
until putPixivState
is called.
putPixivState :: PixivState -> m () Source #
Writes a new PixivState
.
readPixivState :: m PixivState Source #
Reads the stored PixivState
, without blocking other threads which want to read this state.
Don't confuse with takePixivState
, please refer to readMVar
.
Instances
(MonadPixiv m, MonadTrans f, MonadIO (f m), RunClient (f m)) => MonadPixiv (f m) Source # | |
Defined in Web.Pixiv.Types.PixivT Methods takePixivState :: f m PixivState Source # putPixivState :: PixivState -> f m () Source # readPixivState :: f m PixivState Source # | |
MonadIO m => MonadPixiv (PixivT m) Source # | |
Defined in Web.Pixiv.Types.PixivT Methods takePixivState :: PixivT m PixivState Source # putPixivState :: PixivState -> PixivT m () Source # |
data PixivState Source #
State stored in MonadPixiv
.
Constructors
PixivState | |
Fields |
Instances
PixivT monad transformer
A thread safe implementation of MonadPixiv
.
Instances
runPixivT :: MonadIO m => Manager -> Credential -> PixivT m a -> m (Either ClientError a) Source #
runPixivT' :: MonadIO m => Credential -> PixivT m a -> m (Either ClientError a) Source #
Token
data TokenState Source #
Pixiv auth state.
Constructors
TokenState | |
Fields
|
Instances
Show TokenState Source # | |
Defined in Web.Pixiv.Types.PixivT Methods showsPrec :: Int -> TokenState -> ShowS # show :: TokenState -> String # showList :: [TokenState] -> ShowS # | |
Generic TokenState Source # | |
Defined in Web.Pixiv.Types.PixivT Associated Types type Rep TokenState :: Type -> Type # | |
type Rep TokenState Source # | |
Defined in Web.Pixiv.Types.PixivT type Rep TokenState = D1 ('MetaData "TokenState" "Web.Pixiv.Types.PixivT" "pixiv-0.1.1-EohU1eVO1gXLvKhzusySE3" 'False) (C1 ('MetaCons "TokenState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "accessToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token) :*: S1 ('MetaSel ('Just "refreshToken") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token)) :*: (S1 ('MetaSel ('Just "expirationTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "manager") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Manager)))) |
Arguments
:: Manager | |
-> Credential | Could be username with password or |
-> UTCTime | Current time. |
-> IO TokenState |
Computes the TokenState
.
This function calls auth'
to perform authentication.
Utilities
getAccessToken :: MonadPixiv m => m Token Source #
Retrieves the accessToken
from pixiv monad.
If the token is overdue, it will call computeTokenState
to refresh.
getAccessTokenWithAccpetLanguage :: MonadPixiv m => m (Token, Maybe Text) Source #
Retrieves the accessToken
and acceptLanguage
in one go.