hlrdb-0.3.0.0: High-level Redis Database

Safe HaskellNone
LanguageHaskell2010

HLRDB

Contents

Description

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.

Synopsis

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
Instances
Eq Identifier Source # 
Instance details

Defined in HLRDB

Ord Identifier Source # 
Instance details

Defined in HLRDB

Show Identifier Source # 
Instance details

Defined in HLRDB

Generic Identifier Source # 
Instance details

Defined in HLRDB

Associated Types

type Rep Identifier :: Type -> Type #

Hashable Identifier Source # 
Instance details

Defined in HLRDB

Store Identifier Source # 
Instance details

Defined in HLRDB

IsIdentifier Identifier Source # 
Instance details

Defined in HLRDB

type Rep Identifier Source # 
Instance details

Defined in HLRDB

type Rep Identifier = D1 (MetaData "Identifier" "HLRDB" "hlrdb-0.3.0.0-Kz7EQkw5elt6yNpIFiSHF1" True) (C1 (MetaCons "Identifier" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int32, Word32, Word16, Word8))))

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).

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 :: (Store 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 :: (Store 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 :: (Store 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 :: (Store 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 :: (Store i, Store v) => PathName -> RedisSet i v Source #

A set in Redis.

declareHSet :: (Store 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 :: (Store 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 :: Store 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. Further, this method is only guaranteed to work if you've declared your RedisStructures using the declarative tools in this module: if you declared a path yourself, please ensure it is compatible with the pathing convention in this module (namely, a 5-byte prefix).

class Store a #

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 .

Instances
Store Identifier Source # 
Instance details

Defined in HLRDB

KnownNat n => Store (StaticSize n ByteString) 
Instance details

Defined in Data.Store.Internal

module HLRDB.Core