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

Safe HaskellNone

Database.Cassandra.JSON

Contents

Description

A higher level module for working with Cassandra.

All row and column keys are standardized to be of strict types. Row keys are Text, while Column keys are ByteString. This might change in the future and we may revert to entirely ByteString keys.

Serialization and de-serialization of Column values are taken care of automatically using the ToJSON and FromJSON typeclasses.

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

getSource

Arguments

:: (MonadCassandra m, FromJSON a, CasType k) 
=> 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, FromJSON 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, FromJSON a, CasType k) 
=> ColumnFamily 
-> RowKey 
-> k

Column name; anything in CasType

-> ConsistencyLevel 
-> m (Maybe a) 

Get a single column from a single row

getMulti :: (MonadCassandra m, FromJSON 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, ToJSON a, CasType k) 
=> ColumnFamily 
-> RowKey 
-> k

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

-> ConsistencyLevel 
-> a

Content

-> m () 

insertColTTLSource

Arguments

:: (MonadCassandra m, ToJSON a, CasType k) 
=> 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, ToJSON a, FromJSON a, CasType k) 
=> 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, ToJSON a, FromJSON a, CasType k) 
=> 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.

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

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

Working with column types

class CasType a whereSource

This typeclass defines and maps to haskell types that Cassandra natively knows about and uses in sorting and potentially validating column key values.

All column keys are eventually sent to and received from Cassandra in binary form. This typeclass allows us to map some Haskell type definitions to their binary representation. The correct binary serialization is handled for you behind the scenes.

For simplest cases, just use one of the string-like instances, e.g. ByteString, String or Text. Please keep in mind that these are just mapped to untyped BytesType.

Remember that for special column types, such as TLong, to have any effect, your ColumnFamily must have been created with that comparator or validator. Otherwise you're just encoding/decoding integer values without any Cassandra support for sorting or correctness.

The Python library pycassa has a pretty good tutorial to learn more.

Tuple instances support fixed ComponentType columns. Example:

 insert "testCF" "row1" [packCol ((TLong 124, TAscii "Hello"), "some content")]

Instances

CasType Int 
CasType String 
CasType ByteString 
CasType Text 
CasType UTCTime

Via TTimeStamp, which is via TLong

CasType ByteString 
CasType Text 
CasType Day

Encode days as LongType via TLong.

CasType TTimeStamp 
CasType TUtf8

Encode and decode as Utf8 Text

CasType TLong

Pack as an 8 byte unsigned number; negative signs are lost. Maps to LongType.

CasType TInt

Pack as an 8 byte number - same as TLong

CasType TInt32

Pack as a 4 byte number

CasType TCounter 
CasType TBytes 
CasType TAscii 
(CasType a, CasType b) => CasType (SliceStart (a, b))

Composite types - see Cassandra or pycassa docs to understand

(CasType a, CasType b, CasType c) => CasType (SliceStart (a, b, c)) 
(CasType a, CasType b, CasType c, CasType d) => CasType (SliceStart (a, b, c, d)) 
CasType a => CasType (SliceStart (Single a)) 
CasType a => CasType (Single a)

Use the Single wrapper when querying only with the first of a two or more field CompositeType.

CasType a => CasType (Exclusive (Single a)) 
(CasType a, CasType b) => CasType (a, Exclusive b) 
(CasType a, CasType b) => CasType (a, b)

Composite types - see Cassandra or pycassa docs to understand

(CasType a, CasType b, CasType c) => CasType (a, b, Exclusive c) 
(CasType a, CasType b, CasType c) => CasType (a, b, c) 
(CasType a, CasType b, CasType c, CasType d) => CasType (a, b, c, Exclusive d) 
(CasType a, CasType b, CasType c, CasType d) => CasType (a, b, c, d) 

newtype TAscii Source

Constructors

TAscii 

Fields

getAscii :: ByteString
 

newtype TBytes Source

Constructors

TBytes 

newtype TInt Source

Constructors

TInt 

Fields

getInt :: Integer
 

Instances

Enum TInt 
Eq TInt 
Integral TInt 
Num TInt 
Ord TInt 
Read TInt 
Real TInt 
Show TInt 
CasType TInt

Pack as an 8 byte number - same as TLong

newtype TInt32 Source

Constructors

TInt32 

Fields

getInt32 :: Int32
 

Instances

Eq TInt32 
Ord TInt32 
Read TInt32 
Show TInt32 
CasType TInt32

Pack as a 4 byte number

newtype TUtf8 Source

Constructors

TUtf8 

Fields

getUtf8 :: Text
 

Instances

Eq TUtf8 
Ord TUtf8 
Read TUtf8 
Show TUtf8 
CasType TUtf8

Encode and decode as Utf8 Text

newtype TUUID Source

Constructors

TUUID 

Fields

getUUID :: ByteString
 

newtype TLong Source

Constructors

TLong 

Fields

getLong :: Integer
 

Instances

Enum TLong 
Eq TLong 
Integral TLong 
Num TLong 
Ord TLong 
Read TLong 
Real TLong 
Show TLong 
CasType TLong

Pack as an 8 byte unsigned number; negative signs are lost. Maps to LongType.

newtype Exclusive a Source

Exclusive tag for composite column. You may tag the end of a composite range with this to make the range exclusive. See pycassa documentation for more information.

Constructors

Exclusive a 

Instances

Eq a => Eq (Exclusive a) 
Ord a => Ord (Exclusive a) 
Read a => Read (Exclusive a) 
Show a => Show (Exclusive a) 
CasType a => CasType (Exclusive (Single a)) 
(CasType a, CasType b) => CasType (a, Exclusive b) 
(CasType a, CasType b, CasType c) => CasType (a, b, Exclusive c) 
(CasType a, CasType b, CasType c, CasType d) => CasType (a, b, c, Exclusive d)