Database.Cassandra.JSON
Description
A higher level module for working with Cassandra.
Row and Column keys can be any string-like type implementing the CKey typeclass. You can add your own types by defining new instances
Serialization and de-serialization of Column values are taken care of automatically using the ToJSON and FromJSON typeclasses.
Also, this module currently attempts to reduce verbosity by
throwing errors instead of returning Either types as in the
Database.Cassandra.Basic module.
- type CPool = Pool Cassandra Server
- type Server = (HostName, PortID)
- defServer :: Server
- defServers :: [Server]
- type KeySpace = String
- createCassandraPool :: [Server] -> Int -> NominalDiffTime -> KeySpace -> IO CPool
- class CKey a where
- toBS :: a -> ByteString
- fromBS :: ByteString -> a
- data ModifyOperation a
- type ColumnFamily = String
- data ConsistencyLevel
- = ONE
- | QUORUM
- | LOCAL_QUORUM
- | EACH_QUORUM
- | ALL
- | ANY
- | TWO
- | THREE
- data CassandraException
- get :: (CKey rowKey, CKey colKey, FromJSON a) => CPool -> ColumnFamily -> rowKey -> Selector -> ConsistencyLevel -> IO [(colKey, a)]
- getCol :: (CKey rowKey, CKey colKey, FromJSON a) => CPool -> ColumnFamily -> rowKey -> colKey -> ConsistencyLevel -> IO (Maybe a)
- insertCol :: (CKey rowKey, CKey colKey, ToJSON a) => CPool -> ColumnFamily -> rowKey -> colKey -> ConsistencyLevel -> a -> IO ()
- modify :: (CKey rowKey, CKey colKey, ToJSON a, FromJSON a) => CPool -> ColumnFamily -> rowKey -> colKey -> ConsistencyLevel -> ConsistencyLevel -> (Maybe a -> IO (ModifyOperation a, b)) -> IO b
- modify_ :: (CKey rowKey, CKey colKey, ToJSON a, FromJSON a) => CPool -> ColumnFamily -> rowKey -> colKey -> ConsistencyLevel -> ConsistencyLevel -> (Maybe a -> IO (ModifyOperation a)) -> IO ()
- delete :: CKey rowKey => CPool -> ColumnFamily -> rowKey -> Selector -> ConsistencyLevel -> IO ()
Connection
defServers :: [Server]Source
A single localhost server with default configuration
Arguments
| :: [Server] | List of servers to connect to |
| -> Int | Max connections per server (n) |
| -> 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.
Necessary Types
A typeclass to enable using any string-like type for row and column keys
Instances
data ModifyOperation a Source
Possible outcomes of a modify operation
Instances
| Eq a => Eq (ModifyOperation a) | |
| Ord a => Ord (ModifyOperation a) | |
| Read a => Read (ModifyOperation a) | |
| Show a => Show (ModifyOperation a) |
type ColumnFamily = StringSource
data ConsistencyLevel
Constructors
| ONE | |
| QUORUM | |
| LOCAL_QUORUM | |
| EACH_QUORUM | |
| ALL | |
| ANY | |
| TWO | |
| THREE |
data CassandraException Source
Cassandra Operations
get :: (CKey rowKey, CKey colKey, FromJSON a) => CPool -> ColumnFamily -> rowKey -> Selector -> ConsistencyLevel -> IO [(colKey, a)]Source
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.
getCol :: (CKey rowKey, CKey colKey, FromJSON a) => CPool -> ColumnFamily -> rowKey -> colKey -> ConsistencyLevel -> IO (Maybe a)Source
Get a single column from a single row
Arguments
| :: (CKey rowKey, CKey colKey, ToJSON a) | |
| => CPool | |
| -> ColumnFamily | |
| -> rowKey | |
| -> colKey | |
| -> ConsistencyLevel | |
| -> a | Content |
| -> IO () |
Arguments
| :: (CKey rowKey, CKey colKey, ToJSON a, FromJSON a) | |
| => CPool | |
| -> ColumnFamily | |
| -> rowKey | |
| -> colKey | |
| -> ConsistencyLevel | Read quorum |
| -> ConsistencyLevel | Write quorum |
| -> (Maybe a -> IO (ModifyOperation a, b)) | Modification function. Called with |
| -> IO b | Return the decided |
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.
Arguments
| :: (CKey rowKey, CKey colKey, ToJSON a, FromJSON a) | |
| => CPool | |
| -> ColumnFamily | |
| -> rowKey | |
| -> colKey | |
| -> ConsistencyLevel | Read quorum |
| -> ConsistencyLevel | Write quorum |
| -> (Maybe a -> IO (ModifyOperation a)) | Modification function. Called with |
| -> IO () |
Same as modify but does not offer a side value.
This method may throw a CassandraException for all exceptions other than
NotFoundException.
Arguments
| :: CKey rowKey | |
| => CPool | Cassandra connection |
| -> ColumnFamily | In |
| -> rowKey | Key to be deleted |
| -> Selector | Columns to be deleted |
| -> ConsistencyLevel | |
| -> IO () |
Same as the delete in the Cassandra.Basic module, except that
it throws an exception rather than returning an explicit Either
value.