cassandra-cql-0.1.0.0: Haskell client for Cassandra's CQL protocol

Safe HaskellNone

Database.Cassandra.CQL

Contents

Description

Haskell client for Cassandra's CQL protocol

This module isn't properly documented yet. For now, take a look at tests/example.hs.

Credentials are not implemented yet.

Here's the correspondence between Haskell and CQL types. Not all Cassandra data types supported as yet: Haskell types listed below have been implemented.

Synopsis

Initialization

Monads

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

Type used in operations

data Result vs Source

Instances

Functor Result 
Show vs => Show (Result vs) 

data TableSpec Source

Constructors

TableSpec Keyspace Table 

Instances

data Metadata Source

Constructors

Metadata [ColumnSpec] 

Instances

data Change Source

Constructors

CREATED 
UPDATED 
DROPPED 

Instances

newtype Table Source

Constructors

Table Text 

Queries

data Query Source

Instances

Show (Query $a $b $c) 
IsString (Query style i o) 

query :: Text -> Query style i oSource

data Style Source

Constructors

Rows 
Write 
Schema 

Operations

executeRows :: (MonadCassandra m, CasValues i, CasValues o) => Consistency -> Query Rows i o -> i -> m [o]Source

Execute a query that returns rows

executeRow :: (MonadCassandra m, CasValues i, CasValues o) => Consistency -> Query Rows i o -> i -> m (Maybe o)Source

Helper for executeRows useful in situations where you are only expecting one row to be returned.

executeWrite :: (MonadCassandra m, CasValues i) => Consistency -> Query Write i () -> i -> m ()Source

Execute a write operation that returns void

executeSchema :: (MonadCassandra m, CasValues i) => Consistency -> Query Schema i () -> i -> m (Change, Keyspace, Table)Source

Execute a schema change, such as creating or dropping a table.

executeRaw :: (MonadCassandra m, CasValues i) => Query style any_i any_o -> i -> Consistency -> m (Result [ByteString])Source

Value types

class CasValues v whereSource

Methods

encodeValues :: v -> [CType] -> Either CodingFailure [ByteString]Source

decodeValues :: [(CType, ByteString)] -> Either CodingFailure vSource

Instances

CasValues () 
CasType a => CasValues a 
(CasType a, CasType b) => CasValues (a, b) 
(CasType a, CasType b, CasType c) => CasValues (a, b, c) 
(CasType a, CasType b, CasType c, CasType d) => CasValues (a, b, c, d) 
(CasType a, CasType b, CasType c, CasType d, CasType e) => CasValues (a, b, c, d, e) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f) => CasValues (a, b, c, d, e, f) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g) => CasValues (a, b, c, d, e, f, g) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h) => CasValues (a, b, c, d, e, f, g, h) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i) => CasValues (a, b, c, d, e, f, g, h, i) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j) => CasValues (a, b, c, d, e, f, g, h, i, j) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k) => CasValues (a, b, c, d, e, f, g, h, i, j, k) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k, CasType l) => CasValues (a, b, c, d, e, f, g, h, i, j, k, l) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k, CasType l, CasType m) => CasValues (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k, CasType l, CasType m, CasType n) => CasValues (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k, CasType l, CasType m, CasType n, CasType o) => CasValues (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k, CasType l, CasType m, CasType n, CasType o, CasType p) => CasValues (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k, CasType l, CasType m, CasType n, CasType o, CasType p, CasType q) => CasValues (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k, CasType l, CasType m, CasType n, CasType o, CasType p, CasType q, CasType r) => CasValues (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k, CasType l, CasType m, CasType n, CasType o, CasType p, CasType q, CasType r, CasType s) => CasValues (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) 
(CasType a, CasType b, CasType c, CasType d, CasType e, CasType f, CasType g, CasType h, CasType i, CasType j, CasType k, CasType l, CasType m, CasType n, CasType o, CasType p, CasType q, CasType r, CasType s, CasType t) => CasValues (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) 

newtype Blob Source

Constructors

Blob ByteString