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

Safe HaskellNone

Database.Cassandra.CQL

Contents

Description

Haskell client for Cassandra's CQL protocol

For examples, take a look at the tests directory in the source archive.

Here's the correspondence between CQL and Haskell types:

...and you can define your own CasType instances to extend these types, which is a very powerful way to write your code.

One way to do things is to specify your queries with a type signature, like this:

 createSongs :: Query Schema () ()
 createSongs = "create table songs (id uuid PRIMARY KEY, title text, artist text, comment text)"

 insertSong :: Query Write (UUID, Text, Text, Maybe Text) ()
 insertSong = "insert into songs (id, title, artist, comment) values (?, ?, ?)"

 getOneSong :: Query Rows UUID (Text, Text, Maybe Text)
 getOneSong = "select title, artist, comment from songs where id=?"

The three type parameters are the query type (Schema, Write or Rows) followed by the input and output types, which are given as tuples whose constituent types must match the ones in the query CQL. If you do not match them correctly, you'll get a runtime error when you execute the query. If you do, then the query becomes completely type safe.

Types can be Maybe types, in which case you can read and write a Cassandra 'null' in the table. Cassandra allows any column to be null, but you can lock this out by specifying non-Maybe types.

The query types are:

  • Schema for modifications to the schema. The output tuple type must be ().
  • Write for row inserts and updates, and such. The output tuple type must be ().
  • Rows for selects that give a list of rows in response.

The functions to use for these query types are executeSchema, executeWrite and executeRows or executeRow respectively.

The following pattern seems to work very well, especially along with your own CasType instances, because it neatly hides the mechanics from the body of your code:

 insertSong :: UUID -> Text -> Text -> Maybe Text -> Cas ()
 insertSong id title artist comment = executeWrite QUORUM q (id, title, artist, comment)
      where q = "insert into songs (id, title, artist, comment) values (?, ?, ?, ?)"

To do

  • Add credentials.
  • Improve connection pooling.
  • Add the ability to easily run queries in parallel.

Synopsis

Initialization

newtype Keyspace Source

The name of a Cassandra keyspace. See the Cassandra documentation for more information.

Constructors

Keyspace Text 

data Pool Source

A handle for the state of the connection pool.

newPool :: [Server] -> Keyspace -> IO PoolSource

Construct a pool of Cassandra connections.

Cassandra monad

data Cas a Source

The monad used to run Cassandra queries in.

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

Execute Cassandra queries.

data CassandraCommsError Source

All errors at the communications level are reported with this exception (IOExceptions from socket I/O are always wrapped), and this exception typically would mean that a retry is warranted.

Note that this exception isn't guaranteed to be a transient one, so a limit on the number of retries is likely to be a good idea. LocalProtocolError probably indicates a corrupted database or driver bug.

Queries

data Query Source

The text of a CQL query, along with type parameters to make the query type safe. The type arguments are Style, followed by input and output column types for the query each represented as a tuple.

The DataKinds language extension is required for Style.

Instances

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

data Style Source

The first type argument for Query. Tells us what kind of query it is.

Constructors

Schema

A query that modifies the schema, such as DROP TABLE or CREATE TABLE

Write

A query that writes data, such as an INSERT or UPDATE

Rows

A query that returns a list of rows, such as SELECT

query :: Text -> Query style i oSource

Construct a query. Another way to construct one is as an overloaded string through the IsString instance if you turn on the OverloadedStrings language extension, e.g.

 {-# LANGUAGE OverloadedStrings #-}
 ...

 getOneSong :: Query Rows UUID (Text, Text, Maybe Text)
 getOneSong = "select title, artist, comment from songs where id=?"

Executing queries

data Consistency Source

Cassandra consistency level. See the Cassandra documentation for an explanation.

data Change Source

Constructors

CREATED 
UPDATED 
DROPPED 

Instances

executeSchemaSource

Arguments

:: (MonadCassandra m, CasValues i) 
=> Consistency 
-> Query Schema i ()

CQL query to execute

-> i

Input values substituted in the query

-> m (Change, Keyspace, Table) 

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

executeWriteSource

Arguments

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

CQL query to execute

-> i

Input values substituted in the query

-> m () 

Execute a write operation that returns void.

executeRowsSource

Arguments

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

CQL query to execute

-> i

Input values substituted in the query

-> m [o] 

Execute a query that returns rows.

executeRowSource

Arguments

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

CQL query to execute

-> i

Input values substituted in the query

-> m (Maybe o) 

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

Value types

newtype Blob Source

If you wrap this round a ByteString, it will be treated as a blob type instead of ascii (if it was a plain ByteString type).

Constructors

Blob 

Fields

unBlob :: ByteString
 

newtype Counter Source

A Cassandra distributed counter value.

Constructors

Counter 

Fields

unCounter :: Int64
 

newtype TimeUUID Source

If you wrap this round a UUID then it is treated as a timeuuid type instead of uuid (if it was a plain UUID type).

Constructors

TimeUUID 

Fields

unTimeUUID :: UUID
 

metadataTypes :: Metadata -> [CType]Source

A helper for extracting the types from a metadata definition.

class CasType a whereSource

A type class for types that can be used in query arguments or column values in returned results.

To define your own newtypes for Cassandra data, you only need to define getCas, putCas and casType, like this:

 instance CasType UserId where
     getCas = UserId <$> getCas
     putCas (UserId i) = putCas i
     casType (UserId i) = casType i

If you have a more complex type you want to store as a Cassandra blob, you could write an instance like this (assuming we're it's an instance of the cereal package's Serialize class):

 instance CasType User where
     getCas = decode . unBlob <$> getCas
     putCas = putCas . Blob . encode
     casType _ = CBlob

Methods

getCas :: Get aSource

putCas :: a -> PutSource

casType :: a -> CTypeSource

For a given Haskell type given as (undefined :: a), tell the caller how Cassandra represents it.

casNothing :: aSource

casObliterate :: a -> ByteString -> Maybe ByteStringSource

class CasValues v whereSource

A type class for a tuple of CasType instances, representing either a list of arguments for a query, or the values in a row of returned query results.

Methods

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

decodeValues :: [(CType, Maybe 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) 

Lower-level interfaces

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

A low-level function in case you need some rarely-used capabilities.

data Result vs Source

A low-level query result used with executeRaw.

Instances

Functor Result 
Show vs => Show (Result vs) 

data TableSpec Source

A fully qualified identification of a table that includes the Keyspace.

Constructors

TableSpec Keyspace Table 

data ColumnSpec Source

Information about a table column.

Instances

data Metadata Source

The specification of a list of result set columns.

Constructors

Metadata [ColumnSpec] 

Instances

newtype Table Source

The name of a Cassandra table (a.k.a. column family).

Constructors

Table Text