Safe Haskell | None |
---|---|
Language | Haskell2010 |
This driver operates on some state which must be initialised prior to
executing client operations and terminated eventually. The library uses
tinylog for its logging
output and expects a Logger
.
For example (here using the OverloadedStrings
extension) :
> import Data.Text (Text) > import Data.Functor.Identity > import Database.CQL.IO as Client > import qualified System.Logger as Logger > > g <- Logger.new Logger.defSettings > c <- Client.init g defSettings > let q = "SELECT cql_version from system.local" :: QueryString R () (Identity Text) > let p = defQueryParams One () > runClient c (query q p) [Identity "3.4.4"] > shutdown c
Synopsis
- data Settings
- defSettings :: Settings
- addContact :: String -> Settings -> Settings
- setCompression :: Compression -> Settings -> Settings
- setConnectTimeout :: NominalDiffTime -> Settings -> Settings
- setContacts :: String -> [String] -> Settings -> Settings
- setIdleTimeout :: NominalDiffTime -> Settings -> Settings
- setKeyspace :: Keyspace -> Settings -> Settings
- setMaxConnections :: Int -> Settings -> Settings
- setMaxStreams :: Int -> Settings -> Settings
- setMaxTimeouts :: Int -> Settings -> Settings
- setPolicy :: IO Policy -> Settings -> Settings
- setPoolStripes :: Int -> Settings -> Settings
- setPortNumber :: PortNumber -> Settings -> Settings
- data PrepareStrategy
- setPrepareStrategy :: PrepareStrategy -> Settings -> Settings
- setProtocolVersion :: Version -> Settings -> Settings
- setResponseTimeout :: NominalDiffTime -> Settings -> Settings
- setSendTimeout :: NominalDiffTime -> Settings -> Settings
- setRetrySettings :: RetrySettings -> Settings -> Settings
- setMaxRecvBuffer :: Int -> Settings -> Settings
- setSSLContext :: SSLContext -> Settings -> Settings
- data Logger = Logger {
- logMessage :: LogLevel -> Builder -> IO ()
- logRequest :: ByteString -> IO ()
- logResponse :: ByteString -> IO ()
- data LogLevel
- setLogger :: Logger -> Settings -> Settings
- nullLogger :: Logger
- stdoutLogger :: LogLevel -> Logger
- setAuthentication :: [Authenticator] -> Settings -> Settings
- data Authenticator where
- Authenticator :: forall s. {..} -> Authenticator
- data AuthContext
- data ConnId
- authConnId :: Lens' AuthContext ConnId
- authHost :: Lens' AuthContext InetAddr
- newtype AuthMechanism = AuthMechanism Text
- newtype AuthUser = AuthUser Text
- newtype AuthPass = AuthPass Text
- passwordAuthenticator :: AuthUser -> AuthPass -> Authenticator
- data RetrySettings
- noRetry :: RetrySettings
- defRetrySettings :: RetrySettings
- defRetryPolicy :: RetryPolicy
- defRetryHandlers :: Monad m => [RetryStatus -> Handler m Bool]
- eagerRetrySettings :: RetrySettings
- eagerRetryPolicy :: RetryPolicy
- eagerRetryHandlers :: Monad m => [RetryStatus -> Handler m Bool]
- setRetryPolicy :: RetryPolicy -> RetrySettings -> RetrySettings
- setRetryHandlers :: (forall (m :: Type -> Type). Monad m => [RetryStatus -> Handler m Bool]) -> RetrySettings -> RetrySettings
- adjustConsistency :: Consistency -> RetrySettings -> RetrySettings
- adjustSendTimeout :: NominalDiffTime -> RetrySettings -> RetrySettings
- adjustResponseTimeout :: NominalDiffTime -> RetrySettings -> RetrySettings
- data Policy = Policy {}
- random :: IO Policy
- roundRobin :: IO Policy
- data Host
- data HostEvent
- newtype InetAddr = InetAddr {}
- hostAddr :: Lens' Host InetAddr
- dataCentre :: Lens' Host Text
- rack :: Lens' Host Text
- data Client a
- class (MonadIO m, MonadThrow m) => MonadClient (m :: Type -> Type) 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)
- init :: MonadIO m => Settings -> m ClientState
- runClient :: MonadIO m => ClientState -> Client a -> m a
- shutdown :: MonadIO m => ClientState -> m ()
- debugInfo :: MonadClient m => m DebugInfo
- data R
- data W
- data S
- data QueryParams a = QueryParams {}
- defQueryParams :: Consistency -> a -> QueryParams a
- data Consistency
- = Any
- | One
- | LocalOne
- | Two
- | Three
- | Quorum
- | LocalQuorum
- | All
- | EachQuorum
- | Serial
- | LocalSerial
- data SerialConsistency
- newtype Identity a = Identity {
- runIdentity :: a
- newtype QueryString k a b = QueryString {}
- query :: (MonadClient m, Tuple a, Tuple b, RunQ q) => q R a b -> QueryParams a -> m [b]
- query1 :: (MonadClient m, Tuple a, Tuple b, RunQ q) => q R a b -> QueryParams a -> m (Maybe b)
- write :: (MonadClient m, Tuple a, RunQ q) => q W a () -> QueryParams a -> m ()
- schema :: (MonadClient m, Tuple a, RunQ q) => q S a () -> QueryParams a -> m (Maybe SchemaChange)
- data PrepQuery k a b
- prepared :: QueryString k a b -> PrepQuery k a b
- queryString :: PrepQuery k a b -> QueryString k a b
- data Page a = Page {}
- emptyPage :: Page a
- paginate :: (MonadClient m, Tuple a, Tuple b, RunQ q) => q R a b -> QueryParams a -> m (Page b)
- data Row
- fromRow :: Cql a => Int -> Row -> Either String a
- trans :: (MonadClient m, Tuple a, RunQ q) => q W a Row -> QueryParams a -> m [Row]
- data BatchM a
- addQuery :: (Show a, Tuple a, Tuple b) => QueryString W a b -> a -> BatchM ()
- addPrepQuery :: (Show a, Tuple a, Tuple b) => PrepQuery W a b -> a -> BatchM ()
- setType :: BatchType -> BatchM ()
- setConsistency :: Consistency -> BatchM ()
- setSerialConsistency :: SerialConsistency -> BatchM ()
- batch :: MonadClient m => BatchM () -> m ()
- retry :: MonadClient m => RetrySettings -> m a -> m a
- once :: MonadClient m => m a -> m a
- class RunQ q where
- runQ :: (MonadClient m, Tuple a, Tuple b) => q k a b -> QueryParams a -> m (HostResponse k a b)
- data HostResponse k a b = HostResponse {
- hrHost :: !Host
- hrResponse :: !(Response k a b)
- request :: (MonadClient m, Tuple a, Tuple b) => Request k a b -> m (HostResponse k a b)
- getResult :: MonadThrow m => HostResponse k a b -> m (Result k a b)
- data ProtocolError where
- UnexpectedResponse :: forall k a b. Host -> Response k a b -> ProtocolError
- UnexpectedQueryId :: forall k a b. QueryId k a b -> ProtocolError
- UnsupportedCompression :: forall. CompressionAlgorithm -> [CompressionAlgorithm] -> ProtocolError
- SerialiseError :: forall. String -> ProtocolError
- ParseError :: forall. String -> ProtocolError
- data HostError
- data ConnectionError
- data ResponseError = ResponseError {}
- data AuthenticationError
- data HashCollision = HashCollision !Text !Text
Client Settings
defSettings :: Settings #
Default settings:
- The initial contact point is "localhost" on port 9042.
- The load-balancing policy is
random
. - The binary protocol version is 3.
- The connection idle timeout is 60s.
- The connection pool uses 4 stripes to mitigate thread contention.
- Connections use a connect timeout of 5s, a send timeout of 3s and a receive timeout of 10s.
- 128 streams per connection are used.
- 16k receive buffer size.
- No compression is applied to frame bodies.
- No default keyspace is used.
- A single, immediate retry is performed for errors that are always safe to
retry and are known to have good chances of succeeding on a retry.
See
defRetrySettings
. - Query preparation is done lazily. See
PrepareStrategy
.
addContact :: String -> Settings -> Settings #
Add an additional host to the contact list.
setCompression :: Compression -> Settings -> Settings #
Set the compression to use for frame body compression.
setConnectTimeout :: NominalDiffTime -> Settings -> Settings #
Set the connect timeout of a connection.
setContacts :: String -> [String] -> Settings -> Settings #
Set the initial contact points (hosts) from which node discovery will start.
setIdleTimeout :: NominalDiffTime -> Settings -> Settings #
Set the connection idle timeout. Connections in a pool will be closed if not in use for longer than this timeout.
setKeyspace :: Keyspace -> Settings -> Settings #
Set the default keyspace to use. Every new connection will be initialised to use this keyspace.
setMaxConnections :: Int -> Settings -> Settings #
Maximum connections per pool stripe.
setMaxStreams :: Int -> Settings -> Settings #
Set the maximum number of streams per connection. In version 2 of the binary protocol at most 128 streams can be used. Version 3 supports up to 32768 streams.
setMaxTimeouts :: Int -> Settings -> Settings #
When receiving a response times out, we can no longer use the stream of the connection that was used to make the request as it is uncertain if a response will arrive later. Thus the bandwith of a connection will be decreased. This settings defines a threshold after which we close the connection to get a new one with all streams available.
setPoolStripes :: Int -> Settings -> Settings #
Set the number of pool stripes to use. A good setting is equal to the number of CPU cores this codes is running on.
setPortNumber :: PortNumber -> Settings -> Settings #
Set the portnumber to use to connect on every node of the cluster.
data PrepareStrategy #
Strategy for the execution of PrepQuery
s.
EagerPrepare | cluster-wide preparation |
LazyPrepare | on-demand per node preparation |
Instances
Eq PrepareStrategy | |
Defined in Database.CQL.IO.Settings (==) :: PrepareStrategy -> PrepareStrategy -> Bool # (/=) :: PrepareStrategy -> PrepareStrategy -> Bool # | |
Ord PrepareStrategy | |
Defined in Database.CQL.IO.Settings compare :: PrepareStrategy -> PrepareStrategy -> Ordering # (<) :: PrepareStrategy -> PrepareStrategy -> Bool # (<=) :: PrepareStrategy -> PrepareStrategy -> Bool # (>) :: PrepareStrategy -> PrepareStrategy -> Bool # (>=) :: PrepareStrategy -> PrepareStrategy -> Bool # max :: PrepareStrategy -> PrepareStrategy -> PrepareStrategy # min :: PrepareStrategy -> PrepareStrategy -> PrepareStrategy # | |
Show PrepareStrategy | |
Defined in Database.CQL.IO.Settings showsPrec :: Int -> PrepareStrategy -> ShowS # show :: PrepareStrategy -> String # showList :: [PrepareStrategy] -> ShowS # |
setPrepareStrategy :: PrepareStrategy -> Settings -> Settings #
Set strategy to use for preparing statements.
setProtocolVersion :: Version -> Settings -> Settings #
Set the binary protocol version to use.
setResponseTimeout :: NominalDiffTime -> Settings -> Settings #
Set the response timeout of a connection. Requests exceeding the
response timeout will fail with a ResponseTimeout
exception.
setSendTimeout :: NominalDiffTime -> Settings -> Settings #
Set the send timeout of a connection. Requests exceeding the send
timeout will cause the connection to be closed and fail with a
ConnectionClosed
exception.
setRetrySettings :: RetrySettings -> Settings -> Settings #
Set the retry settings to use.
setMaxRecvBuffer :: Int -> Settings -> Settings #
Set maximum receive buffer size.
The actual buffer size used will be the minimum of the CQL response size and the value set here.
setSSLContext :: SSLContext -> Settings -> Settings #
Set a fully configured SSL context.
This will make client server queries use TLS.
Logging
A Logger
provides functions for logging textual messages as well as
binary CQL protocol requests and responses emitted by the client.
Logger | |
|
Log levels used by the client.
LogDebug | Verbose debug information that should not be enabled in production environments. |
LogInfo | General information concerning client and cluster state. |
LogWarn | Warnings of potential problems that should be investigated. |
LogError | Errors that should be investigated and monitored. |
setLogger :: Logger -> Settings -> Settings #
Set the Logger
to use for processing log messages emitted by the client.
nullLogger :: Logger #
A logger that discards all log messages.
stdoutLogger :: LogLevel -> Logger #
A logger that writes all log messages to stdout, discarding log messages whose level is less than the given level. Requests and responses are logged on debug level, formatted in hexadecimal blocks.
Authentication
setAuthentication :: [Authenticator] -> Settings -> Settings #
Set the supported authentication mechanisms.
When a Cassandra server requests authentication on a connection,
it specifies the requested AuthMechanism
. The client Authenticator
is chosen based that name. If no authenticator with a matching
name is configured, an AuthenticationError
is thrown.
data Authenticator where #
A client authentication handler.
The fields of an Authenticator
must implement the client-side
of an (SASL) authentication mechanism as follows:
- When a Cassandra server requests authentication on a new connection,
authOnRequest
is called with theAuthContext
of the connection. - If additional challenges are posed by the server,
authOnChallenge
is called, if available, otherwise anAuthenticationError
is thrown, i.e. every challenge must be answered. - Upon successful authentication
authOnSuccess
is called.
The existential type s
is chosen by an implementation and can
be used to thread arbitrary state through the sequence of callback
invocations during an authentication exchange.
See also: RFC4422 Authentication
Authenticator | |
|
data AuthContext #
Context information given to Authenticator
s when
the server requests authentication on a connection.
See authOnRequest
.
newtype AuthMechanism #
The (unique) name of a SASL authentication mechanism.
In the case of Cassandra, this is currently always the fully-qualified
Java class name of the configured server-side IAuthenticator
implementation.
Instances
passwordAuthenticator :: AuthUser -> AuthPass -> Authenticator #
A password authentication handler for use with Cassandra's
PasswordAuthenticator
.
Retry Settings
data RetrySettings #
Retry settings control if and how retries are performed by the client upon encountering errors during query execution.
There are three aspects to the retry settings:
- What to retry. Determined by the retry handlers (
setRetryHandlers
). - How to perform the retries. Determined by the retry policy
(
setRetryPolicy
). - Configuration adjustments to be performed before retrying. Determined by
adjustConsistency
,adjustSendTimeout
andadjustResponseTimeout
. These adjustments are performed once before the first retry and are scoped to the retries only.
Retry settings can be scoped to a client action by retry
,
thus locally overriding the "global" retry settings configured by
setRetrySettings
.
Never retry.
Default
defRetrySettings :: RetrySettings #
Default retry settings, combining defRetryHandlers
with defRetryPolicy
.
Consistency is never reduced on retries and timeout values remain unchanged.
defRetryPolicy :: RetryPolicy #
The default retry policy permits a single, immediate retry.
defRetryHandlers :: Monad m => [RetryStatus -> Handler m Bool] #
The default retry handlers permit a retry for the following errors:
- A
HostError
, since it always occurs before a query has been sent to the server. - A
ConnectionError
that is aConnectTimeout
, since it always occurs before a query has been sent to the server. A
ResponseError
that is one of the following:Unavailable
, since that is an error response from a coordinator before the query is actually executed.- A
ReadTimeout
that indicates that the required consistency level could be achieved but the data was unfortunately chosen by the coordinator to be returned from a replica that turned out to be unavailable. A retry has a good chance of getting the data from one of the other replicas. - A
WriteTimeout
for a write to the batch log failed. The batch log is written prior to execution of the statements of the batch and hence these errors are safe to retry.
Eager
eagerRetrySettings :: RetrySettings #
Eager retry settings, combining eagerRetryHandlers
with
eagerRetryPolicy
. Consistency is never reduced on retries and timeout
values remain unchanged.
eagerRetryPolicy :: RetryPolicy #
The eager retry policy permits 5 retries with exponential backoff (base-2) with an initial delay of 100ms, i.e. the retries will be performed with 100ms, 200ms, 400ms, 800ms and 1.6s delay, respectively, for a maximum delay of ~3s.
eagerRetryHandlers :: Monad m => [RetryStatus -> Handler m Bool] #
The eager retry handlers permit a superset of the errors
of defRetryHandlers
, namely:
- Any
ResponseError
that is aReadTimeout
,WriteTimeout
,Overloaded
,Unavailable
orServerError
. - Any
ConnectionError
. - Any
IOException
. - Any
HostError
. - Any
SomeSSLException
(if an SSL context is configured).
Notably, these retry handlers are only safe to use for idempotent queries, or if a duplicate write has no severe consequences in the context of the application's data model.
Configuration
setRetryPolicy :: RetryPolicy -> RetrySettings -> RetrySettings #
Set the RetryPolicy
to apply on retryable exceptions,
which determines the number and distribution of retries over time,
i.e. how retries are performed. Configuring a retry policy
does not specify what errors should actually be retried.
See setRetryHandlers
.
setRetryHandlers :: (forall (m :: Type -> Type). Monad m => [RetryStatus -> Handler m Bool]) -> RetrySettings -> RetrySettings #
Set the exception handlers that decide whether a request can be
retried by the client, i.e. what errors are permissible to retry.
For configuring how the retries are performed, see setRetryPolicy
.
adjustConsistency :: Consistency -> RetrySettings -> RetrySettings #
On retry, change the consistency to the given value.
adjustSendTimeout :: NominalDiffTime -> RetrySettings -> RetrySettings #
On retry adjust the send timeout. See setSendTimeout
.
adjustResponseTimeout :: NominalDiffTime -> RetrySettings -> RetrySettings #
On retry adjust the response timeout. See setResponseTimeout
.
Load-balancing
A policy defines a load-balancing strategy and generally handles host visibility.
Policy | |
|
roundRobin :: IO Policy #
Iterate over hosts one by one.
Hosts
This event will be passed to a Policy
to inform it about
cluster changes.
dataCentre :: Lens' Host Text #
The data centre name (may be an empty string).
Client Monad
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 | |
Functor Client | |
Applicative Client | |
MonadIO Client | |
Defined in Database.CQL.IO.Client | |
MonadClient Client | |
Defined in Database.CQL.IO.Client liftClient :: Client a -> Client a # localState :: (ClientState -> ClientState) -> Client a -> Client a # | |
MonadThrow Client | |
Defined in Database.CQL.IO.Client | |
MonadCatch Client | |
MonadMask Client | |
MonadUnliftIO Client | |
Defined in Database.CQL.IO.Client | |
MonadReader ClientState Client | |
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 :: Type -> Type) where #
Monads in which Client
actions may be embedded.
liftClient :: Client a -> m a #
Lift a computation from the Client
monad.
localState :: (ClientState -> ClientState) -> m a -> m a #
Execute an action with a modified ClientState
.
Instances
MonadClient Client | |
Defined in Database.CQL.IO.Client liftClient :: Client a -> Client a # localState :: (ClientState -> ClientState) -> Client a -> Client a # | |
MonadClient m => MonadClient (ExceptT e m) | |
Defined in Database.CQL.IO.Client liftClient :: Client a -> ExceptT e m a # localState :: (ClientState -> ClientState) -> ExceptT e m a -> ExceptT e m a # | |
MonadClient m => MonadClient (StateT s m) | |
Defined in Database.CQL.IO.Client liftClient :: Client a -> StateT s m a # localState :: (ClientState -> ClientState) -> StateT s m a -> StateT s m a # | |
MonadClient m => MonadClient (StateT s m) | |
Defined in Database.CQL.IO.Client liftClient :: Client a -> StateT s m a # localState :: (ClientState -> ClientState) -> StateT s m a -> StateT s m a # | |
MonadClient m => MonadClient (ReaderT r m) | |
Defined in Database.CQL.IO.Client liftClient :: Client a -> ReaderT r m a # localState :: (ClientState -> ClientState) -> ReaderT r m a -> ReaderT r m a # |
data ClientState #
Opaque client state/environment.
Instances
MonadReader ClientState Client | |
Defined in Database.CQL.IO.Client ask :: Client ClientState # local :: (ClientState -> ClientState) -> Client a -> Client a # reader :: (ClientState -> a) -> Client a # |
DebugInfo | |
|
init :: MonadIO m => Settings -> m ClientState #
runClient :: MonadIO m => ClientState -> Client a -> m a #
Execute the client monad.
shutdown :: MonadIO m => ClientState -> m () #
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.
debugInfo :: MonadClient m => m DebugInfo #
Queries
Queries are defined either as QueryString
s or PrepQuery
s.
Both types carry three phantom type parameters used to describe
the query, input and output types, respectively, as follows:
k
is one ofR
ead,W
rite orS
chema.a
is the tuple type for the input, i.e. for the parameters bound by positional (?
) or named (:foo
) placeholders.b
is the tuple type for the outputs, i.e. for the columns selected in a query.
Thereby every type used in an input or output tuple must be an instance
of the Cql
typeclass. It is the responsibility of user code
that the type ascription of a query matches the order, number and types of
the parameters. For example:
myQuery :: QueryString R (Identity UUID) (Text, Int, Maybe UTCTime) myQuery = "select name, age, birthday from user where id = ?"
In this example, the query is declared as a R
ead with a single
input (id) and three outputs (name, age and birthday).
Note that a single input or output type needs to be wrapped
in the Identity
newtype, for which there is a Cql
instance,
in order to avoid overlapping instances.
It is a common strategy to use additional newtype
s with derived
Cql
instances for additional type safety, e.g.
newtype UserId = UserId UUID deriving (Eq, Show, Cql)
The input and output tuples can further be automatically
converted from and to records via the Record
typeclass, whose instances can be generated via TemplateHaskell
,
if desired.
Note on null values
In principle, any column in Cassandra is nullable, i.e. may be
be set to null
as a result of row operations. It is therefore
important that any output type of a query that may be null
is wrapped in the Maybe
type constructor.
It is a common pitfall that a column is assumed to never contain
null values, when in fact partial updates or deletions on a row,
including via the use of TTLs, may result in null values and thus
runtime errors when processing the responses.
data QueryParams a #
Query parameters.
QueryParams | |
|
Instances
Show a => Show (QueryParams a) | |
Defined in Database.CQL.Protocol.Request showsPrec :: Int -> QueryParams a -> ShowS # show :: QueryParams a -> String # showList :: [QueryParams a] -> ShowS # |
defQueryParams :: Consistency -> a -> QueryParams a #
Construct default QueryParams
for the given consistency
and bound values. In particular, no page size, paging state
or serial consistency will be set.
data Consistency #
Consistency level.
See: Consistency
Any | |
One | |
LocalOne | |
Two | |
Three | |
Quorum | |
LocalQuorum | |
All | |
EachQuorum | Only for write queries. |
Serial | Only for read queries. |
LocalSerial | Only for read queries. |
Instances
Eq Consistency | |
Defined in Database.CQL.Protocol.Types (==) :: Consistency -> Consistency -> Bool # (/=) :: Consistency -> Consistency -> Bool # | |
Show Consistency | |
Defined in Database.CQL.Protocol.Types showsPrec :: Int -> Consistency -> ShowS # show :: Consistency -> String # showList :: [Consistency] -> ShowS # |
data SerialConsistency #
Consistency level for the serial phase of conditional updates (aka "lightweight transactions").
See: SerialConsistency
SerialConsistency | Default. Quorum-based linearizable consistency. |
LocalSerialConsistency | Like |
Instances
Show SerialConsistency | |
Defined in Database.CQL.Protocol.Request showsPrec :: Int -> SerialConsistency -> ShowS # show :: SerialConsistency -> String # showList :: [SerialConsistency] -> ShowS # |
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Identity | |
|
Instances
Basic Queries
newtype QueryString k a b #
Instances
RunQ QueryString Source # | |
Defined in Database.CQL.IO runQ :: (MonadClient m, Tuple a, Tuple b) => QueryString k a b -> QueryParams a -> m (HostResponse k a b) Source # | |
Eq (QueryString k a b) | |
Defined in Database.CQL.Protocol.Types (==) :: QueryString k a b -> QueryString k a b -> Bool # (/=) :: QueryString k a b -> QueryString k a b -> Bool # | |
Show (QueryString k a b) | |
Defined in Database.CQL.Protocol.Types showsPrec :: Int -> QueryString k a b -> ShowS # show :: QueryString k a b -> String # showList :: [QueryString k a b] -> ShowS # | |
IsString (QueryString k a b) | |
Defined in Database.CQL.Protocol.Types fromString :: String -> QueryString k a b # |
query :: (MonadClient m, Tuple a, Tuple b, RunQ q) => q R a b -> QueryParams a -> m [b] Source #
Run a CQL read-only query returning a list of results.
query1 :: (MonadClient m, Tuple a, Tuple b, RunQ q) => q R a b -> QueryParams a -> m (Maybe b) Source #
Run a CQL read-only query returning a single result.
write :: (MonadClient m, Tuple a, RunQ q) => q W a () -> QueryParams a -> m () Source #
Run a CQL write-only query (e.g. insert/update/delete), returning no result.
/Note: If the write operation is conditional, i.e. is in fact a "lightweight
transaction" returning a result, trans
must be used instead./
schema :: (MonadClient m, Tuple a, RunQ q) => q S a () -> QueryParams a -> m (Maybe SchemaChange) Source #
Run a CQL schema query, returning SchemaChange
information, if any.
Prepared Queries
Representation of a prepared QueryString
. A prepared query is
executed in two stages:
- The query string is sent to a server without parameters for
preparation. The server responds with a
QueryId
. - The prepared query is executed by sending the
QueryId
and parameters to the server.
Thereby step 1 is only performed when the query has not yet been prepared with the host (coordinator) used for query execution. Thus, prepared queries enhance performance by avoiding the repeated sending and parsing of query strings.
Query preparation is handled transparently by the client.
See setPrepareStrategy
.
Note
Prepared statements are fully supported but rely on some assumptions beyond the scope of the CQL binary protocol specification (spec):
- The spec scopes the
QueryId
to the node the query has been prepared with. The spec does not state anything about the format of theQueryId
. However the official Java driver assumes that any givenQueryString
yields the sameQueryId
on every node. This client make the same assumption. - In case a node does not know a given
QueryId
anUnprepared
error is returned. We assume that it is always safe to transparently re-prepare the correspondingQueryString
and to re-execute the original request against the same node.
Besides these assumptions there is also a potential tradeoff in
regards to eager vs. lazy query preparation.
We understand eager to mean preparation against all current nodes of
a cluster and lazy to mean preparation against a single node on demand,
i.e. upon receiving an Unprepared
error response. Which strategy to
choose depends on the scope of query reuse and the size of the cluster.
The global default can be changed through the Settings
module as well
as locally using withPrepareStrategy
.
Instances
RunQ PrepQuery Source # | |
Defined in Database.CQL.IO runQ :: (MonadClient m, Tuple a, Tuple b) => PrepQuery k a b -> QueryParams a -> m (HostResponse k a b) Source # | |
IsString (PrepQuery k a b) | |
Defined in Database.CQL.IO.PrepQuery fromString :: String -> PrepQuery k a b # |
prepared :: QueryString k a b -> PrepQuery k a b #
queryString :: PrepQuery k a b -> QueryString k a b #
Paging
Return value of paginate
. Contains the actual result values as well
as an indication of whether there is more data available and the actual
action to fetch the next page.
paginate :: (MonadClient m, Tuple a, Tuple b, RunQ q) => q R a b -> QueryParams a -> m (Page b) Source #
Run a CQL read-only query against a Cassandra node.
This function is like query
, but limits the result size to 10000
(default) unless there is an explicit size restriction given in
QueryParams
. The returned Page
can be used to continue the query.
Please note that -- as of Cassandra 2.1.0 -- if your requested page size
is equal to the result size, hasMore
might be true and a subsequent
nextPage
will return an empty list in result
.
Lightweight Transactions
A row is a vector of Value
s.
trans :: (MonadClient m, Tuple a, RunQ q) => q W a Row -> QueryParams a -> m [Row] Source #
Run a CQL conditional write query (e.g. insert/update/delete) as a
"lightweight transaction", returning the result Row
s describing the
outcome.
Batch Queries
addQuery :: (Show a, Tuple a, Tuple b) => QueryString W a b -> a -> BatchM () #
Add a query to this batch.
addPrepQuery :: (Show a, Tuple a, Tuple b) => PrepQuery W a b -> a -> BatchM () #
Add a prepared query to this batch.
setConsistency :: Consistency -> BatchM () #
Set Batch
consistency level.
setSerialConsistency :: SerialConsistency -> BatchM () #
Set Batch
serial consistency.
batch :: MonadClient m => BatchM () -> m () Source #
Run a batch query against a Cassandra node.
Retries
retry :: MonadClient m => RetrySettings -> m a -> m a #
Use given RetrySettings
during execution of some client action.
once :: MonadClient m => m a -> m a #
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.
Low-Level Queries
Note: Use of the these functions may require additional imports from
Database.CQL.Protocol
or its submodules in order to construct
Request
s and evaluate Response
s.
A type which can be run as a query.
runQ :: (MonadClient m, Tuple a, Tuple b) => q k a b -> QueryParams a -> m (HostResponse k a b) Source #
Instances
RunQ QueryString Source # | |
Defined in Database.CQL.IO runQ :: (MonadClient m, Tuple a, Tuple b) => QueryString k a b -> QueryParams a -> m (HostResponse k a b) Source # | |
RunQ PrepQuery Source # | |
Defined in Database.CQL.IO runQ :: (MonadClient m, Tuple a, Tuple b) => PrepQuery k a b -> QueryParams a -> m (HostResponse k a b) Source # |
data HostResponse k a b #
A response that is known to originate from a specific Host
.
HostResponse | |
|
Instances
Show b => Show (HostResponse k a b) | |
Defined in Database.CQL.IO.Cluster.Host showsPrec :: Int -> HostResponse k a b -> ShowS # show :: HostResponse k a b -> String # showList :: [HostResponse k a b] -> ShowS # |
request :: (MonadClient m, Tuple a, Tuple b) => Request k a b -> m (HostResponse k a b) #
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
.
getResult :: MonadThrow m => HostResponse k a b -> m (Result k a b) #
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.
Exceptions
data ProtocolError where #
A protocol error indicates a problem related to the client-server communication protocol. The cause may either be misconfiguration on the client or server, or an implementation bug. In the latter case it should be reported. In either case these errors are not recoverable and should never be retried.
UnexpectedResponse :: forall k a b. Host -> Response k a b -> ProtocolError | The client received an unexpected response for a request. This indicates a problem with the communication protocol and should be reported. |
UnexpectedQueryId :: forall k a b. QueryId k a b -> ProtocolError | The client received an unexpected query ID in an |
UnsupportedCompression :: forall. CompressionAlgorithm -> [CompressionAlgorithm] -> ProtocolError | The client tried to use a compression algorithm that is not supported by the server. The first argument is the offending algorithm and the second argument the list of supported algorithms as reported by the server. This indicates a client or server-side configuration error. |
SerialiseError :: forall. String -> ProtocolError | An error occurred during the serialisation of a request. This indicates a problem with the wire protocol and should be reported. |
ParseError :: forall. String -> ProtocolError | An error occurred during parsing of a response. This indicates a problem with the wire protocol and should be reported. |
Instances
Show ProtocolError | |
Defined in Database.CQL.IO.Exception showsPrec :: Int -> ProtocolError -> ShowS # show :: ProtocolError -> String # showList :: [ProtocolError] -> ShowS # | |
Exception ProtocolError | |
Defined in Database.CQL.IO.Exception |
An error during host selection prior to query execution.
These errors are always safe to retry but may indicate an overload situation and thus suggest a review of the client and cluster configuration (number of hosts, pool sizes, connections per host, streams per connection, ...).
NoHostAvailable | There is currently not a single host available to the
client according to the configured |
HostsBusy | All streams on all connections are currently in use. |
Instances
Show HostError | |
Exception HostError | |
Defined in Database.CQL.IO.Exception toException :: HostError -> SomeException # fromException :: SomeException -> Maybe HostError # displayException :: HostError -> String # |
data ConnectionError #
An error while establishing or using a connection to send a request or receive a response.
ConnectionClosed !InetAddr | The connection was suddenly closed. Retries are only safe for idempotent queries. |
ConnectTimeout !InetAddr | A timeout occurred while establishing a connection.
See also |
ResponseTimeout !InetAddr | A timeout occurred while waiting for a response.
See also |
Instances
Show ConnectionError | |
Defined in Database.CQL.IO.Exception showsPrec :: Int -> ConnectionError -> ShowS # show :: ConnectionError -> String # showList :: [ConnectionError] -> ShowS # | |
Exception ConnectionError | |
Defined in Database.CQL.IO.Exception |
data ResponseError #
The server responded with an Error
.
Most of these errors are either not retryable or only safe to retry for idempotent queries. For more details of which errors may be safely retried under which circumstances, see also the documentation of the Java driver.
Instances
Show ResponseError | |
Defined in Database.CQL.IO.Exception showsPrec :: Int -> ResponseError -> ShowS # show :: ResponseError -> String # showList :: [ResponseError] -> ShowS # | |
Exception ResponseError | |
Defined in Database.CQL.IO.Exception |
data AuthenticationError #
An error occurred during the authentication phase while
initialising a new connection. This indicates a configuration
error or a faulty Authenticator
.
AuthenticationRequired !AuthMechanism | The server demanded authentication but none was provided by the client. |
UnexpectedAuthenticationChallenge !AuthMechanism !AuthChallenge | The server presented an additional authentication challenge
that the configured |
Instances
Show AuthenticationError | |
Defined in Database.CQL.IO.Exception showsPrec :: Int -> AuthenticationError -> ShowS # show :: AuthenticationError -> String # showList :: [AuthenticationError] -> ShowS # | |
Exception AuthenticationError | |
data HashCollision #
An unexpected hash collision occurred for a prepared query string. This indicates a problem with the implementation of prepared queries and should be reported.
Instances
Show HashCollision | |
Defined in Database.CQL.IO.Exception showsPrec :: Int -> HashCollision -> ShowS # show :: HashCollision -> String # showList :: [HashCollision] -> ShowS # | |
Exception HashCollision | |
Defined in Database.CQL.IO.Exception |