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:
> import Data.Text (Text) > import Data.Functor.Identity > import Database.CQL.IO as Client > import Database.CQL.Protocol > import qualified System.Logger as Logger > > g <- Logger.new Logger.defSettings > c <- Client.init g defSettings > let p = QueryParams One False () Nothing Nothing Nothing > runClient c $ query ("SELECT cql_version from system.local" :: QueryString R () (Identity Text)) p [Identity "3.2.0"] > shutdown c
- 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
- setProtocolVersion :: Version -> Settings -> Settings
- setResponseTimeout :: NominalDiffTime -> Settings -> Settings
- setSendTimeout :: NominalDiffTime -> Settings -> Settings
- setRetrySettings :: RetrySettings -> Settings -> Settings
- setMaxRecvBuffer :: Int -> Settings -> Settings
- data RetrySettings
- noRetry :: RetrySettings
- retryForever :: RetrySettings
- maxRetries :: Word -> RetrySettings -> RetrySettings
- adjustConsistency :: Consistency -> RetrySettings -> RetrySettings
- constDelay :: NominalDiffTime -> RetrySettings -> RetrySettings
- expBackoff :: NominalDiffTime -> NominalDiffTime -> RetrySettings -> RetrySettings
- fibBackoff :: NominalDiffTime -> NominalDiffTime -> RetrySettings -> RetrySettings
- adjustSendTimeout :: NominalDiffTime -> RetrySettings -> RetrySettings
- adjustResponseTimeout :: NominalDiffTime -> RetrySettings -> RetrySettings
- data Client a
- class (Functor m, Applicative m, Monad m, MonadIO m, MonadCatch m) => MonadClient m where
- liftClient :: Client a -> m a
- localState :: (ClientState -> ClientState) -> m a -> m a
- data ClientState
- data DebugInfo = DebugInfo {}
- init :: MonadIO m => Logger -> Settings -> m ClientState
- runClient :: MonadIO m => ClientState -> Client a -> m a
- retry :: MonadClient m => RetrySettings -> m a -> m a
- shutdown :: MonadIO m => ClientState -> m ()
- debugInfo :: MonadClient m => m DebugInfo
- query :: (MonadClient m, Tuple a, Tuple b) => QueryString R a b -> QueryParams a -> m [b]
- query1 :: (MonadClient m, Tuple a, Tuple b) => QueryString R a b -> QueryParams a -> m (Maybe b)
- write :: (MonadClient m, Tuple a) => QueryString W a () -> QueryParams a -> m ()
- schema :: (MonadClient m, Tuple a) => QueryString S a () -> QueryParams a -> m (Maybe SchemaChange)
- batch :: MonadClient m => Batch -> m ()
- data Page a = Page {}
- emptyPage :: Page a
- paginate :: (MonadClient m, Tuple a, Tuple b) => QueryString R a b -> QueryParams a -> m (Page b)
- request :: (MonadClient m, Tuple a, Tuple b) => Request k a b -> m (Response k a b)
- command :: MonadClient m => Request k () () -> m ()
- 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 InvalidSettings
- newtype InternalError = InternalError String
- data HostError
- data ConnectionError
- data UnexpectedResponse where
- UnexpectedResponse :: UnexpectedResponse
- UnexpectedResponse' :: Show b => !(Response k a b) -> UnexpectedResponse
- newtype Timeout = TimeoutRead String
Client settings
defSettings :: Settings Source
Default settings:
- contact point is "localhost" port 9042
- load-balancing policy is
random
- binary protocol version is 3 (supported by Cassandra >= 2.1.0)
- 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.
- no retries are done
addContact :: String -> Settings -> Settings Source
Add an additional host to the contact list.
setCompression :: Compression -> Settings -> Settings Source
Set the compression to use for frame body compression.
setConnectTimeout :: NominalDiffTime -> Settings -> Settings Source
Set the connect timeout of a connection.
setContacts :: String -> [String] -> Settings -> Settings Source
Set the initial contact points (hosts) from which node discovery will start.
setIdleTimeout :: NominalDiffTime -> Settings -> Settings Source
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 Source
Set the default keyspace to use. Every new connection will be initialised to use this keyspace.
setMaxConnections :: Int -> Settings -> Settings Source
Maximum connections per pool stripe.
setMaxStreams :: Int -> Settings -> Settings Source
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 Source
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 Source
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 Source
Set the portnumber to use to connect on every node of the cluster.
setProtocolVersion :: Version -> Settings -> Settings Source
Set the binary protocol version to use.
setResponseTimeout :: NominalDiffTime -> Settings -> Settings Source
Set the receive timeout of a connection. Requests exceeding the
receive timeout will fail with a Timeout
exception.
setSendTimeout :: NominalDiffTime -> Settings -> Settings Source
Set the send timeout of a connection. Request exceeding the send will
cause the connection to be closed and fail with ConnectionClosed
exception.
setRetrySettings :: RetrySettings -> Settings -> Settings Source
Set default retry settings to use.
setMaxRecvBuffer :: Int -> Settings -> Settings Source
Set maximum receive buffer size.
The actual buffer size used will be the minimum of the CQL response size and the value set here.
Retry Settings
data RetrySettings Source
noRetry :: RetrySettings Source
Never retry.
retryForever :: RetrySettings Source
Forever retry immediately.
maxRetries :: Word -> RetrySettings -> RetrySettings Source
Limit number of retries.
adjustConsistency :: Consistency -> RetrySettings -> RetrySettings Source
When retrying a (batch-) query, change consistency to the given value.
constDelay :: NominalDiffTime -> RetrySettings -> RetrySettings Source
Wait a constant time between retries.
:: NominalDiffTime | Initial delay. |
-> NominalDiffTime | Maximum delay. |
-> RetrySettings | |
-> RetrySettings |
Delay retries with exponential backoff.
:: NominalDiffTime | Initial delay. |
-> NominalDiffTime | Maximum delay. |
-> RetrySettings | |
-> RetrySettings |
Delay retries using Fibonacci sequence as backoff.
adjustSendTimeout :: NominalDiffTime -> RetrySettings -> RetrySettings Source
On retry adjust the send timeout.
adjustResponseTimeout :: NominalDiffTime -> RetrySettings -> RetrySettings Source
On retry adjust the response timeout.
Client monad
The Client monad.
A simple reader monad 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
.
Actual CQL queries are handled by invoking request
oder command
.
Additionally debugInfo
returns an internal cluster view.
class (Functor m, Applicative m, Monad m, MonadIO m, MonadCatch m) => MonadClient m where Source
Monads in which Client
actions may be embedded.
liftClient :: Client a -> m a Source
Lift a computation to the Client
monad.
localState :: (ClientState -> ClientState) -> m a -> m a Source
Execute an action with a modified ClientState
.
MonadClient Client | |
MonadClient m => MonadClient (ReaderT r m) | |
MonadClient m => MonadClient (StateT s m) | |
MonadClient m => MonadClient (StateT s m) | |
MonadClient m => MonadClient (ExceptT e m) |
runClient :: MonadIO m => ClientState -> Client a -> m a Source
Execute the client monad.
retry :: MonadClient m => RetrySettings -> m a -> m a Source
Use given RetrySettings
during execution of some client action.
shutdown :: MonadIO m => ClientState -> m () Source
Terminate client state, i.e. end all running background checks and shutdown all connection pools.
debugInfo :: MonadClient m => m DebugInfo Source
query :: (MonadClient m, Tuple a, Tuple b) => QueryString R a b -> QueryParams a -> m [b] Source
Run a CQL read-only query against a Cassandra node.
query1 :: (MonadClient m, Tuple a, Tuple b) => QueryString R a b -> QueryParams a -> m (Maybe b) Source
Run a CQL read-only query against a Cassandra node.
write :: (MonadClient m, Tuple a) => QueryString W a () -> QueryParams a -> m () Source
Run a CQL insert/update query against a Cassandra node.
schema :: (MonadClient m, Tuple a) => QueryString S a () -> QueryParams a -> m (Maybe SchemaChange) Source
Run a CQL schema query against a Cassandra node.
batch :: MonadClient m => Batch -> m () Source
Run a batch query against a Cassandra node.
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) => QueryString 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
.
low-level
request :: (MonadClient m, Tuple a, Tuple b) => Request k a b -> m (Response k a b) Source
Send a CQL 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.
command :: MonadClient m => Request k () () -> m () Source
Like request
but not returning any result.
Policies
A policy defines a load-balancing strategy and generally handles host visibility.
Policy | |
|
roundRobin :: IO Policy Source
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 Source
The data centre name (may be an empty string).
Exceptions
data InvalidSettings Source
newtype InternalError Source
data ConnectionError Source
data UnexpectedResponse where Source
UnexpectedResponse :: UnexpectedResponse | |
UnexpectedResponse' :: Show b => !(Response k a b) -> UnexpectedResponse |