Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class (HttpMethod (Method r), HttpBody (Body r), HttpResponse (Response r), HttpBodyAllowed (AllowsBody (Method r)) (ProvidesBody (Body r))) => Request cfg r where
- type Method r :: Type
- type Body r :: Type
- type Response r :: Type
- type Output r :: Type
- method :: cfg -> r -> Method r
- url :: cfg -> r -> Url 'Https
- body :: cfg -> r -> Body r
- response :: cfg -> r -> Proxy (Response r)
- option :: cfg -> r -> IO (Option 'Https)
- requestModifier :: cfg -> r -> Request -> IO Request
- process :: (MonadHttp m, MonadError SafeException m, SessionState st) => cfg -> r -> Response r -> StateT st m (Output r)
- data Config cfg = Config {
- httpConfig :: HttpConfig
- apiDefaultParameters :: [Option 'Https]
- apiConfig :: cfg
- class SessionState st where
- csrfToken :: Lens' st (Maybe ByteString)
- sessionData :: Lens' st (Maybe ByteString)
- cookieJarData :: Lens' st (Maybe CookieJar)
- data Session = Session {}
- emptySession :: Session
- runSafeReqM :: MonadIO m => Config cfg -> SafeReqM cfg a -> m (Either SafeException a)
- askConfig :: SafeReqM cfg (Config cfg)
- askApiConfig :: SafeReqM cfg cfg
- type SafeReqSt sessionState cfg a = StateT sessionState (SafeReqM cfg) a
- type SafeReq cfg a = SafeReqSt Session cfg a
- newtype SafeReqM cfg a = SafeReqM (ExceptT SafeException (ReaderT (Config cfg) IO) a)
- data SafeException
- = ReqException HttpException
- | forall e.(Typeable e, Exception e) => SafeUserException e
- throwUserException :: (MonadError SafeException m, Exception e) => e -> m a
Documentation
class (HttpMethod (Method r), HttpBody (Body r), HttpResponse (Response r), HttpBodyAllowed (AllowsBody (Method r)) (ProvidesBody (Body r))) => Request cfg r where Source #
Class definition for a Request
. Every request should implement this, the rest is then handled by the library. See mkReq
to create a request, the functions
mkReqM
and runRequests
to build a SafeReqM
monad that shares the same state, session and configuration, and finally
runReqM
, runSessReqM
, runReqWithParamsM
and runSessReqWithParamsM
to run the monad.
method :: cfg -> r -> Method r Source #
url :: cfg -> r -> Url 'Https Source #
body :: cfg -> r -> Body r Source #
response :: cfg -> r -> Proxy (Response r) Source #
option :: cfg -> r -> IO (Option 'Https) Source #
requestModifier :: cfg -> r -> Request -> IO Request Source #
process :: (MonadHttp m, MonadError SafeException m, SessionState st) => cfg -> r -> Response r -> StateT st m (Output r) Source #
Configuration that is passed from request to request to hold the session and default https header options. It also holds a user defined configuration.
Config | |
|
class SessionState st where Source #
Session state contract.
csrfToken :: Lens' st (Maybe ByteString) Source #
sessionData :: Lens' st (Maybe ByteString) Source #
Instances
SessionState Session Source # | Simple session state implemention. |
Defined in Network.HTTP.ApiMaker.SessionState |
Simple session state. This probably is sufficient for the day-to-day use.
Instances
Show Session Source # | |
SessionState Session Source # | Simple session state implemention. |
Defined in Network.HTTP.ApiMaker.SessionState |
emptySession :: Session Source #
Empty session state.
:: MonadIO m | |
=> Config cfg | Config including |
-> SafeReqM cfg a | Computation to run |
-> m (Either SafeException a) |
Safely run the request monad.
askApiConfig :: SafeReqM cfg cfg Source #
type SafeReqSt sessionState cfg a = StateT sessionState (SafeReqM cfg) a Source #
Safe request monad with customized session state sessionState
, Config cfg
and result a
.
type SafeReq cfg a = SafeReqSt Session cfg a Source #
Safe request monad with predetermined Session
, config cfg
and result a
.
newtype SafeReqM cfg a Source #
Safe request, e.g. all errors are caught and tured into exceptions.
Instances
MonadError SafeException (SafeReqM cfg) Source # | |
Defined in Network.HTTP.ApiMaker.Class throwError :: SafeException -> SafeReqM cfg a # catchError :: SafeReqM cfg a -> (SafeException -> SafeReqM cfg a) -> SafeReqM cfg a # | |
MonadBase IO (SafeReqM cfg) Source # | |
Defined in Network.HTTP.ApiMaker.Class | |
Monad (SafeReqM cfg) Source # | |
Functor (SafeReqM cfg) Source # | |
Applicative (SafeReqM cfg) Source # | |
Defined in Network.HTTP.ApiMaker.Class | |
MonadIO (SafeReqM cfg) Source # | |
Defined in Network.HTTP.ApiMaker.Class | |
MonadHttp (SafeReqM cfg) Source # | |
Defined in Network.HTTP.ApiMaker.Class handleHttpException :: HttpException -> SafeReqM cfg a # getHttpConfig :: SafeReqM cfg HttpConfig # |
data SafeException Source #
ReqException HttpException | |
forall e.(Typeable e, Exception e) => SafeUserException e |
Instances
Show SafeException Source # | |
Defined in Network.HTTP.ApiMaker.Class showsPrec :: Int -> SafeException -> ShowS # show :: SafeException -> String # showList :: [SafeException] -> ShowS # | |
Exception SafeException Source # | |
Defined in Network.HTTP.ApiMaker.Class | |
MonadError SafeException (SafeReqM cfg) Source # | |
Defined in Network.HTTP.ApiMaker.Class throwError :: SafeException -> SafeReqM cfg a # catchError :: SafeReqM cfg a -> (SafeException -> SafeReqM cfg a) -> SafeReqM cfg a # |
throwUserException :: (MonadError SafeException m, Exception e) => e -> m a Source #
Throw an Exception to the SafeReqM
Monad.