Safe Haskell | None |
---|---|
Language | Haskell2010 |
The schema-based Redis module.
This module is intended to be imported qualified.
That's why we don't have RedisRef
but rather Ref
.
Synopsis
- newtype Pool inst = Pool {
- _unPool :: Connection
- newtype RedisM inst a = Redis {
- unRedis :: Redis a
- type Redis = RedisM DefaultInstance
- type Instance = Type
- data DefaultInstance
- data Tx inst a
- atomically :: Tx inst a -> RedisM inst a
- runTx :: Tx inst a -> RedisM inst (TxResult (Either RedisException a))
- data RedisException
- class Value (RefInstance ref) (ValueType ref) => Ref ref where
- type ValueType ref :: Type
- type RefInstance ref :: Instance
- toIdentifier :: ref -> Identifier (ValueType ref)
- class Value inst val where
- type Identifier val :: Type
- txValGet :: Identifier val -> Tx inst (Maybe val)
- txValSet :: Identifier val -> val -> Tx inst ()
- txValDelete :: Identifier val -> Tx inst ()
- txValSetTTLIfExists :: Identifier val -> TTL -> Tx inst Bool
- valGet :: Identifier val -> RedisM inst (Maybe val)
- valSet :: Identifier val -> val -> RedisM inst ()
- valDelete :: Identifier val -> RedisM inst ()
- valSetTTLIfExists :: Identifier val -> TTL -> RedisM inst Bool
- type SimpleRef ref = (Ref ref, SimpleValue (RefInstance ref) (ValueType ref))
- class (Value inst val, Identifier val ~ SimpleValueIdentifier, Serializable val) => SimpleValue inst val
- data SimpleValueIdentifier
- class Serializable val where
- fromBS :: ByteString -> Maybe val
- toBS :: val -> ByteString
- class Serializables (as :: [Type]) where
- encodeSerializables :: Tuple as -> [ByteString]
- decodeSerializables :: [ByteString] -> Maybe (Tuple as)
- newtype TTL = TTLSec {}
- run :: MonadIO m => Pool inst -> RedisM inst a -> m a
- connect :: String -> Int -> IO (Pool inst)
- incrementBy :: (SimpleRef ref, Num (ValueType ref)) => ref -> Integer -> RedisM (RefInstance ref) (ValueType ref)
- incrementByFloat :: (SimpleRef ref, Floating (ValueType ref)) => ref -> Double -> RedisM (RefInstance ref) (ValueType ref)
- txIncrementBy :: (SimpleRef ref, Num (ValueType ref)) => ref -> Integer -> Tx (RefInstance ref) (ValueType ref)
- get :: Ref ref => ref -> RedisM (RefInstance ref) (Maybe (ValueType ref))
- set :: Ref ref => ref -> ValueType ref -> RedisM (RefInstance ref) ()
- getSet :: forall ref. SimpleRef ref => ref -> ValueType ref -> RedisM (RefInstance ref) (Maybe (ValueType ref))
- txGet :: Ref ref => ref -> Tx (RefInstance ref) (Maybe (ValueType ref))
- txSet :: Ref ref => ref -> ValueType ref -> Tx (RefInstance ref) ()
- txExpect :: (Eq a, Show a) => String -> a -> Tx inst a -> Tx inst ()
- setWithTTL :: forall ref. SimpleRef ref => ref -> TTL -> ValueType ref -> RedisM (RefInstance ref) ()
- setIfNotExists :: forall ref. SimpleRef ref => ref -> ValueType ref -> RedisM (RefInstance ref) Bool
- setIfNotExists_ :: SimpleRef ref => ref -> ValueType ref -> RedisM (RefInstance ref) ()
- txSetWithTTL :: SimpleRef ref => ref -> TTL -> ValueType ref -> Tx (RefInstance ref) ()
- txSetIfNotExists :: forall ref. SimpleRef ref => ref -> ValueType ref -> Tx (RefInstance ref) Bool
- txSetIfNotExists_ :: SimpleRef ref => ref -> ValueType ref -> Tx (RefInstance ref) ()
- delete_ :: forall ref. Ref ref => ref -> RedisM (RefInstance ref) ()
- txDelete_ :: forall ref. Ref ref => ref -> Tx (RefInstance ref) ()
- take :: Ref ref => ref -> RedisM (RefInstance ref) (Maybe (ValueType ref))
- txTake :: Ref ref => ref -> Tx (RefInstance ref) (Maybe (ValueType ref))
- setTTL :: Ref ref => ref -> TTL -> RedisM (RefInstance ref) ()
- setTTLIfExists :: forall ref. Ref ref => ref -> TTL -> RedisM (RefInstance ref) Bool
- setTTLIfExists_ :: Ref ref => ref -> TTL -> RedisM (RefInstance ref) ()
- txSetTTL :: Ref ref => ref -> TTL -> Tx (RefInstance ref) ()
- txSetTTLIfExists :: forall ref. Ref ref => ref -> TTL -> Tx (RefInstance ref) Bool
- txSetTTLIfExists_ :: forall ref. Ref ref => ref -> TTL -> Tx (RefInstance ref) ()
- readBS :: Read val => ByteString -> Maybe val
- showBS :: Show val => val -> ByteString
- showBinary :: Binary val => val -> ByteString
- readBinary :: Binary val => ByteString -> Maybe val
- colonSep :: [ByteString] -> ByteString
- data Tuple :: [Type] -> Type where
- day :: TTL
- hour :: TTL
- minute :: TTL
- second :: TTL
- throw :: RedisException -> RedisM inst a
- throwMsg :: String -> RedisM inst a
- sInsert :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> [a] -> RedisM (RefInstance ref) ()
- sDelete :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> [a] -> RedisM (RefInstance ref) ()
- sContains :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> a -> RedisM (RefInstance ref) Bool
- sSize :: (Ref ref, ValueType ref ~ Set a) => ref -> RedisM (RefInstance ref) Integer
- newtype Priority = Priority {
- unPriority :: Double
- zInsert :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> [(Priority, a)] -> RedisM (RefInstance ref) ()
- zSize :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> RedisM (RefInstance ref) Integer
- zCount :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> Priority -> Priority -> RedisM (RefInstance ref) Integer
- zDelete :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> a -> RedisM (RefInstance ref) ()
- zPopMin :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> Integer -> RedisM (RefInstance ref) [(Priority, a)]
- bzPopMin :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> Integer -> RedisM (RefInstance ref) (Maybe (Priority, a))
- zRangeByScoreLimit :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> Priority -> Priority -> Integer -> Integer -> RedisM (RefInstance ref) [a]
- txSInsert :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> [a] -> Tx (RefInstance ref) ()
- txSDelete :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> [a] -> Tx (RefInstance ref) ()
- txSContains :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> a -> Tx (RefInstance ref) Bool
- txSSize :: (Ref ref, ValueType ref ~ Set a) => ref -> Tx (RefInstance ref) Integer
- data MapItem :: Type -> Type -> Type -> Type where
- class RecordField (fieldF :: Type -> Type) where
- rfToBS :: fieldF a -> ByteString
- data RecordItem ref fieldF val = (:.) ref (fieldF val)
- data Record (fieldF :: Type -> Type)
- lLength :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> RedisM (RefInstance ref) Integer
- lAppend :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> [a] -> RedisM (RefInstance ref) ()
- txLAppend :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> [a] -> Tx (RefInstance ref) ()
- lPushLeft :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> [a] -> RedisM (RefInstance ref) ()
- lPopRight :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> RedisM (RefInstance ref) (Maybe a)
- lPopRightBlocking :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => TTL -> ref -> RedisM (RefInstance ref) (Maybe a)
- lRem :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> Integer -> a -> RedisM (RefInstance ref) ()
- watch :: SimpleRef ref => ref -> RedisM (RefInstance ref) ()
- unwatch :: RedisM inst ()
- unliftIO :: ((forall a. RedisM inst a -> IO a) -> IO b) -> RedisM inst b
- deleteIfEqual :: forall ref. SimpleRef ref => ref -> ValueType ref -> RedisM (RefInstance ref) Bool
- setIfNotExistsTTL :: forall ref. SimpleRef ref => ref -> ValueType ref -> TTL -> RedisM (RefInstance ref) Bool
- data PubSub msg
- pubSubListen :: (Ref ref, ValueType ref ~ PubSub msg, Serializable msg) => ref -> (Either RedisException msg -> IO Bool) -> RedisM (RefInstance ref) ()
- pubSubCountSubs :: (Ref ref, ValueType ref ~ PubSub msg) => ref -> RedisM (RefInstance ref) Integer
Documentation
Each instance has a distinct connection pool type. (Hedis names it Connection but it's a pool.)
newtype RedisM inst a Source #
Instance-indexed monad for Redis computations.
Instances
Monad (RedisM inst) Source # | |
Functor (RedisM inst) Source # | |
Applicative (RedisM inst) Source # | |
Defined in Database.Redis.Schema | |
MonadIO (RedisM inst) Source # | |
Defined in Database.Redis.Schema | |
MonadRedis (RedisM inst) Source # | |
Defined in Database.Redis.Schema | |
RedisCtx (RedisM inst) (Either Reply) Source # | |
Defined in Database.Redis.Schema returnDecode :: RedisResult a => Reply -> RedisM inst (Either Reply a) |
type Redis = RedisM DefaultInstance Source #
The Redis monad related to the default instance.
The kind of Redis instances. Ideally, this would be a user-defined DataKind, but since Haskell does not have implicit arguments, that would require that we index everything with it explicitly, which would create a lot of syntactic noise.
(Ab)using the Type kind for instances is a compromise.
data DefaultInstance Source #
We also define a default instance.
This is convenient for code bases using only one Redis instance,
since RefInstance
defaults to this. (See the Ref
typeclass below.)
Redis transactions.
In comparison with Hedis transactions:
Tx
is newtyped as a separate functor for clearer types and better error messages.Tx
is not a monad, just anApplicative
functor. Applicative exactly corresponds to the nature of Redis transactions, and does not needQueued
hacks.Tx
supports throwing, and catching viaAlternative
. Beware thatTx
isApplicative
so all side effects will be carried out, whether any actions throw or not. Throwing and catching is done at the level where the _results_ of the individual applicative actions are composed.
You can still have do-notation with the ApplicativeDo
extension.
runTx :: Tx inst a -> RedisM inst (TxResult (Either RedisException a)) Source #
Run a Redis transaction and return its result.
Most code will probably want to use atomically
instead,
which automatically propagates errors.
data RedisException Source #
Instances
Show RedisException Source # | |
Defined in Database.Redis.Schema showsPrec :: Int -> RedisException -> ShowS # show :: RedisException -> String # showList :: [RedisException] -> ShowS # | |
Exception RedisException Source # | |
Defined in Database.Redis.Schema |
class Value (RefInstance ref) (ValueType ref) => Ref ref where Source #
Reference to some abstract Redis value.
ByteString
s are inappropriate for this purpose:
Ref
s are typed.- bytestring concatenation and other faffing is ugly and error-prone.
- some values may be stored across several Redis keys, (such as Tiers.Redis.Profile), in which case bytestrings are not even sufficient.
All methods have defaults for easy implementation of SimpleValue
s for new types.
For simple values, it's sufficient to implement (or newtype-derive) SimpleValue
,
and declare an empty instance Value TheType
.
type ValueType ref :: Type Source #
Type of the value that this ref points to.
type RefInstance ref :: Instance Source #
RedisM instance this ref points into, with a default.
type RefInstance ref = DefaultInstance
toIdentifier :: ref -> Identifier (ValueType ref) Source #
How to convert the ref to an identifier that its value accepts.
Instances
(Ref ref, ValueType ref ~ Map k v, Serializable k, SimpleValue (RefInstance ref) v) => Ref (MapItem ref k v) Source # | |
Defined in Database.Redis.Schema toIdentifier :: MapItem ref k v -> Identifier (ValueType (MapItem ref k v)) Source # | |
(Ref ref, ValueType ref ~ Record fieldF, SimpleValue (RefInstance ref) val, RecordField fieldF) => Ref (RecordItem ref fieldF val) Source # | |
Defined in Database.Redis.Schema type ValueType (RecordItem ref fieldF val) Source # type RefInstance (RecordItem ref fieldF val) Source # toIdentifier :: RecordItem ref fieldF val -> Identifier (ValueType (RecordItem ref fieldF val)) Source # |
class Value inst val where Source #
Type that can be read/written from Redis.
This can be a simple value, such as string or integer, or a composite value, such as a complex record stored across multiple keys, hashes, sets and lists.
We parameterise the typeclass with the Redis instance.
Most Value instances will want to keep inst
open
but some may need to restrict it to a particular Redis instance;
especially those that access Refs under the hood, since Refs are instance-specific.
Nothing
type Identifier val :: Type Source #
How the value is identified in Redis.
Types like hashes, sets or list are always top-level keys in Redis,
so these are identified by bytestrings. Simple values can be top-level
or hash fields, so they are identified by SimpleValueIdentifier.
Complex values may be identified by something else; for example
Profile
is identified by a Token
,
because it's a complex value spread across multiple Redis keys.
type Identifier val = SimpleValueIdentifier
txValGet :: Identifier val -> Tx inst (Maybe val) Source #
Read a value from Redis in a transaction.
default txValGet :: SimpleValue inst val => Identifier val -> Tx inst (Maybe val) Source #
txValSet :: Identifier val -> val -> Tx inst () Source #
Write a value to Redis in a transaction.
default txValSet :: SimpleValue inst val => Identifier val -> val -> Tx inst () Source #
txValDelete :: Identifier val -> Tx inst () Source #
Delete a value from Redis in a transaction.
default txValDelete :: SimpleValue inst val => Identifier val -> Tx inst () Source #
txValSetTTLIfExists :: Identifier val -> TTL -> Tx inst Bool Source #
Set time-to-live for a value in a transaction. Return True
if the value exists.
default txValSetTTLIfExists :: SimpleValue inst val => Identifier val -> TTL -> Tx inst Bool Source #
valGet :: Identifier val -> RedisM inst (Maybe val) Source #
Read a value.
default valGet :: SimpleValue inst val => Identifier val -> RedisM inst (Maybe val) Source #
valSet :: Identifier val -> val -> RedisM inst () Source #
Write a value.
default valSet :: SimpleValue inst val => Identifier val -> val -> RedisM inst () Source #
valDelete :: Identifier val -> RedisM inst () Source #
Delete a value.
default valDelete :: SimpleValue inst val => Identifier val -> RedisM inst () Source #
valSetTTLIfExists :: Identifier val -> TTL -> RedisM inst Bool Source #
Set time-to-live for a value. Return True
if the value exists.
default valSetTTLIfExists :: SimpleValue inst val => Identifier val -> TTL -> RedisM inst Bool Source #
Instances
type SimpleRef ref = (Ref ref, SimpleValue (RefInstance ref) (ValueType ref)) Source #
Ref
pointing to a SimpleValue
.
class (Value inst val, Identifier val ~ SimpleValueIdentifier, Serializable val) => SimpleValue inst val Source #
Simple values, like strings, integers or enums, that be represented as a single bytestring.
Of course, any value can be represented as a single bytestring,
but structures like lists, hashes and sets have special support in Redis.
This allows insertions, updates, etc. in Redis directly,
but they cannot be read or written as bytestrings, and thus are not SimpleValue
s.
Instances
data SimpleValueIdentifier Source #
SviTopLevel ByteString | Stored in a top-level key. |
SviHash ByteString ByteString | Stored in a hash field. |
class Serializable val where Source #
fromBS :: ByteString -> Maybe val Source #
toBS :: val -> ByteString Source #
Instances
class Serializables (as :: [Type]) where Source #
encodeSerializables :: Tuple as -> [ByteString] Source #
decodeSerializables :: [ByteString] -> Maybe (Tuple as) Source #
Instances
Serializables ('[] :: [Type]) Source # | |
Defined in Database.Redis.Schema encodeSerializables :: Tuple '[] -> [ByteString] Source # decodeSerializables :: [ByteString] -> Maybe (Tuple '[]) Source # | |
(Serializable a, Serializables as) => Serializables (a ': as) Source # | |
Defined in Database.Redis.Schema encodeSerializables :: Tuple (a ': as) -> [ByteString] Source # decodeSerializables :: [ByteString] -> Maybe (Tuple (a ': as)) Source # |
Time-To-Live for Redis values. The Num instance works in (integral) seconds.
incrementBy :: (SimpleRef ref, Num (ValueType ref)) => ref -> Integer -> RedisM (RefInstance ref) (ValueType ref) Source #
Increment the value under the given ref.
incrementByFloat :: (SimpleRef ref, Floating (ValueType ref)) => ref -> Double -> RedisM (RefInstance ref) (ValueType ref) Source #
Increment the value under the given ref.
txIncrementBy :: (SimpleRef ref, Num (ValueType ref)) => ref -> Integer -> Tx (RefInstance ref) (ValueType ref) Source #
getSet :: forall ref. SimpleRef ref => ref -> ValueType ref -> RedisM (RefInstance ref) (Maybe (ValueType ref)) Source #
Atomically set a value and return its old value.
setWithTTL :: forall ref. SimpleRef ref => ref -> TTL -> ValueType ref -> RedisM (RefInstance ref) () Source #
Set value and TTL atomically.
setIfNotExists :: forall ref. SimpleRef ref => ref -> ValueType ref -> RedisM (RefInstance ref) Bool Source #
setIfNotExists_ :: SimpleRef ref => ref -> ValueType ref -> RedisM (RefInstance ref) () Source #
txSetWithTTL :: SimpleRef ref => ref -> TTL -> ValueType ref -> Tx (RefInstance ref) () Source #
txSetIfNotExists :: forall ref. SimpleRef ref => ref -> ValueType ref -> Tx (RefInstance ref) Bool Source #
txSetIfNotExists_ :: SimpleRef ref => ref -> ValueType ref -> Tx (RefInstance ref) () Source #
take :: Ref ref => ref -> RedisM (RefInstance ref) (Maybe (ValueType ref)) Source #
Atomically read and delete.
txTake :: Ref ref => ref -> Tx (RefInstance ref) (Maybe (ValueType ref)) Source #
Atomically read and delete in a transaction.
setTTLIfExists :: forall ref. Ref ref => ref -> TTL -> RedisM (RefInstance ref) Bool Source #
Bump the TTL without changing the content.
setTTLIfExists_ :: Ref ref => ref -> TTL -> RedisM (RefInstance ref) () Source #
txSetTTLIfExists :: forall ref. Ref ref => ref -> TTL -> Tx (RefInstance ref) Bool Source #
txSetTTLIfExists_ :: forall ref. Ref ref => ref -> TTL -> Tx (RefInstance ref) () Source #
showBS :: Show val => val -> ByteString Source #
showBinary :: Binary val => val -> ByteString Source #
readBinary :: Binary val => ByteString -> Maybe val Source #
colonSep :: [ByteString] -> ByteString Source #
data Tuple :: [Type] -> Type where Source #
Instances
throw :: RedisException -> RedisM inst a Source #
sInsert :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> [a] -> RedisM (RefInstance ref) () Source #
Insert into a Redis set.
sDelete :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> [a] -> RedisM (RefInstance ref) () Source #
Delete from a Redis set.
sContains :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> a -> RedisM (RefInstance ref) Bool Source #
Check membership in a Redis set.
sSize :: (Ref ref, ValueType ref ~ Set a) => ref -> RedisM (RefInstance ref) Integer Source #
Get set size.
Priority for a sorted set
zInsert :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> [(Priority, a)] -> RedisM (RefInstance ref) () Source #
Add elements to a sorted set
zSize :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> RedisM (RefInstance ref) Integer Source #
Get the cardinality (number of elements) of a sorted set
zCount :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> Priority -> Priority -> RedisM (RefInstance ref) Integer Source #
Returns the number of elements in the sorted set that have a score between minScore and maxScore inclusive.
zDelete :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> a -> RedisM (RefInstance ref) () Source #
Delete from a Redis sorted set
zPopMin :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> Integer -> RedisM (RefInstance ref) [(Priority, a)] Source #
Remove given number of smallest elements from a sorted set. Available since Redis 5.0.0
bzPopMin :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> Integer -> RedisM (RefInstance ref) (Maybe (Priority, a)) Source #
Remove the smallest element from a sorted set, and block for the given number of seconds when it is not there yet. Available since Redis 5.0.0
zRangeByScoreLimit :: forall ref a. (Ref ref, ValueType ref ~ [(Priority, a)], Serializable a) => ref -> Priority -> Priority -> Integer -> Integer -> RedisM (RefInstance ref) [a] Source #
Get elements from a sorted set, between the given min and max values, and with the given offset and limit.
txSInsert :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> [a] -> Tx (RefInstance ref) () Source #
Insert into a Redis set in a transaction.
txSDelete :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> [a] -> Tx (RefInstance ref) () Source #
Delete from a Redis set in a transaction.
txSContains :: forall ref a. (Ref ref, ValueType ref ~ Set a, Serializable a) => ref -> a -> Tx (RefInstance ref) Bool Source #
Check membership in a Redis set, in a transaction.
txSSize :: (Ref ref, ValueType ref ~ Set a) => ref -> Tx (RefInstance ref) Integer Source #
Get set size, in a transaction.
data MapItem :: Type -> Type -> Type -> Type where Source #
Map field addressing operator.
If ref
is a Ref
pointing to a Map k v
,
then (ref :/ k)
is a ref with type v
,
pointing to the entry in the map identified by k
.
Instances
(Ref ref, ValueType ref ~ Map k v, Serializable k, SimpleValue (RefInstance ref) v) => Ref (MapItem ref k v) Source # | |
Defined in Database.Redis.Schema toIdentifier :: MapItem ref k v -> Identifier (ValueType (MapItem ref k v)) Source # | |
type ValueType (MapItem ref k v) Source # | |
Defined in Database.Redis.Schema | |
type RefInstance (MapItem ref k v) Source # | |
Defined in Database.Redis.Schema |
class RecordField (fieldF :: Type -> Type) where Source #
Class of record fields. See Record
for details.
rfToBS :: fieldF a -> ByteString Source #
data RecordItem ref fieldF val Source #
Record item addressing operator.
If ref
is a ref pointing to a Record fieldF
,
and k :: fieldF v
is a field of that record,
then (ref :. k)
is a ref with type v
,
pointing to that field of that record.
(:.) ref (fieldF val) infix 3 |
Instances
(Ref ref, ValueType ref ~ Record fieldF, SimpleValue (RefInstance ref) val, RecordField fieldF) => Ref (RecordItem ref fieldF val) Source # | |
Defined in Database.Redis.Schema type ValueType (RecordItem ref fieldF val) Source # type RefInstance (RecordItem ref fieldF val) Source # toIdentifier :: RecordItem ref fieldF val -> Identifier (ValueType (RecordItem ref fieldF val)) Source # | |
type ValueType (RecordItem ref fieldF val) Source # | |
Defined in Database.Redis.Schema | |
type RefInstance (RecordItem ref fieldF val) Source # | |
Defined in Database.Redis.Schema |
data Record (fieldF :: Type -> Type) Source #
The value type for refs that point to records. Can be deleted and SetTTLed. Can't be read or written as a whole (at the moment).
The parameter fieldF
gives the field functor for this record.
This is usually a GADT indexed by the type of the corresponding record field.
Record
and Map
are related but different:
Map
is a homogeneous variable-size collection of associationsk -> v
, where all refs have the same type and all values have the same type, just like a HaskellMap
.
Map
s can be read/written to Redis as whole entities out-of-the-box.
Record
is a heterogeneous fixed-size record of items with different types, just like Haskell records.
Record
s cannot be read/written whole at the moment.
There's no special reason for that, except that it would probably be
too much type-level code that noone needs at the moment.
See also: (:.)
.
Instances
Value (inst :: k) (Record fieldF) Source # | |
Defined in Database.Redis.Schema type Identifier (Record fieldF) Source # txValGet :: Identifier (Record fieldF) -> Tx inst (Maybe (Record fieldF)) Source # txValSet :: Identifier (Record fieldF) -> Record fieldF -> Tx inst () Source # txValDelete :: Identifier (Record fieldF) -> Tx inst () Source # txValSetTTLIfExists :: Identifier (Record fieldF) -> TTL -> Tx inst Bool Source # valGet :: Identifier (Record fieldF) -> RedisM inst (Maybe (Record fieldF)) Source # valSet :: Identifier (Record fieldF) -> Record fieldF -> RedisM inst () Source # valDelete :: Identifier (Record fieldF) -> RedisM inst () Source # valSetTTLIfExists :: Identifier (Record fieldF) -> TTL -> RedisM inst Bool Source # | |
type Identifier (Record fieldF) Source # | |
Defined in Database.Redis.Schema |
lLength :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> RedisM (RefInstance ref) Integer Source #
Length of a Redis list
lAppend :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> [a] -> RedisM (RefInstance ref) () Source #
Append to a Redis list.
txLAppend :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> [a] -> Tx (RefInstance ref) () Source #
Append to a Redis list in a transaction.
lPushLeft :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> [a] -> RedisM (RefInstance ref) () Source #
Prepend to a Redis list.
lPopRight :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> RedisM (RefInstance ref) (Maybe a) Source #
Pop from the right.
lPopRightBlocking :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => TTL -> ref -> RedisM (RefInstance ref) (Maybe a) Source #
Pop from the right, blocking.
lRem :: forall ref a. (Ref ref, ValueType ref ~ [a], Serializable a) => ref -> Integer -> a -> RedisM (RefInstance ref) () Source #
Delete from a Redis list
watch :: SimpleRef ref => ref -> RedisM (RefInstance ref) () Source #
Make any subsequent transaction fail if the watched ref is modified
between the call to watch
and the transaction.
unwatch :: RedisM inst () Source #
Unwatch all watched keys. I can't find it anywhere in the documentation but I hope that this unwatches only the keys for the current connection, and does not affect other connections. Nothing else would make much sense.
deleteIfEqual :: forall ref. SimpleRef ref => ref -> ValueType ref -> RedisM (RefInstance ref) Bool Source #
setIfNotExistsTTL :: forall ref. SimpleRef ref => ref -> ValueType ref -> TTL -> RedisM (RefInstance ref) Bool Source #
PubSub channels.
Instances
Value (inst :: k1) (PubSub msg) Source # | |
Defined in Database.Redis.Schema type Identifier (PubSub msg) Source # txValGet :: Identifier (PubSub msg) -> Tx inst (Maybe (PubSub msg)) Source # txValSet :: Identifier (PubSub msg) -> PubSub msg -> Tx inst () Source # txValDelete :: Identifier (PubSub msg) -> Tx inst () Source # txValSetTTLIfExists :: Identifier (PubSub msg) -> TTL -> Tx inst Bool Source # valGet :: Identifier (PubSub msg) -> RedisM inst (Maybe (PubSub msg)) Source # valSet :: Identifier (PubSub msg) -> PubSub msg -> RedisM inst () Source # valDelete :: Identifier (PubSub msg) -> RedisM inst () Source # valSetTTLIfExists :: Identifier (PubSub msg) -> TTL -> RedisM inst Bool Source # | |
type Identifier (PubSub msg) Source # | |
Defined in Database.Redis.Schema |
pubSubListen :: (Ref ref, ValueType ref ~ PubSub msg, Serializable msg) => ref -> (Either RedisException msg -> IO Bool) -> RedisM (RefInstance ref) () Source #
pubSubCountSubs :: (Ref ref, ValueType ref ~ PubSub msg) => ref -> RedisM (RefInstance ref) Integer Source #