cql-io-1.1.1: Cassandra CQL client.

Safe HaskellNone
LanguageHaskell2010

Database.CQL.IO.Client

Synopsis

Documentation

data Client a Source #

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 # 
Instance details

Defined in Database.CQL.IO.Client

Methods

(>>=) :: Client a -> (a -> Client b) -> Client b #

(>>) :: Client a -> Client b -> Client b #

return :: a -> Client a #

fail :: String -> Client a #

Functor Client Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

fmap :: (a -> b) -> Client a -> Client b #

(<$) :: a -> Client b -> Client a #

Applicative Client Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

pure :: a -> Client a #

(<*>) :: Client (a -> b) -> Client a -> Client b #

liftA2 :: (a -> b -> c) -> Client a -> Client b -> Client c #

(*>) :: Client a -> Client b -> Client b #

(<*) :: Client a -> Client b -> Client a #

MonadIO Client Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

liftIO :: IO a -> Client a #

MonadThrow Client Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

throwM :: Exception e => e -> Client a #

MonadCatch Client Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

catch :: Exception e => Client a -> (e -> Client a) -> Client a #

MonadMask Client Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

mask :: ((forall a. Client a -> Client a) -> Client b) -> Client b #

uninterruptibleMask :: ((forall a. Client a -> Client a) -> Client b) -> Client b #

generalBracket :: Client a -> (a -> ExitCase b -> Client c) -> (a -> Client b) -> Client (b, c) #

MonadUnliftIO Client Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

askUnliftIO :: Client (UnliftIO Client) #

withRunInIO :: ((forall a. Client a -> IO a) -> IO b) -> Client b #

MonadClient Client Source # 
Instance details

Defined in Database.CQL.IO.Client

MonadReader ClientState Client Source # 
Instance details

Defined in Database.CQL.IO.Client

class (MonadIO m, MonadThrow m) => MonadClient m where Source #

Monads in which Client actions may be embedded.

Methods

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
MonadClient Client Source # 
Instance details

Defined in Database.CQL.IO.Client

MonadClient m => MonadClient (ExceptT e m) Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

liftClient :: Client a -> ExceptT e m a Source #

localState :: (ClientState -> ClientState) -> ExceptT e m a -> ExceptT e m a Source #

MonadClient m => MonadClient (StateT s m) Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

liftClient :: Client a -> StateT s m a Source #

localState :: (ClientState -> ClientState) -> StateT s m a -> StateT s m a Source #

MonadClient m => MonadClient (StateT s m) Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

liftClient :: Client a -> StateT s m a Source #

localState :: (ClientState -> ClientState) -> StateT s m a -> StateT s m a Source #

MonadClient m => MonadClient (ReaderT r m) Source # 
Instance details

Defined in Database.CQL.IO.Client

Methods

liftClient :: Client a -> ReaderT r m a Source #

localState :: (ClientState -> ClientState) -> ReaderT r m a -> ReaderT r m a Source #

data ClientState Source #

Opaque client state/environment.

Instances
MonadReader ClientState Client Source # 
Instance details

Defined in Database.CQL.IO.Client

data DebugInfo Source #

Constructors

DebugInfo 

Fields

Instances
Show DebugInfo Source # 
Instance details

Defined in Database.CQL.IO.Client

runClient :: MonadIO m => ClientState -> Client a -> m a Source #

Execute the client monad.

init :: MonadIO m => Settings -> m ClientState Source #

Initialise client state with the given Settings using the provided Logger for all it's logging output.

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 #

Send a Request to a specific Host.

If the request cannot be executed on the given host, e.g. because all connections are occupied, HostsBusy is thrown.

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.

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.

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.