Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Client a
- class (MonadIO m, MonadThrow m) => MonadClient m where
- liftClient :: Client a -> m a
- localState :: (ClientState -> ClientState) -> m a -> m a
- data ClientState
- data DebugInfo = DebugInfo {
- policyInfo :: String
- jobInfo :: [InetAddr]
- hostInfo :: [Host]
- controlInfo :: (Host, ControlState)
- data ControlState
- runClient :: MonadIO m => ClientState -> Client a -> m a
- init :: MonadIO m => Settings -> m ClientState
- shutdown :: MonadIO m => ClientState -> m ()
- request :: (MonadClient m, Tuple a, Tuple b) => Request k a b -> m (HostResponse k a b)
- requestN :: (Tuple b, Tuple a) => Word -> Request k a b -> ClientState -> Client (HostResponse k a b)
- request1 :: (Tuple a, Tuple b) => Host -> Request k a b -> ClientState -> Client (HostResponse k a b)
- execute :: (Tuple b, Tuple a) => PrepQuery k a b -> QueryParams a -> Client (HostResponse k a b)
- executeWithPrepare :: (Tuple b, Tuple a) => Maybe Host -> Request k a b -> Client (HostResponse k a b)
- prepare :: (Tuple b, Tuple a) => Maybe PrepareStrategy -> QueryString k a b -> Client (Host, QueryId k a b)
- retry :: MonadClient m => RetrySettings -> m a -> m a
- once :: MonadClient m => m a -> m a
- debugInfo :: MonadClient m => m DebugInfo
- preparedQueries :: Client PreparedQueries
- withPrepareStrategy :: MonadClient m => PrepareStrategy -> m a -> m a
- getResult :: MonadThrow m => HostResponse k a b -> m (Result k a b)
- unexpected :: MonadThrow m => HostResponse k a b -> m c
- defQueryParams :: Consistency -> a -> QueryParams a
Documentation
The Client monad.
A simple reader monad on IO
around some internal state. Prior to executing
this monad via runClient
, its state must be initialised through
init
and after finishing operation it should be
terminated with shutdown
.
To lift Client
actions into another monad, see MonadClient
.
Instances
Monad Client Source # | |
Functor Client Source # | |
Applicative Client Source # | |
MonadIO Client Source # | |
Defined in Database.CQL.IO.Client | |
MonadThrow Client Source # | |
Defined in Database.CQL.IO.Client | |
MonadCatch Client Source # | |
MonadMask Client Source # | |
MonadUnliftIO Client Source # | |
Defined in Database.CQL.IO.Client | |
MonadClient Client Source # | |
Defined in Database.CQL.IO.Client liftClient :: Client a -> Client a Source # localState :: (ClientState -> ClientState) -> Client a -> Client a Source # | |
MonadReader ClientState Client Source # | |
Defined in Database.CQL.IO.Client ask :: Client ClientState # local :: (ClientState -> ClientState) -> Client a -> Client a # reader :: (ClientState -> a) -> Client a # |
class (MonadIO m, MonadThrow m) => MonadClient m where Source #
Monads in which Client
actions may be embedded.
liftClient :: Client a -> m a Source #
Lift a computation from the Client
monad.
localState :: (ClientState -> ClientState) -> m a -> m a Source #
Execute an action with a modified ClientState
.
Instances
data ClientState Source #
Opaque client state/environment.
Instances
MonadReader ClientState Client Source # | |
Defined in Database.CQL.IO.Client ask :: Client ClientState # local :: (ClientState -> ClientState) -> Client a -> Client a # reader :: (ClientState -> a) -> Client a # |
DebugInfo | |
|
data ControlState Source #
Instances
Eq ControlState Source # | |
Defined in Database.CQL.IO.Client (==) :: ControlState -> ControlState -> Bool # (/=) :: ControlState -> ControlState -> Bool # | |
Ord ControlState Source # | |
Defined in Database.CQL.IO.Client compare :: ControlState -> ControlState -> Ordering # (<) :: ControlState -> ControlState -> Bool # (<=) :: ControlState -> ControlState -> Bool # (>) :: ControlState -> ControlState -> Bool # (>=) :: ControlState -> ControlState -> Bool # max :: ControlState -> ControlState -> ControlState # min :: ControlState -> ControlState -> ControlState # | |
Show ControlState Source # | |
Defined in Database.CQL.IO.Client showsPrec :: Int -> ControlState -> ShowS # show :: ControlState -> String # showList :: [ControlState] -> ShowS # |
shutdown :: MonadIO m => ClientState -> m () Source #
Terminate client state, i.e. end all running background checks and shutdown all connection pools. Once this is entered, the client will eventually be shut down, though an asynchronous exception can interrupt the wait for that to occur.
request :: (MonadClient m, Tuple a, Tuple b) => Request k a b -> m (HostResponse k a b) Source #
Send a Request
to the server and return a Response
.
This function will first ask the clients load-balancing Policy
for
some host and use its connection pool to acquire a connection for
request transmission.
If all available hosts are busy (i.e. their connection pools are fully utilised), the function will block until a connection becomes available or the maximum wait-queue length has been reached.
The request is retried according to the configured RetrySettings
.
requestN :: (Tuple b, Tuple a) => Word -> Request k a b -> ClientState -> Client (HostResponse k a b) Source #
Send a request to a host chosen by the configured host policy.
Tries up to max(1,n)
hosts. If no host can execute the request,
a HostError
is thrown. Specifically:
- If no host is available from the
Policy
,NoHostAvailable
is thrown. - If no host can execute the request, e.g. because all streams
on all connections are occupied,
HostsBusy
is thrown.
request1 :: (Tuple a, Tuple b) => Host -> Request k a b -> ClientState -> Client (HostResponse k a b) Source #
execute :: (Tuple b, Tuple a) => PrepQuery k a b -> QueryParams a -> Client (HostResponse k a b) Source #
Execute a prepared query (transparently re-preparing if necessary).
executeWithPrepare :: (Tuple b, Tuple a) => Maybe Host -> Request k a b -> Client (HostResponse k a b) Source #
Execute the given request. If an Unprepared
error is returned, this
function will automatically try to re-prepare the query and re-execute
the original request using the same host which was used for re-preparation.
prepare :: (Tuple b, Tuple a) => Maybe PrepareStrategy -> QueryString k a b -> Client (Host, QueryId k a b) Source #
Prepare the given query according to the given PrepareStrategy
,
returning the resulting QueryId
and Host
which was used for
preparation.
retry :: MonadClient m => RetrySettings -> m a -> m a Source #
Use given RetrySettings
during execution of some client action.
once :: MonadClient m => m a -> m a Source #
Execute a client action once, without retries, i.e.
once action = retry noRetry action
.
Primarily for use in applications where global RetrySettings
are configured and need to be selectively disabled for individual
queries.
debugInfo :: MonadClient m => m DebugInfo Source #
withPrepareStrategy :: MonadClient m => PrepareStrategy -> m a -> m a Source #
Change the default PrepareStrategy
for the given client action.
getResult :: MonadThrow m => HostResponse k a b -> m (Result k a b) Source #
Get the Result
out of a HostResponse
. If the response is an RsError
,
a ResponseError
is thrown. If the response is neither
RsResult
nor RsError
, an UnexpectedResponse
is thrown.
unexpected :: MonadThrow m => HostResponse k a b -> m c Source #
defQueryParams :: Consistency -> a -> QueryParams a Source #
Construct default QueryParams
for the given consistency
and bound values. In particular, no page size, paging state
or serial consistency will be set.