Safe Haskell | None |
---|---|
Language | Haskell2010 |
HLRDB is an opinionated, high-level, type-driven library for modeling Redis-backed database architecture.
This package provides an easy API for you to declare your data paths in Redis, but in doing so makes many decisions for you about how to serialize and deserialize values, construct identifiers, and define path names. If you want more control over these aspects, you may instead use the HLRDB Core package, which simply defines the commands and the abstract API without opining on these matters.
There is a simple demo project that shows how to get started.
Finally, make sure that your Eq instances always respect the induced equality via Store serialization, since obviously Redis commands will be comparing serialized values.
Minimal example
import Data.Store import Database.Redis (checkedConnect,defaultConnectInfo,runRedis) import HLRDB newtype CommentId = CommentId Identifier deriving (Eq,Ord,Show,Store,IsIdentifier) newtype Comment = Comment String deriving (Eq,Ord,Show,Store) cidToComment :: RedisBasic CommentId (Maybe Comment) cidToComment = declareBasic "canonical mapping from CommentId to Comment" main :: IO () main = do -- connect to Redis rconn <- checkedConnect defaultConnectInfo cid :: CommentId <- genId c :: Maybe Comment <- runRedis rconn $ do -- create a comment set' cidToComment cid $ Comment "hi" -- read it back get cidToComment cid print c
Commands
The commands are located in the core package.
- data Identifier
- class IsIdentifier a where
- genId :: IsIdentifier a => IO a
- genId' :: IsIdentifier a => UTCTime -> IO a
- identifierTimestamp :: IsIdentifier a => a -> UTCTime
- declareBasic :: (IsIdentifier i, Store v) => PathName -> RedisBasic i (Maybe v)
- declareIntegral :: (IsIdentifier i, Integral b) => PathName -> RedisIntegral i b
- declareBasicZero :: (IsIdentifier i, Store v) => PathName -> v -> RedisBasic i v
- declareList :: (IsIdentifier i, Store v) => PathName -> Maybe TrimScheme -> RedisList i v
- declareSet :: (IsIdentifier i, Store v) => PathName -> RedisSet i v
- declareHSet :: (IsIdentifier i, Store s, Store v) => PathName -> RedisHSet i s v
- declareSSet :: (IsIdentifier i, Store v) => PathName -> Maybe TrimScheme -> RedisSSet i v
- declareGlobalBasic :: Store v => PathName -> RedisBasic () (Maybe v)
- declareGlobalIntegral :: Integral b => PathName -> RedisIntegral () b
- declareGlobalBasicZero :: Store v => PathName -> v -> RedisBasic () v
- declareGlobalList :: Store v => PathName -> Maybe TrimScheme -> RedisList () v
- declareGlobalSet :: Store v => PathName -> RedisSet () v
- declareGlobalHSet :: (Store s, Store v) => PathName -> RedisHSet () s v
- declareGlobalSSet :: Store v => PathName -> Maybe TrimScheme -> RedisSSet () v
- encodePath :: IsIdentifier a => PathName -> a -> ByteString
- foldPath :: (MonadRedis m, IsIdentifier i, Store v) => RedisStructure s i v -> (a -> i -> m a) -> a -> m a
- class Store a
- module HLRDB.Core
Identifiers
data Identifier Source #
Use the following newtype pattern to declare your identifiers
newtype CommentId = CommentId Identifier deriving (Eq,Ord,Show,Store,IsIdentifier)
You may generate a new random identifier using genId
example :: IO CommentId example = genId
class IsIdentifier a where Source #
IsIdentifier means that a
is isomorphic to Identifier, usually via newtype. This enables to use genId :: IsIdentifier a => IO a
, declared below. It is required that not only is it isomorphic; it must respect the Store instance as well (you get this for free with a newtype anyway).
toIdentifier :: a -> Identifier Source #
fromIdentifier :: Identifier -> a Source #
genId :: IsIdentifier a => IO a Source #
Generate a new identifier using the current time as the timestamp
genId' :: IsIdentifier a => UTCTime -> IO a Source #
Generate a new identifier for the given timestamp
identifierTimestamp :: IsIdentifier a => a -> UTCTime Source #
Extract the timestamp from an identifier
Indexed path declaration
declareBasic :: (IsIdentifier i, Store v) => PathName -> RedisBasic i (Maybe v) Source #
Declare your paths by choosing the declaration for the Redis structure you want to use. You must provide a unique description, which not only serves to document your architecture, but the hash of which is used to distinguish between otherwise identical paths of the same type.
cidToComment :: RedisBasic CommentId (Maybe Comment) cidToComment = declareBasic "canonical mapping from CommentId to Comment"
declareIntegral :: (IsIdentifier i, Integral b) => PathName -> RedisIntegral i b Source #
Standard key-value store, but backed by a primitive integer in Redis, enabling extra commands like incr
declareBasicZero :: (IsIdentifier i, Store v) => PathName -> v -> RedisBasic i v Source #
Allows defining your own "zero" value. An example might be RoseTree, where a non-existant value in Redis can be mapped to a sensible empty value in Haskell.
declareList :: (IsIdentifier i, Store v) => PathName -> Maybe TrimScheme -> RedisList i v Source #
Standard Redis list, supporting prepends, appends, and range access. If a TrimScheme
is provided, operations will automatically trim the list to the specified length.
declareSet :: (IsIdentifier i, Store v) => PathName -> RedisSet i v Source #
A set in Redis.
declareHSet :: (IsIdentifier i, Store s, Store v) => PathName -> RedisHSet i s v Source #
A sub-hash table, using the sub-index type s
. s
here is only required to be Storable rather than IsIdentifier, but in practice you'll probably use identifiers for s
, too.
declareSSet :: (IsIdentifier i, Store v) => PathName -> Maybe TrimScheme -> RedisSSet i v Source #
A sorted set in Redis. You may optionally provide a trim scheme, which will automatically manage the sorted set's size for you.
Global path declaration
declareGlobalBasic :: Store v => PathName -> RedisBasic () (Maybe v) Source #
A global version of declareBasic
declareGlobalIntegral :: Integral b => PathName -> RedisIntegral () b Source #
A global version of declareIntegral
declareGlobalBasicZero :: Store v => PathName -> v -> RedisBasic () v Source #
A global version of declareZero
declareGlobalList :: Store v => PathName -> Maybe TrimScheme -> RedisList () v Source #
A global version of declareList
declareGlobalSet :: Store v => PathName -> RedisSet () v Source #
A global version of declareSet
declareGlobalHSet :: (Store s, Store v) => PathName -> RedisHSet () s v Source #
A global version of declareHSet
declareGlobalSSet :: Store v => PathName -> Maybe TrimScheme -> RedisSSet () v Source #
A global version of declareSSet
Other commands
encodePath :: IsIdentifier a => PathName -> a -> ByteString Source #
If for some reason you need the actual, raw key name (which you may use with the low-level commands in hedis), you may obtain it via encodePath
.
foldPath :: (MonadRedis m, IsIdentifier i, Store v) => RedisStructure s i v -> (a -> i -> m a) -> a -> m a Source #
Note that despite the pretty type signature, the actual implementation of foldPath
in Redis is slow (it uses the global scan command, so its run time is proportional to the number of total keys in Redis, *not* the number of keys specifically related to the given path). You should only use foldPath
for administrative tasks, and never for any public API.
The Store
typeclass provides efficient serialization and
deserialization to raw pointer addresses.
The peek
and poke
methods should be defined such that
decodeEx (encode x) == x
.
Store Identifier # | |
KnownNat n => Store (StaticSize n ByteString) | |
module HLRDB.Core