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

Stabilityexperimental
MaintainerOzgun Ataman
Safe HaskellNone

Database.Cassandra.Basic

Contents

Description

Low-level functionality for working with Cassandra at the most basic level.

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

Cassandra Operations

getColSource

Arguments

:: (MonadCassandra m, CasType k) 
=> ColumnFamily 
-> ByteString

Row key

-> k

Column/SuperColumn key; see CasType for what it can be. Use ByteString in the simple case.

-> ConsistencyLevel

Read quorum

-> m (Maybe Column) 

Get a single key-column value.

getSource

Arguments

:: MonadCassandra m 
=> ColumnFamily

in ColumnFamily

-> ByteString

Row key to get

-> Selector

Slice columns with selector

-> ConsistencyLevel 
-> m [Column] 

An arbitrary get operation - slice with Selector

getMultiSource

Arguments

:: MonadCassandra m 
=> ColumnFamily 
-> KeySelector

A selection of rows to fetch in one hit

-> Selector

Subject to column selector conditions

-> ConsistencyLevel 
-> m (Map ByteString Row)

A Map from Row keys to Rows is returned

Do multiple gets in one DB hit

insertSource

Arguments

:: MonadCassandra m 
=> ColumnFamily 
-> ByteString

Row key

-> ConsistencyLevel 
-> [Column]

best way to make these columns is through packCol

-> m () 

Insert an entire row into the db.

This will do as many round-trips as necessary to insert the full row. Please keep in mind that each column and each column of each super-column is sent to the server one by one.

 insert "testCF" "row1" ONE [packCol ("column key", "some column content")]

deleteSource

Arguments

:: MonadCassandra m 
=> ColumnFamily

In ColumnFamily

-> Key

Key to be deleted

-> Selector

Columns to be deleted

-> ConsistencyLevel 
-> m () 

Delete an entire row, specific columns or a specific sub-set of columns within a SuperColumn.

Retrying Queries

retryCasSource

Arguments

:: (MonadCatch m, MonadIO m) 
=> RetryPolicy

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

networkRetryH :: Monad m => Int -> Handler m BoolSource

IOExceptions should be retried

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

Exceptions

Utility

getTime :: IO Int64Source

Cassandra is VERY sensitive to its timestamp values. As a convention, timestamps are always in microseconds

throwing :: IO (Either CassandraException a) -> IO aSource

Make exceptions implicit.

wrapException :: IO a -> IO aSource

Wrap exceptions of the underlying thrift library into the exception types defined here.

Basic Types

data Column Source

A Column is either a single key-value pair or a SuperColumn with an arbitrary number of key-value pairs

Constructors

SuperColumn ColumnName [Column] 
Column 

Fields

colKey :: ColumnName
 
colVal :: Value
 
colTS :: Maybe Int64

Last update timestamp; will be overridden during write/update ops

colTTL :: Maybe Int32

A TTL after which Cassandra will erase the column

col :: ByteString -> ByteString -> ColumnSource

A short-hand for creating key-value Column values. This is pretty low level; you probably want to use packCol.

packCol :: CasType k => (k, ByteString) -> ColumnSource

Pack key-value pair into Column form ready to be written to Cassandra

unpackCol :: CasType k => Column -> (k, Value)Source

Unpack a Cassandra Column into a more convenient (k,v) form

packKey :: CasType a => a -> ByteStringSource

Pack a column key into binary, ready for submission to Cassandra

type Row = [Column]Source

A full row is simply a sequence of columns

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