| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.HTTP.ApiMaker.Class
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 -> Option 'Https
- process :: (MonadHttp 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 HttpException 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 HttpException (ReaderT (Config cfg) IO) 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.
Methods
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 -> Option 'Https Source #
process :: (MonadHttp 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.
Constructors
| Config | |
Fields
| |
class SessionState st where Source #
Session state contract.
Methods
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.
Constructors
| Session | |
Fields | |
Instances
| Show Session Source # | |
| SessionState Session Source # | Simple session state implemention. |
Defined in Network.HTTP.ApiMaker.SessionState | |
emptySession :: Session Source #
Empty session state.
Arguments
| :: MonadIO m | |
| => Config cfg | Config including |
| -> SafeReqM cfg a | Computation to run |
| -> m (Either HttpException a) |
Safely run the request monad.
askApiConfig :: SafeReqM cfg cfg Source #
newtype SafeReqM cfg a Source #
Safe request, e.g. all errors are caught and tured into exceptions.
Instances
| 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 Methods handleHttpException :: HttpException -> SafeReqM cfg a # getHttpConfig :: SafeReqM cfg HttpConfig # | |