eventuo11y-batteries-0.2.1.1: Grab bag of eventuo11y-enriched functionality
CopyrightCopyright 2022 Shea Levy.
LicenseApache-2.0
Maintainershea@shealevy.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Observe.Event.Servant.Client

Description

This module offers a variant of servant-client's ClientM which instruments all requests with Events. It also has miscellaneous helpers for instrumenting servant-client functionality in other ways.

Synopsis

ClientM

newtype ClientM r a Source #

A monad to use in place of ClientM to get instrumentation on requests.

Instances

Instances details
MonadBaseControl IO (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Associated Types

type StM (ClientM r) a #

Methods

liftBaseWith :: (RunInBase (ClientM r) IO -> IO a) -> ClientM r a #

restoreM :: StM (ClientM r) a -> ClientM r a #

MonadError ClientError (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Methods

throwError :: ClientError -> ClientM r a #

catchError :: ClientM r a -> (ClientError -> ClientM r a) -> ClientM r a #

MonadBase IO (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Methods

liftBase :: IO α -> ClientM r α #

MonadIO (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Methods

liftIO :: IO a -> ClientM r a #

Applicative (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Methods

pure :: a -> ClientM r a #

(<*>) :: ClientM r (a -> b) -> ClientM r a -> ClientM r b #

liftA2 :: (a -> b -> c) -> ClientM r a -> ClientM r b -> ClientM r c #

(*>) :: ClientM r a -> ClientM r b -> ClientM r b #

(<*) :: ClientM r a -> ClientM r b -> ClientM r a #

Functor (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Methods

fmap :: (a -> b) -> ClientM r a -> ClientM r b #

(<$) :: a -> ClientM r b -> ClientM r a #

Monad (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Methods

(>>=) :: ClientM r a -> (a -> ClientM r b) -> ClientM r b #

(>>) :: ClientM r a -> ClientM r b -> ClientM r b #

return :: a -> ClientM r a #

MonadCatch (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Methods

catch :: Exception e => ClientM r a -> (e -> ClientM r a) -> ClientM r a #

MonadThrow (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Methods

throwM :: Exception e => e -> ClientM r a #

Alt (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Methods

(<!>) :: ClientM r a -> ClientM r a -> ClientM r a #

some :: Applicative (ClientM r) => ClientM r a -> ClientM r [a] #

many :: Applicative (ClientM r) => ClientM r a -> ClientM r [a] #

RunClient (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Generic (ClientM r a) Source # 
Instance details

Defined in Observe.Event.Servant.Client

Associated Types

type Rep (ClientM r a) :: Type -> Type #

Methods

from :: ClientM r a -> Rep (ClientM r a) x #

to :: Rep (ClientM r a) x -> ClientM r a #

MonadReader (EventBackend ClientM r RunRequest) (ClientM r) Source # 
Instance details

Defined in Observe.Event.Servant.Client

type StM (ClientM r) a Source # 
Instance details

Defined in Observe.Event.Servant.Client

type StM (ClientM r) a = Either ClientError a
type Rep (ClientM r a) Source # 
Instance details

Defined in Observe.Event.Servant.Client

type Rep (ClientM r a) = D1 ('MetaData "ClientM" "Observe.Event.Servant.Client" "eventuo11y-batteries-0.2.1.1-5JeFyoLdR06As76hu7lWkg" 'True) (C1 ('MetaCons "ClientM" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ReaderT (EventBackend ClientM r RunRequest) ClientM a))))

Instrumentation

data RunRequest f where Source #

Selector for events in ClientM

runRequestJSON :: RenderSelectorJSON RunRequest Source #

Render a RunRequest and the fields of its selected events as JSON

data RunRequestField Source #

A field for RunRequest events.

Miscellaneous instrumentation

clientErrorJSON :: RenderFieldJSON ClientError Source #

Render a ClientError, considered as an Event field, as JSON

responseJSON :: Response -> Bool -> Value Source #

Render a Response as JSON, optionally forcing rendering the body even if it's large.