Safe Haskell | None |
---|
- data ModifyOperation a
- data KeySelector
- data KeyRangeType
- mkKeyRange :: KeySelector -> KeyRange
- data Selector
- range :: Selector
- boundless :: Maybe ByteString
- showCas :: CasType a => a -> String
- mkPredicate :: Selector -> SlicePredicate
- data Order
- renderOrd :: Order -> Bool
- reverseOrder :: Order -> Order
- type ColumnFamily = String
- type Key = ByteString
- type RowKey = Key
- type ColumnName = ByteString
- type Value = ByteString
- data Column
- = SuperColumn ColumnName [Column]
- | Column { }
- type Row = [Column]
- col :: ByteString -> ByteString -> Column
- mkThriftCol :: Column -> IO Column
- castColumn :: ColumnOrSuperColumn -> Either CassandraException Column
- castCol :: Column -> Either CassandraException Column
- castSuperCol :: SuperColumn -> Either CassandraException Column
- data CassandraException
- casRetryH :: Monad m => Int -> Handler m Bool
- networkRetryH :: Monad m => Int -> Handler m Bool
- getTime :: IO Int64
- data PageResult m a
- pIsDry :: PageResult m a -> Bool
- pIsDone :: PageResult t t1 -> Bool
- pHasMore :: PageResult t t1 -> Bool
- class CKey a where
- toColKey :: a -> ByteString
- fromColKey :: ByteString -> Either String a
- fromColKey' :: CKey a => ByteString -> a
Documentation
data ModifyOperation a Source
Possible outcomes of a modify operation
Eq a => Eq (ModifyOperation a) | |
Ord a => Ord (ModifyOperation a) | |
Read a => Read (ModifyOperation a) | |
Show a => Show (ModifyOperation a) |
data KeySelector Source
A Key
range selector to use with getMulti
.
data KeyRangeType Source
Encodes the Key vs. Token options in the thrift API.
InclusiveRange
ranges are just plain intuitive range queries.
WrapAround
ranges are also inclusive, but they wrap around the ring.
A column selector/filter statement for queries.
Remember that SuperColumns are always fully deserialized, so we don't offer
a way to filter columns within a SuperColumn
.
Column names and ranges are specified by any type that can be
packed into a Cassandra column using the CasType
typeclass.
All | Return everything in |
forall a . CasType a => ColNames [a] | Return specific columns or super-columns depending on the |
forall a b . (CasType a, CasType b) => SupNames a [b] | When deleting specific columns in a super column |
forall a b . (CasType a, CasType b) => Range | Return a range of columns or super-columns. |
|
A default starting point for range Selector
. Use this so you
don't run into ambiguous type variables when using Nothing.
range = Range (Nothing :: Maybe ByteString) (Nothing :: Maybe ByteString) Regular 1024
reverseOrder :: Order -> OrderSource
type ColumnFamily = StringSource
type Key = ByteStringSource
type ColumnName = ByteStringSource
type Value = ByteStringSource
A Column is either a single key-value pair or a SuperColumn with an arbitrary number of key-value pairs
col :: ByteString -> ByteString -> ColumnSource
A short-hand for creating key-value Column
values. This is
pretty low level; you probably want to use packCol
.
mkThriftCol :: Column -> IO ColumnSource
data CassandraException Source
casRetryH :: Monad m => Int -> Handler m BoolSource
Exception handler that returns True
for errors that may be
resolved after a retry. So they are good candidates for retrying
queries.
networkRetryH :: Monad m => Int -> Handler m BoolSource
IOException
s should be retried
Cassandra is VERY sensitive to its timestamp values. As a convention, timestamps are always in microseconds
data PageResult m a Source
Describes the result of a single pagination action
PDone | Done, this is all I have. |
| |
PMore | Here's a batch and there is more when you call the action. |
|
Monad m => Functor (PageResult m) |
pIsDry :: PageResult m a -> BoolSource
pIsDone :: PageResult t t1 -> BoolSource
pHasMore :: PageResult t t1 -> BoolSource
A typeclass to enable using any string-like type for row and column keys
toColKey :: a -> ByteStringSource
fromColKey :: ByteString -> Either String aSource
CKey String | |
CKey ByteString | |
CKey ByteString | |
CKey Text | |
CKey Text | |
CKey [ByteString] | For easy composite keys, just serialize your data type to a list of bytestrings, we'll concat them and turn them into column keys. |
fromColKey' :: CKey a => ByteString -> aSource
Raise an error if conversion fails