Stability | experimental |
---|---|
Maintainer | Ozgun Ataman <oz@soostone.com> |
Safe Haskell | None |
Defines Cassandra operations for persistence of complex Haskell data objects with custom-selected but implicitly performed serialization.
The main design choice is to require a dictionary dictating marshalling/serialization policy for every operation, rather than a typeclass that can be instantiated once.
- type CPool = Pool Cassandra
- type Server = (HostName, Int)
- defServer :: Server
- defServers :: [Server]
- type KeySpace = String
- createCassandraPool :: [Server] -> Int -> Int -> NominalDiffTime -> KeySpace -> IO CPool
- class MonadIO m => MonadCassandra m where
- getCassandraPool :: m CPool
- type Cas a = ReaderT CPool IO a
- runCas :: CPool -> Cas a -> IO a
- transCas :: MonadCassandra m => Cas a -> m (IO a)
- mapCassandra :: (Traversable t, MonadCassandra m) => t (Cas b) -> m (t b)
- data Marshall a = Marshall {
- marshallEncode :: a -> ByteString
- marshallDecode :: ByteString -> Either String a
- casShow :: (Show a, Read a) => Marshall a
- casJSON :: (ToJSON a, FromJSON a) => Marshall a
- casSerialize :: Serialize a => Marshall a
- casSafeCopy :: SafeCopy a => Marshall a
- get :: (MonadCassandra m, CasType k) => Marshall a -> ColumnFamily -> RowKey -> Selector -> ConsistencyLevel -> m [(k, a)]
- get_ :: MonadCassandra m => Marshall a -> ColumnFamily -> RowKey -> Selector -> ConsistencyLevel -> m [a]
- getCol :: (MonadCassandra m, CasType k) => Marshall a -> ColumnFamily -> RowKey -> k -> ConsistencyLevel -> m (Maybe a)
- getMulti :: MonadCassandra m => Marshall a -> ColumnFamily -> KeySelector -> Selector -> ConsistencyLevel -> m (Map RowKey [(ColumnName, a)])
- insertCol :: (MonadCassandra m, CasType k) => Marshall a -> ColumnFamily -> RowKey -> k -> ConsistencyLevel -> a -> m ()
- insertColTTL :: (MonadCassandra m, CasType k) => Marshall a -> ColumnFamily -> RowKey -> k -> ConsistencyLevel -> a -> Int32 -> m ()
- modify :: (MonadCassandra m, CasType k) => Marshall a -> ColumnFamily -> RowKey -> k -> ConsistencyLevel -> ConsistencyLevel -> (Maybe a -> m (ModifyOperation a, b)) -> m b
- modify_ :: (MonadCassandra m, CasType k) => Marshall a -> ColumnFamily -> RowKey -> k -> ConsistencyLevel -> ConsistencyLevel -> (Maybe a -> m (ModifyOperation a)) -> m ()
- delete :: MonadCassandra m => ColumnFamily -> RowKey -> Selector -> ConsistencyLevel -> m ()
- retryCas :: (MonadBaseControl IO m, MonadIO m) => RetrySettings -> m a -> m a
- casRetryH :: Monad m => Handler m Bool
- type RowKey = Key
- type ColumnName = ByteString
- data ModifyOperation a
- type ColumnFamily = String
- data ConsistencyLevel
- = ONE
- | QUORUM
- | LOCAL_QUORUM
- | EACH_QUORUM
- | ALL
- | ANY
- | TWO
- | THREE
- data CassandraException
- data Selector
- range :: Selector
- boundless :: Maybe ByteString
- data Order
- reverseOrder :: Order -> Order
- data KeySelector
- data KeyRangeType
- data PageResult m a
- pIsDry :: PageResult m a -> Bool
- pIsDone :: PageResult t t1 -> Bool
- pHasMore :: PageResult t t1 -> Bool
- paginate :: (MonadCassandra m, MonadBaseControl IO m, CasType k) => Marshall a -> ColumnFamily -> RowKey -> Selector -> ConsistencyLevel -> RetrySettings -> m (PageResult m (k, a))
- paginateSource :: (CasType k, MonadBaseControl IO m, MonadCassandra m) => Marshall a -> ColumnFamily -> RowKey -> Selector -> ConsistencyLevel -> RetrySettings -> Source m (k, a)
- pageToSource :: (MonadBaseControl IO m, Monad m) => PageResult m a -> Source m a
- class CKey a where
- toColKey :: a -> ByteString
- fromColKey :: ByteString -> Either String a
- fromColKey' :: CKey a => ByteString -> a
- module Database.Cassandra.Pack
Connection
defServers :: [Server]Source
A single localhost server with default configuration
:: [Server] | List of servers to connect to |
-> Int | Number of stripes to maintain |
-> Int | Max connections per stripe |
-> NominalDiffTime | Kill each connection after this many seconds |
-> KeySpace | Each pool operates on a single KeySpace |
-> IO CPool |
Create a pool of connections to a cluster of Cassandra boxes
Each box in the cluster will get up to n connections. The pool will send queries in round-robin fashion to balance load on each box in the cluster.
MonadCassandra Typeclass
class MonadIO m => MonadCassandra m whereSource
All Cassy operations are designed to run inside MonadCassandra
context.
We provide a default concrete Cas
datatype, but you can simply
make your own application monads an instance of MonadCassandra
for conveniently using all operations of this package.
Please keep in mind that all Cassandra operations may raise
CassandraException
s at any point in time.
MonadIO m => MonadCassandra (ReaderT CPool m) |
transCas :: MonadCassandra m => Cas a -> m (IO a)Source
Unwrap a Cassandra action and return an IO continuation that can then be run in a pure IO context.
This is useful when you design all your functions in a generic form
with MonadCassandra
m constraints and then one day need to feed
your function to a utility that can only run in an IO context. This
function is then your friendly utility for extracting an IO action.
mapCassandra :: (Traversable t, MonadCassandra m) => t (Cas b) -> m (t b)Source
Run a list of cassandra computations in parallel using the async library
Haskell Record Marshalling
A Haskell dictionary containing a pair of encode/decode functions.
This is the main design choice in this module. We require that each operation takes an explicit marshalling policy rather than a typeclass which makes it possible to do it in a single way per data type.
You can create your own objects of this type with great ease. Just
look at one of the examples here (casJSON
, casSerialize
, etc.)
Marshall | |
|
casJSON :: (ToJSON a, FromJSON a) => Marshall aSource
Marshall data using JSON encoding. Good interoperability, but not very efficient for data storage.
casSerialize :: Serialize a => Marshall aSource
Marshall data using the Serialize
instance. Like Binary
,
Serialize
is very efficient.
casSafeCopy :: SafeCopy a => Marshall aSource
Marshall data using the SafeCopy
instance. This is quite well
suited for production because it is both very efficient and
provides a systematic way to migrate your data types over time.
Cassandra Operations
:: (MonadCassandra m, CasType k) | |
=> Marshall a | |
-> ColumnFamily | |
-> RowKey | |
-> Selector | A slice selector |
-> ConsistencyLevel | |
-> m [(k, a)] | List of key-value pairs. See |
An arbitrary get operation - slice with Selector
.
Internally based on Basic.get. Table is assumed to be a regular ColumnFamily and contents of returned columns are cast into the target type.
:: MonadCassandra m | |
=> Marshall a | |
-> ColumnFamily | |
-> RowKey | |
-> Selector | A slice selector |
-> ConsistencyLevel | |
-> m [a] |
:: (MonadCassandra m, CasType k) | |
=> Marshall a | |
-> ColumnFamily | |
-> RowKey | |
-> k | Column name; anything in |
-> ConsistencyLevel | |
-> m (Maybe a) |
Get a single column from a single row
getMulti :: MonadCassandra m => Marshall a -> ColumnFamily -> KeySelector -> Selector -> ConsistencyLevel -> m (Map RowKey [(ColumnName, a)])Source
Get a slice of columns from multiple rows at once. Note that since we are auto-serializing from JSON, all the columns must be of the same data type.
:: (MonadCassandra m, CasType k) | |
=> Marshall a | |
-> ColumnFamily | |
-> RowKey | |
-> k | Column name. See |
-> ConsistencyLevel | |
-> a | Content |
-> m () |
:: (MonadCassandra m, CasType k) | |
=> Marshall a | |
-> ColumnFamily | |
-> RowKey | |
-> k | Column name. See |
-> ConsistencyLevel | |
-> a | Content |
-> Int32 | TTL for this column |
-> m () |
:: (MonadCassandra m, CasType k) | |
=> Marshall a | A serialization methodology. Example: |
-> ColumnFamily | |
-> RowKey | |
-> k | Column name; anything in CasType |
-> ConsistencyLevel | Read quorum |
-> ConsistencyLevel | Write quorum |
-> (Maybe a -> m (ModifyOperation a, b)) | Modification function. Called with |
-> m b | Return the decided |
A modify function that will fetch a specific column, apply modification function on it and save results back to Cassandra.
A b
side value is returned for computational convenience.
This is intended to be a workhorse function, in that you should be able to do all kinds of relatively straightforward operations just using this function.
This method may throw a CassandraException
for all exceptions other than
NotFoundException
.
:: (MonadCassandra m, CasType k) | |
=> Marshall a | |
-> ColumnFamily | |
-> RowKey | |
-> k | Column name; anything in CasType |
-> ConsistencyLevel | Read quorum |
-> ConsistencyLevel | Write quorum |
-> (Maybe a -> m (ModifyOperation a)) | Modification function. Called with |
-> m () |
Same as modify
but does not offer a side value.
This method may throw a CassandraException
for all exceptions other than
NotFoundException
.
:: MonadCassandra m | |
=> ColumnFamily | In |
-> RowKey | Key to be deleted |
-> Selector | Columns to be deleted |
-> ConsistencyLevel | |
-> m () |
Retrying Queries
:: (MonadBaseControl IO m, MonadIO m) | |
=> RetrySettings | For default settings, just use |
-> m a | Action to perform |
-> m a |
retrying
with direct cassandra support. Server-related failures
will be retried.
UnavailableException
, TimedOutException
and
SchemaDisagreementException
will be automatically retried.
casRetryH :: Monad m => Handler m BoolSource
Exception handler that returns True
for errors that may be
resolved after a retry. So they are good candidates for retrying
queries.
Necessary Types
type ColumnName = ByteStringSource
data ModifyOperation a Source
Possible outcomes of a modify operation
Eq a => Eq (ModifyOperation a) | |
Ord a => Ord (ModifyOperation a) | |
Read a => Read (ModifyOperation a) | |
Show a => Show (ModifyOperation a) |
type ColumnFamily = StringSource
data ConsistencyLevel
data CassandraException Source
Filtering
A column selector/filter statement for queries.
Remember that SuperColumns are always fully deserialized, so we don't offer
a way to filter columns within a SuperColumn
.
Column names and ranges are specified by any type that can be
packed into a Cassandra column using the CasType
typeclass.
All | Return everything in |
forall a . CasType a => ColNames [a] | Return specific columns or super-columns depending on the |
forall a b . (CasType a, CasType b) => SupNames a [b] | When deleting specific columns in a super column |
forall a b . (CasType a, CasType b) => Range | Return a range of columns or super-columns. |
|
A default starting point for range Selector
. Use this so you
don't run into ambiguous type variables when using Nothing.
range = Range (Nothing :: Maybe ByteString) (Nothing :: Maybe ByteString) Regular 1024
reverseOrder :: Order -> OrderSource
data KeySelector Source
A Key
range selector to use with getMulti
.
data KeyRangeType Source
Encodes the Key vs. Token options in the thrift API.
InclusiveRange
ranges are just plain intuitive range queries.
WrapAround
ranges are also inclusive, but they wrap around the ring.
Pagination
data PageResult m a Source
Describes the result of a single pagination action
PDone | Done, this is all I have. |
| |
PMore | Here's a batch and there is more when you call the action. |
|
Monad m => Functor (PageResult m) |
pIsDry :: PageResult m a -> BoolSource
pIsDone :: PageResult t t1 -> BoolSource
pHasMore :: PageResult t t1 -> BoolSource
:: (MonadCassandra m, MonadBaseControl IO m, CasType k) | |
=> Marshall a | Serialization strategy |
-> ColumnFamily | |
-> RowKey | Paginate columns of this row |
-> Selector |
|
-> ConsistencyLevel | |
-> RetrySettings | Retry strategy for each underlying Cassandra call |
-> m (PageResult m (k, a)) |
paginateSource :: (CasType k, MonadBaseControl IO m, MonadCassandra m) => Marshall a -> ColumnFamily -> RowKey -> Selector -> ConsistencyLevel -> RetrySettings -> Source m (k, a)Source
pageToSource :: (MonadBaseControl IO m, Monad m) => PageResult m a -> Source m aSource
Convenience layer: Convert a pagination scheme to a conduit Source
.
Helpers
A typeclass to enable using any string-like type for row and column keys
toColKey :: a -> ByteStringSource
fromColKey :: ByteString -> Either String aSource
CKey String | |
CKey ByteString | |
CKey ByteString | |
CKey Text | |
CKey Text | |
CKey [ByteString] | For easy composite keys, just serialize your data type to a list of bytestrings, we'll concat them and turn them into column keys. |
fromColKey' :: CKey a => ByteString -> aSource
Raise an error if conversion fails
Cassandra Column Key Types
module Database.Cassandra.Pack