cassy-0.5.1.0: A high level driver for the Cassandra datastore

Stabilityexperimental
MaintainerOzgun Ataman <oz@soostone.com>
Safe HaskellNone

Database.Cassandra.Marshall

Contents

Description

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.

Synopsis

Connection

type CPool = Pool CassandraSource

A round-robin pool of cassandra connections

type Server = (HostName, Int)Source

A (ServerName, Port) tuple

defServer :: ServerSource

A localhost server with default configuration

defServers :: [Server]Source

A single localhost server with default configuration

createCassandraPoolSource

Arguments

:: [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 CassandraExceptions at any point in time.

Instances

runCas :: CPool -> Cas a -> IO aSource

Main running function when using the ad-hoc Cas monad. Just write your cassandra actions within the Cas monad and supply them with a CPool to execute.

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

data Marshall a Source

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.)

Constructors

Marshall 

Fields

marshallEncode :: a -> ByteString

An encoding function

marshallDecode :: ByteString -> Either String a

A decoding function

casShow :: (Show a, Read a) => Marshall aSource

Marshall data using Show and Read. Not meant for serious production cases.

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

getSource

Arguments

:: (MonadCassandra m, CasType k) 
=> Marshall a 
-> ColumnFamily 
-> RowKey 
-> Selector

A slice selector

-> ConsistencyLevel 
-> m [(k, a)]

List of key-value pairs. See CasType for what key types you can use.

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.

get_Source

Arguments

:: MonadCassandra m 
=> Marshall a 
-> ColumnFamily 
-> RowKey 
-> Selector

A slice selector

-> ConsistencyLevel 
-> m [a] 

A version of get that discards the column names for the common scenario. Useful because you would otherwise be forced to manually supply type signatures to get rid of the CasType ambiguity.

getColSource

Arguments

:: (MonadCassandra m, CasType k) 
=> Marshall a 
-> ColumnFamily 
-> RowKey 
-> k

Column name; anything in CasType

-> 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.

insertColSource

Arguments

:: (MonadCassandra m, CasType k) 
=> Marshall a 
-> ColumnFamily 
-> RowKey 
-> k

Column name. See CasType for what you can use here.

-> ConsistencyLevel 
-> a

Content

-> m () 

insertColTTLSource

Arguments

:: (MonadCassandra m, CasType k) 
=> Marshall a 
-> ColumnFamily 
-> RowKey 
-> k

Column name. See CasType for what you can use here.

-> ConsistencyLevel 
-> a

Content

-> Int32

TTL for this column

-> m () 

modifySource

Arguments

:: (MonadCassandra m, CasType k) 
=> Marshall a

A serialization methodology. Example: casJSON

-> ColumnFamily 
-> RowKey 
-> k

Column name; anything in CasType

-> ConsistencyLevel

Read quorum

-> ConsistencyLevel

Write quorum

-> (Maybe a -> m (ModifyOperation a, b))

Modification function. Called with Just the value if present, Nothing otherwise.

-> m b

Return the decided ModifyOperation and its execution outcome

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.

modify_Source

Arguments

:: (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 Just the value if present, Nothing otherwise.

-> m () 

Same as modify but does not offer a side value.

This method may throw a CassandraException for all exceptions other than NotFoundException.

deleteSource

Arguments

:: MonadCassandra m 
=> ColumnFamily

In ColumnFamily

-> RowKey

Key to be deleted

-> Selector

Columns to be deleted

-> ConsistencyLevel 
-> m () 

Same as the delete in the Basic module, except that it throws an exception rather than returning an explicit Either value.

Retrying Queries

retryCasSource

Arguments

:: MonadCatchIO m 
=> RetrySettings

For default settings, just use def

-> 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

data ModifyOperation a Source

Possible outcomes of a modify operation

Constructors

Update a 
Delete 
DoNothing 

Instances

Filtering

data Selector Source

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.

Constructors

All

Return everything in Row

forall a . CasType a => ColNames [a]

Return specific columns or super-columns depending on the ColumnFamily

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.

range :: SelectorSource

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

data Order Source

Order in a range query

Constructors

Regular 
Reversed 

Instances

data KeySelector Source

A Key range selector to use with getMulti.

Constructors

Keys [Key]

Just a list of keys to get

KeyRange KeyRangeType Key Key Int32

A range of keys to get. Remember that RandomPartitioner ranges may not mean much as keys are randomly assigned to nodes.

Instances

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.

Constructors

InclusiveRange 
WrapAround 

Instances

Pagination

data PageResult m a Source

Describes the result of a single pagination action

Constructors

PDone

Done, this is all I have.

Fields

pCache :: [a]
 
PMore

Here's a batch and there is more when you call the action.

Fields

pCache :: [a]
 
pMore :: m (PageResult m a)
 

Instances

paginateSource

Arguments

:: (MonadCassandra m, MonadCatchIO m, CasType k) 
=> Marshall a

Serialization strategy

-> ColumnFamily 
-> RowKey

Paginate columns of this row

-> Selector

Range selector to initially and repeatedly apply.

-> ConsistencyLevel 
-> RetrySettings

Retry strategy for each underlying Cassandra call

-> m (PageResult m (k, a)) 

Paginate over columns in a given key, repeatedly applying the given Selector. The Selector must be a Range selector, or else this funtion will raise an exception.

paginateSource :: (CasType k, MonadCatchIO m, MonadCassandra m) => Marshall a -> ColumnFamily -> RowKey -> Selector -> ConsistencyLevel -> RetrySettings -> Source m (k, a)Source

Just like paginate, but we instead return a conduit Source.

pageToSource :: (MonadCatchIO m, Monad m) => PageResult m a -> Source m aSource

Convenience layer: Convert a pagination scheme to a conduit Source.

Helpers

class CKey a whereSource

A typeclass to enable using any string-like type for row and column keys

Instances

CKey String 
CKey ByteString 
CKey Text 
CKey ByteString 
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