cql-3.1.1: Cassandra CQL binary protocol.

Safe HaskellNone
LanguageHaskell2010

Database.CQL.Protocol

Contents

Description

The CQL native protocol is a binary frame-based protocol where each frame has a Header, a Length and a body. The protocol distinguishes Requests and Responses.

Some usage examples:

Constructing and Serialising a Request

let q = QueryString "select peer from system.peers where data_center = ? and rack = ?"
    p = QueryParams One False ("uk-1", "r-0") Nothing Nothing Nothing
    r = RqQuery (Query q p :: Query R (Text, Text) (Identity IP))
    i = mkStreamId 0
in pack V3 noCompression False i r

Deserialising a Response

-- assuming bh contains the raw header byte string and bb the raw
-- body byte string.
case header V3 bh of
    Left  e -> ...
    Right h -> unpack noCompression h bb

A generic query processing function

query :: (Tuple a, Tuple b) => Version -> Socket -> QueryString k a b -> QueryParams a -> IO (Response k a b)
query v s q p = do
    let i = mkStreamId 0
    sendToServer s (pack v noCompression False i (RqQuery (Query q p)))
    b <- recv (if v == V3 then 9 else 8) s
    h <- either (throwIO . MyException) return (header v b)
    when (headerType h == RqHeader) $
        throwIO UnexpectedRequestHeader
    let len = lengthRepr (bodyLength h)
    x <- recv (fromIntegral len) s
    case unpack noCompression h x of
        Left e              -> throwIO $ AnotherException e
        Right (RsError _ e) -> throwIO e
        Right response      -> return response

Synopsis

Cql type-class

class Cql a where Source #

A type that can be converted from and to some CQL Value.

This type-class is used to map custom types to Cassandra data-types. For example:

newtype MyType = MyType Int32

instance Cql MyType where
    ctype              = Tagged IntColumn
    toCql (MyType i)   = CqlInt i
    fromCql (CqlInt i) = Right (MyType i)
    fromCql _          = Left "Expected CqlInt"

Minimal complete definition

ctype, toCql, fromCql

Methods

ctype :: Tagged a ColumnType Source #

the column-type of a

toCql :: a -> Value Source #

map a to some CQL data-type

fromCql :: Value -> Either String a Source #

map a CQL value back to a

Instances

Cql Bool Source # 
Cql Double Source # 
Cql Float Source # 
Cql Int32 Source # 
Cql Int64 Source # 
Cql Integer Source # 
Cql Decimal Source # 
Cql IP Source # 
Cql Text Source # 
Cql UTCTime Source # 
Cql UUID Source # 
Cql TimeUuid Source # 
Cql Counter Source # 
Cql Blob Source # 
Cql Ascii Source # 
Cql a => Cql [a] Source # 
Cql a => Cql (Maybe a) Source #

Please note that due to the fact that Cassandra internally represents empty collection type values (i.e. lists, maps and sets) as null, we can not distinguish Just [] from Nothing on response decoding.

Cql a => Cql (Set a) Source # 
(Cql a, Cql b) => Cql (Map a b) Source # 

Basic type definitions

newtype Keyspace Source #

Constructors

Keyspace 

Fields

newtype Table Source #

Constructors

Table 

Fields

Instances

Eq Table Source # 

Methods

(==) :: Table -> Table -> Bool #

(/=) :: Table -> Table -> Bool #

Show Table Source # 

Methods

showsPrec :: Int -> Table -> ShowS #

show :: Table -> String #

showList :: [Table] -> ShowS #

newtype PagingState Source #

Opaque token passed to the server to continue result paging.

Constructors

PagingState 

newtype QueryId k a b Source #

ID representing a prepared query.

Constructors

QueryId 

Instances

Eq (QueryId k a b) Source # 

Methods

(==) :: QueryId k a b -> QueryId k a b -> Bool #

(/=) :: QueryId k a b -> QueryId k a b -> Bool #

Show (QueryId k a b) Source # 

Methods

showsPrec :: Int -> QueryId k a b -> ShowS #

show :: QueryId k a b -> String #

showList :: [QueryId k a b] -> ShowS #

newtype QueryString k a b Source #

Constructors

QueryString 

Fields

Instances

Eq (QueryString k a b) Source # 

Methods

(==) :: QueryString k a b -> QueryString k a b -> Bool #

(/=) :: QueryString k a b -> QueryString k a b -> Bool #

Show (QueryString k a b) Source # 

Methods

showsPrec :: Int -> QueryString k a b -> ShowS #

show :: QueryString k a b -> String #

showList :: [QueryString k a b] -> ShowS #

IsString (QueryString k a b) Source # 

Methods

fromString :: String -> QueryString k a b #

data Version Source #

CQL binary protocol version.

Constructors

V2

version 2

V3

version 3

data CqlVersion Source #

The CQL version (not the binary protocol version).

Constructors

Cqlv300 
CqlVersion !Text 

newtype Blob Source #

Constructors

Blob 

Fields

Instances

newtype Set a Source #

Constructors

Set 

Fields

Instances

Show a => Show (Set a) Source # 

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Cql a => Cql (Set a) Source # 

newtype Map a b Source #

Constructors

Map 

Fields

Instances

(Show b, Show a) => Show (Map a b) Source # 

Methods

showsPrec :: Int -> Map a b -> ShowS #

show :: Map a b -> String #

showList :: [Map a b] -> ShowS #

(Cql a, Cql b) => Cql (Map a b) Source # 

data Value Source #

A CQL value. The various constructors correspond to CQL data-types for individual columns in Cassandra.

Instances

Eq Value Source # 

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Show Value Source # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

newtype Tagged a b Source #

Tag some value with a phantom type.

Constructors

Tagged 

Fields

retag :: Tagged a c -> Tagged b c Source #

data R Source #

data W Source #

data S Source #

Header

data Header Source #

Protocol frame header.

Instances

data HeaderType Source #

Constructors

RqHeader

A request frame header.

RsHeader

A response frame header.

header :: Version -> ByteString -> Either String Header Source #

Deserialise a frame header using the version specific decoding format.

Length

newtype Length Source #

The type denoting a protocol frame length.

Constructors

Length 

Fields

Instances

StreamId

data StreamId Source #

Streams allow multiplexing of requests over a single communication channel. The StreamId correlates Requests with Responses.

mkStreamId :: Integral i => i -> StreamId Source #

Create a StreamId from the given integral value. In version 2, a StreamId is an Int8 and in version 3 an Int16.

fromStreamId :: StreamId -> Int Source #

Convert the stream ID to an integer.

Flags

data Flags Source #

Type representing header flags. Flags form a monoid and can be used as in compress <> tracing <> mempty.

Instances

compress :: Flags Source #

Compression flag. If set, the frame body is compressed.

tracing :: Flags Source #

Tracing flag. If a request support tracing and the tracing flag was set, the response to this request will have the tracing flag set and contain tracing information.

isSet :: Flags -> Flags -> Bool Source #

Check if a particular flag is present.

Request

data Request k a b Source #

The type corresponding to the protocol request frame.

The type parameter k denotes the kind of request. It is present to allow distinguishing read operations from write operations. Use R for read, W for write and S for schema related operations.

a represents the argument type and b the return type of this request.

Instances

Show a => Show (Request k a b) Source # 

Methods

showsPrec :: Int -> Request k a b -> ShowS #

show :: Request k a b -> String #

showList :: [Request k a b] -> ShowS #

getOpCode :: Request k a b -> OpCode Source #

Get the protocol OpCode corresponding to the given Request.

pack Source #

Arguments

:: Tuple a 
=> Version

protocol version, which determines the encoding

-> Compression

compression to use

-> Bool

enable/disable tracing

-> StreamId

the stream Id to use

-> Request k a b

the actual request to serialise

-> Either String ByteString 

Serialise the given request, optionally using compression. The result is either an error description in case of failure or a binary protocol frame, including Header, Length and body.

Options

data Options Source #

An options request, send prior to Startup to request the server's startup options.

Constructors

Options 

Instances

Startup

data Startup Source #

A startup request which is used when initialising a connection to the server. It specifies the CQL version to use and optionally the compression algorithm.

Instances

Auth Response

newtype AuthResponse Source #

A request send in response to a previous authentication challenge.

Constructors

AuthResponse ByteString 

Register

newtype Register Source #

Register's the connection this request is made through, to receive server events.

Constructors

Register [EventType] 

data EventType Source #

Event types to register.

Constructors

TopologyChangeEvent

events related to change in the cluster topology

StatusChangeEvent

events related to change of node status

SchemaChangeEvent

events related to schema change

Query

data Query k a b Source #

A CQL query (select, insert, etc.).

Constructors

Query !(QueryString k a b) !(QueryParams a) 

Instances

Show a => Show (Query k a b) Source # 

Methods

showsPrec :: Int -> Query k a b -> ShowS #

show :: Query k a b -> String #

showList :: [Query k a b] -> ShowS #

data QueryParams a Source #

Query parameters.

Constructors

QueryParams 

Fields

Instances

data SerialConsistency Source #

Consistency level for the serial phase of conditional updates.

Batch

data Batch Source #

Allows executing a list of queries (prepared or not) as a batch.

Instances

data BatchQuery where Source #

A GADT to unify queries and prepared queries both of which can be used in batch requests.

Constructors

BatchQuery :: (Show a, Tuple a, Tuple b) => !(QueryString W a b) -> !a -> BatchQuery 
BatchPrepared :: (Show a, Tuple a, Tuple b) => !(QueryId W a b) -> !a -> BatchQuery 

data BatchType Source #

Constructors

BatchLogged

default, uses a batch log for atomic application

BatchUnLogged

skip the batch log

BatchCounter

used for batched counter updates

Prepare

newtype Prepare k a b Source #

Prepare a query for later execution (cf. Execute).

Constructors

Prepare (QueryString k a b) 

Instances

Show (Prepare k a b) Source # 

Methods

showsPrec :: Int -> Prepare k a b -> ShowS #

show :: Prepare k a b -> String #

showList :: [Prepare k a b] -> ShowS #

Execute

data Execute k a b Source #

Executes a prepared query.

Constructors

Execute !(QueryId k a b) !(QueryParams a) 

Instances

Show a => Show (Execute k a b) Source # 

Methods

showsPrec :: Int -> Execute k a b -> ShowS #

show :: Execute k a b -> String #

showList :: [Execute k a b] -> ShowS #

Response

data Response k a b Source #

The type corresponding to the protocol response frame.

The type parameter k denotes the kind of response. It is present to allow distinguishing read operations from write operations. Use R for read, W for write and S for schema related operations.

a represents the argument type and b the return type of this response.

Instances

Show b => Show (Response k a b) Source # 

Methods

showsPrec :: Int -> Response k a b -> ShowS #

show :: Response k a b -> String #

showList :: [Response k a b] -> ShowS #

unpack :: (Tuple a, Tuple b) => Compression -> Header -> ByteString -> Either String (Response k a b) Source #

Deserialise a Response from the given ByteString.

Ready

data Ready Source #

The server is ready to process queries. Response of a Startup request.

Constructors

Ready 

Instances

Authenticate

newtype Authenticate Source #

The server requires authentication.

Constructors

Authenticate Text 

newtype AuthChallenge Source #

A server-send authentication challenge.

newtype AuthSuccess Source #

Indicates the success of an authentication phase.

Constructors

AuthSuccess (Maybe ByteString) 

Result

data Result k a b Source #

Query response.

Instances

Show b => Show (Result k a b) Source # 

Methods

showsPrec :: Int -> Result k a b -> ShowS #

show :: Result k a b -> String #

showList :: [Result k a b] -> ShowS #

data MetaData Source #

Part of a RowsResult. Describes the result set.

data ColumnSpec Source #

The column specification. Part of MetaData unless skipMetaData in QueryParams was True.

Constructors

ColumnSpec 

Supported

data Supported Source #

The startup options supported by the server. Response of an Options request.

Event

data Event Source #

Messages send by the server without request, if the connection has been Registered to receive such events.

Instances

Error

Row, Tuple and Record

class PrivateTuple a => Tuple a Source #

Instances

count :: PrivateTuple a => Tagged a Int Source #

check :: PrivateTuple a => Tagged a ([ColumnType] -> [ColumnType]) Source #

tuple :: PrivateTuple a => Version -> [ColumnType] -> Get a Source #

store :: PrivateTuple a => Version -> Putter a Source #

data Row Source #

A row is a vector of Values.

Instances

Eq Row Source # 

Methods

(==) :: Row -> Row -> Bool #

(/=) :: Row -> Row -> Bool #

Show Row Source # 

Methods

showsPrec :: Int -> Row -> ShowS #

show :: Row -> String #

showList :: [Row] -> ShowS #

Tuple Row Source # 

fromRow :: Cql a => Int -> Row -> Either String a Source #

Convert a row element.

class Record a where Source #

Record/Tuple conversion. For example:

data Peer = Peer
    { peerAddr :: IP
    , peerRPC  :: IP
    , peerDC   :: Text
    , peerRack :: Text
    } deriving Show

recordInstance ''Peer

map asRecord <$> performQuery "SELECT peer, rpc_address, data_center, rack FROM system.peers"

The generated type-class instance maps between record and tuple constructors:

type instance TupleType Peer = (IP, IP, Text, Text)

instance Record Peer where
    asTuple (Peer a b c d) = (a, b, c, d)
    asRecord (a, b, c, d)  = Peer a b c d

Minimal complete definition

asTuple, asRecord

Methods

asTuple :: a -> TupleType a Source #

asRecord :: TupleType a -> a Source #

type family TupleType a Source #