Safe Haskell | None |
---|---|
Language | Haskell98 |
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:
- ascii -
ByteString
- bigint -
Int64
- blob -
Blob
- boolean -
Bool
- counter -
Counter
- decimal -
Decimal
- double -
Double
- float -
Float
- int -
Int
- text / varchar -
Text
- timestamp -
UTCTime
- uuid -
UUID
- varint -
Integer
- timeuuid -
TimeUUID
- inet -
SockAddr
- list<a> - [a]
- map<a, b> -
Map
a b - set<a> -
Set
b
...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
, executeTrans
and executeRows
or executeRow
respectively.
The following pattern seems to work very well, especially along with your own CasType
instances, because it gives you a place to neatly add marshalling details that keeps
away 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 (?, ?, ?, ?)"
Incidentally, here's Haskell's little-known multi-line string syntax. You escape it using \ and then another \ where the string starts again.
str = "multi\ \line"
(gives "multiline")
To do
- Add the ability to easily run queries in parallel.
- Add support for batch queries.
- Add support for query paging.
- type Server = (HostName, ServiceName)
- newtype Keyspace = Keyspace Text
- data Pool
- newPool :: [Server] -> Keyspace -> Maybe Authentication -> IO Pool
- newPool' :: PoolConfig -> IO Pool
- defaultConfig :: [Server] -> Keyspace -> Maybe Authentication -> PoolConfig
- class MonadCatchIO m => MonadCassandra m where
- getCassandraPool :: m Pool
- data Cas a
- runCas :: Pool -> Cas a -> IO a
- data CassandraException
- = ServerError Text Text
- | ProtocolError Text Text
- | BadCredentials Text Text
- | UnavailableException Text Consistency Int Int Text
- | Overloaded Text Text
- | IsBootstrapping Text Text
- | TruncateError Text Text
- | WriteTimeout Text Consistency Int Int Text Text
- | ReadTimeout Text Consistency Int Int Bool Text
- | SyntaxError Text Text
- | Unauthorized Text Text
- | Invalid Text Text
- | ConfigError Text Text
- | AlreadyExists Text Keyspace Table Text
- | Unprepared Text PreparedQueryID Text
- data CassandraCommsError
- data TransportDirection
- data Authentication = PasswordAuthenticator UserId Password
- data Query :: Style -> * -> * -> *
- data Style
- query :: Text -> Query style i o
- data Consistency
- = ANY
- | ONE
- | TWO
- | THREE
- | QUORUM
- | ALL
- | LOCAL_QUORUM
- | EACH_QUORUM
- | SERIAL
- | LOCAL_SERIAL
- | LOCAL_ONE
- data Change
- executeSchema :: (MonadCassandra m, CasValues i) => Consistency -> Query Schema i () -> i -> m (Change, Keyspace, Table)
- executeWrite :: (MonadCassandra m, CasValues i) => Consistency -> Query Write i () -> i -> m ()
- executeRows :: (MonadCassandra m, CasValues i, CasValues o) => Consistency -> Query Rows i o -> i -> m [o]
- executeRow :: (MonadCassandra m, CasValues i, CasValues o) => Consistency -> Query Rows i o -> i -> m (Maybe o)
- executeTrans :: (MonadCassandra m, CasValues i) => Query Write i () -> i -> m Bool
- newtype Blob = Blob {
- unBlob :: ByteString
- newtype Counter = Counter {}
- newtype TimeUUID = TimeUUID {
- unTimeUUID :: UUID
- metadataTypes :: Metadata -> [CType]
- class CasType a where
- getCas :: Get a
- putCas :: a -> Put
- casType :: a -> CType
- casNothing :: a
- casObliterate :: a -> ByteString -> Maybe ByteString
- class CasValues v where
- encodeValues :: v -> [CType] -> Either CodingFailure [Maybe ByteString]
- decodeValues :: [(CType, Maybe ByteString)] -> Either CodingFailure v
- executeRaw :: (MonadCassandra m, CasValues i) => Query style any_i any_o -> i -> Consistency -> m (Result [Maybe ByteString])
- data Result vs
- data TableSpec = TableSpec Keyspace Table
- data ColumnSpec = ColumnSpec TableSpec Text CType
- data Metadata = Metadata [ColumnSpec]
- data CType
- newtype Table = Table Text
- newtype PreparedQueryID = PreparedQueryID ByteString
- serverStats :: Pool -> IO [ServerStat]
- data ServerStat = ServerStat {}
- data PoolConfig = PoolConfig {}
Initialization
type Server = (HostName, ServiceName) Source
The name of a Cassandra keyspace. See the Cassandra documentation for more information.
newPool :: [Server] -> Keyspace -> Maybe Authentication -> IO Pool Source
Construct a pool of Cassandra connections.
newPool' :: PoolConfig -> IO Pool Source
defaultConfig :: [Server] -> Keyspace -> Maybe Authentication -> PoolConfig Source
Cassandra monad
class MonadCatchIO m => MonadCassandra m where Source
getCassandraPool :: m Pool Source
MonadCassandra Cas | |
MonadCassandra m => MonadCassandra (ReaderT a m) | |
MonadCassandra m => MonadCassandra (StateT a m) | |
(MonadCassandra m, Error e) => MonadCassandra (ErrorT e m) | |
(MonadCassandra m, Monoid a) => MonadCassandra (WriterT a m) | |
(MonadCassandra m, Monoid w) => MonadCassandra (RWST r w s m) |
The monad used to run Cassandra queries in.
data CassandraException Source
An exception that indicates an error originating in the Cassandra server.
data CassandraCommsError Source
All errors at the communications level are reported with this exception
(IOException
s 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.
data TransportDirection Source
Auth
data Authentication Source
PasswordAuthenticator UserId Password |
Queries
The first type argument for Query. Tells us what kind of query it is.
query :: Text -> Query style i o Source
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.
:: (MonadCassandra m, CasValues i) | |
=> Consistency | Consistency level of the operation |
-> 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.
:: (MonadCassandra m, CasValues i) | |
=> Consistency | Consistency level of the operation |
-> Query Write i () | CQL query to execute |
-> i | Input values substituted in the query |
-> m () |
Execute a write operation that returns void.
:: (MonadCassandra m, CasValues i, CasValues o) | |
=> Consistency | Consistency level of the operation |
-> Query Rows i o | CQL query to execute |
-> i | Input values substituted in the query |
-> m [o] |
Execute a query that returns rows.
:: (MonadCassandra m, CasValues i, CasValues o) | |
=> Consistency | Consistency level of the operation |
-> 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.
:: (MonadCassandra m, CasValues i) | |
=> Query Write i () | CQL query to execute |
-> i | Input values substituted in the query |
-> m Bool |
Execute a lightweight transaction. The consistency level is implicit and is SERIAL.
Value types
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).
Blob | |
|
A Cassandra distributed counter value.
metadataTypes :: Metadata -> [CType] Source
A helper for extracting the types from a metadata definition.
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:
newtype UserId = UserId UUID deriving (Eq, Show) instance CasType UserId where getCas = UserId <$> getCas putCas (UserId i) = putCas i casType (UserId i) = casType i
The same can be done more simply using the GeneralizedNewtypeDeriving language extension, e.g.
{-# LANGUAGE GeneralizedNewtypeDeriving #-} ... newtype UserId = UserId UUID deriving (Eq, Show, CasType)
If you have a more complex type you want to store as a Cassandra blob, you could
write an instance like this (assuming 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
For a given Haskell type given as (undefined
:: a), tell the caller how Cassandra
represents it.
casNothing :: a Source
casObliterate :: a -> ByteString -> Maybe ByteString Source
CasType Bool | |
CasType Double | |
CasType Float | |
CasType Int | |
CasType Int64 | |
CasType Integer | |
CasType Decimal | |
CasType ByteString | |
CasType SockAddr | |
CasType Text | |
CasType UTCTime | |
CasType UUID | |
CasType TimeUUID | |
CasType Counter | |
CasType Blob | |
CasType a => CasType [a] | |
CasType a => CasType (Maybe a) | |
(CasType a, Ord a) => CasType (Set a) | |
(CasType a, Ord a, CasType b) => CasType (Map a b) |
class CasValues v where Source
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.
encodeValues :: v -> [CType] -> Either CodingFailure [Maybe ByteString] Source
decodeValues :: [(CType, Maybe ByteString)] -> Either CodingFailure v Source
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.
A low-level query result used with executeRaw
.
A fully qualified identification of a table that includes the Keyspace
.
data ColumnSpec Source
Information about a table column.
The specification of a list of result set columns.
Cassandra data types as used in metadata.
The name of a Cassandra table (a.k.a. column family).
newtype PreparedQueryID Source
serverStats :: Pool -> IO [ServerStat] Source
data ServerStat Source
Exported stats for a server.
data PoolConfig Source