redis-schema-0.1.0: Typed, schema-based, composable Redis library
Safe HaskellNone
LanguageHaskell2010

Database.Redis.Schema

Description

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

Documentation

newtype Pool inst Source #

Each instance has a distinct connection pool type. (Hedis names it Connection but it's a pool.)

Constructors

Pool 

Fields

newtype RedisM inst a Source #

Instance-indexed monad for Redis computations.

Constructors

Redis 

Fields

Instances

Instances details
Monad (RedisM inst) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

(>>=) :: RedisM inst a -> (a -> RedisM inst b) -> RedisM inst b #

(>>) :: RedisM inst a -> RedisM inst b -> RedisM inst b #

return :: a -> RedisM inst a #

Functor (RedisM inst) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

fmap :: (a -> b) -> RedisM inst a -> RedisM inst b #

(<$) :: a -> RedisM inst b -> RedisM inst a #

Applicative (RedisM inst) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

pure :: a -> RedisM inst a #

(<*>) :: RedisM inst (a -> b) -> RedisM inst a -> RedisM inst b #

liftA2 :: (a -> b -> c) -> RedisM inst a -> RedisM inst b -> RedisM inst c #

(*>) :: RedisM inst a -> RedisM inst b -> RedisM inst b #

(<*) :: RedisM inst a -> RedisM inst b -> RedisM inst a #

MonadIO (RedisM inst) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

liftIO :: IO a -> RedisM inst a #

MonadRedis (RedisM inst) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

liftRedis :: Redis a -> RedisM inst a

RedisCtx (RedisM inst) (Either Reply) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

returnDecode :: RedisResult a => Reply -> RedisM inst (Either Reply a)

type Redis = RedisM DefaultInstance Source #

The Redis monad related to the default instance.

type Instance = Type Source #

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

data Tx inst a Source #

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 an Applicative functor. Applicative exactly corresponds to the nature of Redis transactions, and does not need Queued hacks.
  • Tx supports throwing, and catching via Alternative. Beware that Tx is Applicative 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.

Instances

Instances details
Functor (Tx inst) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

fmap :: (a -> b) -> Tx inst a -> Tx inst b #

(<$) :: a -> Tx inst b -> Tx inst a #

Applicative (Tx inst) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

pure :: a -> Tx inst a #

(<*>) :: Tx inst (a -> b) -> Tx inst a -> Tx inst b #

liftA2 :: (a -> b -> c) -> Tx inst a -> Tx inst b -> Tx inst c #

(*>) :: Tx inst a -> Tx inst b -> Tx inst b #

(<*) :: Tx inst a -> Tx inst b -> Tx inst a #

Alternative (Tx inst) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

empty :: Tx inst a #

(<|>) :: Tx inst a -> Tx inst a -> Tx inst a #

some :: Tx inst a -> Tx inst [a] #

many :: Tx inst a -> Tx inst [a] #

atomically :: Tx inst a -> RedisM inst a Source #

Run a Tx transaction, propagating any errors.

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.

class Value (RefInstance ref) (ValueType ref) => Ref ref where Source #

Reference to some abstract Redis value.

ByteStrings are inappropriate for this purpose:

  • Refs 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 SimpleValues for new types. For simple values, it's sufficient to implement (or newtype-derive) SimpleValue, and declare an empty instance Value TheType.

Associated Types

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.

Methods

toIdentifier :: ref -> Identifier (ValueType ref) Source #

How to convert the ref to an identifier that its value accepts.

Instances

Instances details
(Ref ref, ValueType ref ~ Map k v, Serializable k, SimpleValue (RefInstance ref) v) => Ref (MapItem ref k v) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type ValueType (MapItem ref k v) Source #

type RefInstance (MapItem ref k v) Source #

Methods

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 # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type ValueType (RecordItem ref fieldF val) Source #

type RefInstance (RecordItem ref fieldF val) Source #

Methods

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.

Minimal complete definition

Nothing

Associated Types

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.

Methods

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

Instances details
Value (inst :: k) ByteString Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier ByteString Source #

Value (inst :: k) ByteString Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier ByteString Source #

Value (inst :: k) LocalTime Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier LocalTime Source #

Value (inst :: k) Day Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier Day Source #

Value (inst :: k) UTCTime Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier UTCTime Source #

Value (inst :: k) Bool Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier Bool Source #

Value (inst :: k) Double Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier Double Source #

Value (inst :: k) Integer Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier Integer Source #

Value (inst :: k) Int64 Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier Int64 Source #

Value (inst :: k) Word32 Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier Word32 Source #

Value (inst :: k) Int Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier Int Source #

Value (inst :: k) Text Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier Text Source #

Value (inst :: k) () Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier () Source #

Methods

txValGet :: Identifier () -> Tx inst (Maybe ()) Source #

txValSet :: Identifier () -> () -> Tx inst () Source #

txValDelete :: Identifier () -> Tx inst () Source #

txValSetTTLIfExists :: Identifier () -> TTL -> Tx inst Bool Source #

valGet :: Identifier () -> RedisM inst (Maybe ()) Source #

valSet :: Identifier () -> () -> RedisM inst () Source #

valDelete :: Identifier () -> RedisM inst () Source #

valSetTTLIfExists :: Identifier () -> TTL -> RedisM inst Bool Source #

(Serializable a, Ord a) => Value (inst :: k) (Set a) Source #

Redis sets.

Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (Set a) Source #

Methods

txValGet :: Identifier (Set a) -> Tx inst (Maybe (Set a)) Source #

txValSet :: Identifier (Set a) -> Set a -> Tx inst () Source #

txValDelete :: Identifier (Set a) -> Tx inst () Source #

txValSetTTLIfExists :: Identifier (Set a) -> TTL -> Tx inst Bool Source #

valGet :: Identifier (Set a) -> RedisM inst (Maybe (Set a)) Source #

valSet :: Identifier (Set a) -> Set a -> RedisM inst () Source #

valDelete :: Identifier (Set a) -> RedisM inst () Source #

valSetTTLIfExists :: Identifier (Set a) -> TTL -> RedisM inst Bool Source #

Serializable a => Value (inst :: k) [a] Source #

Redis lists.

Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier [a] Source #

Methods

txValGet :: Identifier [a] -> Tx inst (Maybe [a]) Source #

txValSet :: Identifier [a] -> [a] -> Tx inst () Source #

txValDelete :: Identifier [a] -> Tx inst () Source #

txValSetTTLIfExists :: Identifier [a] -> TTL -> Tx inst Bool Source #

valGet :: Identifier [a] -> RedisM inst (Maybe [a]) Source #

valSet :: Identifier [a] -> [a] -> RedisM inst () Source #

valDelete :: Identifier [a] -> RedisM inst () Source #

valSetTTLIfExists :: Identifier [a] -> TTL -> RedisM inst Bool Source #

Serializables as => Value (inst :: k) (Tuple as) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (Tuple as) Source #

Methods

txValGet :: Identifier (Tuple as) -> Tx inst (Maybe (Tuple as)) Source #

txValSet :: Identifier (Tuple as) -> Tuple as -> Tx inst () Source #

txValDelete :: Identifier (Tuple as) -> Tx inst () Source #

txValSetTTLIfExists :: Identifier (Tuple as) -> TTL -> Tx inst Bool Source #

valGet :: Identifier (Tuple as) -> RedisM inst (Maybe (Tuple as)) Source #

valSet :: Identifier (Tuple as) -> Tuple as -> RedisM inst () Source #

valDelete :: Identifier (Tuple as) -> RedisM inst () Source #

valSetTTLIfExists :: Identifier (Tuple as) -> TTL -> RedisM inst Bool Source #

Value (inst :: k) (Record fieldF) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (Record fieldF) Source #

Methods

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 #

(Ord k2, Serializable k2, Serializable v) => Value (inst :: k1) (Map k2 v) Source #

Redis hashes.

Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (Map k2 v) Source #

Methods

txValGet :: Identifier (Map k2 v) -> Tx inst (Maybe (Map k2 v)) Source #

txValSet :: Identifier (Map k2 v) -> Map k2 v -> Tx inst () Source #

txValDelete :: Identifier (Map k2 v) -> Tx inst () Source #

txValSetTTLIfExists :: Identifier (Map k2 v) -> TTL -> Tx inst Bool Source #

valGet :: Identifier (Map k2 v) -> RedisM inst (Maybe (Map k2 v)) Source #

valSet :: Identifier (Map k2 v) -> Map k2 v -> RedisM inst () Source #

valDelete :: Identifier (Map k2 v) -> RedisM inst () Source #

valSetTTLIfExists :: Identifier (Map k2 v) -> TTL -> RedisM inst Bool Source #

(SimpleValue inst a, SimpleValue inst b) => Value (inst :: k) (a, b) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (a, b) Source #

Methods

txValGet :: Identifier (a, b) -> Tx inst (Maybe (a, b)) Source #

txValSet :: Identifier (a, b) -> (a, b) -> Tx inst () Source #

txValDelete :: Identifier (a, b) -> Tx inst () Source #

txValSetTTLIfExists :: Identifier (a, b) -> TTL -> Tx inst Bool Source #

valGet :: Identifier (a, b) -> RedisM inst (Maybe (a, b)) Source #

valSet :: Identifier (a, b) -> (a, b) -> RedisM inst () Source #

valDelete :: Identifier (a, b) -> RedisM inst () Source #

valSetTTLIfExists :: Identifier (a, b) -> TTL -> RedisM inst Bool Source #

Value (inst :: k1) (PubSub msg) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (PubSub msg) Source #

Methods

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 #

(SimpleValue inst a, SimpleValue inst b, SimpleValue inst c) => Value (inst :: k) (a, b, c) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (a, b, c) Source #

Methods

txValGet :: Identifier (a, b, c) -> Tx inst (Maybe (a, b, c)) Source #

txValSet :: Identifier (a, b, c) -> (a, b, c) -> Tx inst () Source #

txValDelete :: Identifier (a, b, c) -> Tx inst () Source #

txValSetTTLIfExists :: Identifier (a, b, c) -> TTL -> Tx inst Bool Source #

valGet :: Identifier (a, b, c) -> RedisM inst (Maybe (a, b, c)) Source #

valSet :: Identifier (a, b, c) -> (a, b, c) -> RedisM inst () Source #

valDelete :: Identifier (a, b, c) -> RedisM inst () Source #

valSetTTLIfExists :: Identifier (a, b, c) -> TTL -> RedisM inst Bool Source #

Value (inst :: Type) ShareableLock Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Associated Types

type Identifier ShareableLock Source #

Value (inst :: Type) LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Associated Types

type Identifier LockSharing Source #

Value (inst :: Type) ExclusiveLock Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Associated Types

type Identifier ExclusiveLock Source #

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

Instances

Instances details
SimpleValue (inst :: k) ByteString Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) ByteString Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) LocalTime Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) Day Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) UTCTime Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) Bool Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) Double Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) Integer Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) Int64 Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) Word32 Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) Int Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) Text Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: k) () Source # 
Instance details

Defined in Database.Redis.Schema

Serializables as => SimpleValue (inst :: k) (Tuple as) Source # 
Instance details

Defined in Database.Redis.Schema

(SimpleValue inst a, SimpleValue inst b) => SimpleValue (inst :: k) (a, b) Source # 
Instance details

Defined in Database.Redis.Schema

(SimpleValue inst a, SimpleValue inst b, SimpleValue inst c) => SimpleValue (inst :: k) (a, b, c) Source # 
Instance details

Defined in Database.Redis.Schema

SimpleValue (inst :: Type) LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

SimpleValue (inst :: Type) ExclusiveLock Source # 
Instance details

Defined in Database.Redis.Schema.Lock

data SimpleValueIdentifier Source #

Constructors

SviTopLevel ByteString

Stored in a top-level key.

SviHash ByteString ByteString

Stored in a hash field.

class Serializable val where Source #

Methods

fromBS :: ByteString -> Maybe val Source #

toBS :: val -> ByteString Source #

Instances

Instances details
Serializable Bool Source # 
Instance details

Defined in Database.Redis.Schema

Serializable Double Source # 
Instance details

Defined in Database.Redis.Schema

Serializable Int Source # 
Instance details

Defined in Database.Redis.Schema

Serializable Int64 Source # 
Instance details

Defined in Database.Redis.Schema

Serializable Integer Source # 
Instance details

Defined in Database.Redis.Schema

Serializable Word32 Source # 
Instance details

Defined in Database.Redis.Schema

Serializable () Source # 
Instance details

Defined in Database.Redis.Schema

Serializable ByteString Source # 
Instance details

Defined in Database.Redis.Schema

Serializable ByteString Source # 
Instance details

Defined in Database.Redis.Schema

Serializable Text Source # 
Instance details

Defined in Database.Redis.Schema

Serializable LocalTime Source # 
Instance details

Defined in Database.Redis.Schema

Serializable UTCTime Source # 
Instance details

Defined in Database.Redis.Schema

Serializable Day Source # 
Instance details

Defined in Database.Redis.Schema

Serializable UUID Source # 
Instance details

Defined in Database.Redis.Schema

Methods

fromBS :: ByteString -> Maybe UUID Source #

toBS :: UUID -> ByteString Source #

Serializable Priority Source # 
Instance details

Defined in Database.Redis.Schema

Serializable LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Serializable ExclusiveLock Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Serializable a => Serializable (Maybe a) Source # 
Instance details

Defined in Database.Redis.Schema

Serializables as => Serializable (Tuple as) Source # 
Instance details

Defined in Database.Redis.Schema

(Serializable a, Serializable b) => Serializable (Either a b) Source # 
Instance details

Defined in Database.Redis.Schema

(Serializable a, Serializable b) => Serializable (a, b) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

fromBS :: ByteString -> Maybe (a, b) Source #

toBS :: (a, b) -> ByteString Source #

(Serializable a, Serializable b, Serializable c) => Serializable (a, b, c) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

fromBS :: ByteString -> Maybe (a, b, c) Source #

toBS :: (a, b, c) -> ByteString Source #

class Serializables (as :: [Type]) where Source #

Instances

Instances details
Serializables ('[] :: [Type]) Source # 
Instance details

Defined in Database.Redis.Schema

(Serializable a, Serializables as) => Serializables (a ': as) Source # 
Instance details

Defined in Database.Redis.Schema

newtype TTL Source #

Time-To-Live for Redis values. The Num instance works in (integral) seconds.

Constructors

TTLSec 

Instances

Instances details
Eq TTL Source # 
Instance details

Defined in Database.Redis.Schema

Methods

(==) :: TTL -> TTL -> Bool #

(/=) :: TTL -> TTL -> Bool #

Num TTL Source # 
Instance details

Defined in Database.Redis.Schema

Methods

(+) :: TTL -> TTL -> TTL #

(-) :: TTL -> TTL -> TTL #

(*) :: TTL -> TTL -> TTL #

negate :: TTL -> TTL #

abs :: TTL -> TTL #

signum :: TTL -> TTL #

fromInteger :: Integer -> TTL #

Ord TTL Source # 
Instance details

Defined in Database.Redis.Schema

Methods

compare :: TTL -> TTL -> Ordering #

(<) :: TTL -> TTL -> Bool #

(<=) :: TTL -> TTL -> Bool #

(>) :: TTL -> TTL -> Bool #

(>=) :: TTL -> TTL -> Bool #

max :: TTL -> TTL -> TTL #

min :: TTL -> TTL -> TTL #

run :: MonadIO m => Pool inst -> RedisM inst a -> m a Source #

connect :: String -> Int -> IO (Pool inst) Source #

Open a connection pool to redis

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 #

get :: Ref ref => ref -> RedisM (RefInstance ref) (Maybe (ValueType ref)) Source #

set :: Ref ref => ref -> ValueType ref -> RedisM (RefInstance 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.

txGet :: Ref ref => ref -> Tx (RefInstance ref) (Maybe (ValueType ref)) Source #

txSet :: Ref ref => ref -> ValueType ref -> Tx (RefInstance ref) () Source #

txExpect :: (Eq a, Show a) => String -> a -> Tx inst a -> Tx inst () Source #

Expect an exact 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 #

delete_ :: forall ref. Ref ref => ref -> RedisM (RefInstance ref) () Source #

txDelete_ :: forall ref. Ref ref => 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.

setTTL :: Ref ref => ref -> TTL -> RedisM (RefInstance ref) () Source #

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 #

txSetTTL :: Ref ref => ref -> TTL -> Tx (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 #

readBS :: Read val => ByteString -> Maybe val Source #

showBS :: Show val => val -> ByteString Source #

data Tuple :: [Type] -> Type where Source #

Constructors

Nil :: Tuple '[] 
(:*:) :: a -> Tuple as -> Tuple (a ': as) infixr 3 

Instances

Instances details
Serializables as => SimpleValue (inst :: k) (Tuple as) Source # 
Instance details

Defined in Database.Redis.Schema

Serializables as => Value (inst :: k) (Tuple as) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (Tuple as) Source #

Methods

txValGet :: Identifier (Tuple as) -> Tx inst (Maybe (Tuple as)) Source #

txValSet :: Identifier (Tuple as) -> Tuple as -> Tx inst () Source #

txValDelete :: Identifier (Tuple as) -> Tx inst () Source #

txValSetTTLIfExists :: Identifier (Tuple as) -> TTL -> Tx inst Bool Source #

valGet :: Identifier (Tuple as) -> RedisM inst (Maybe (Tuple as)) Source #

valSet :: Identifier (Tuple as) -> Tuple as -> RedisM inst () Source #

valDelete :: Identifier (Tuple as) -> RedisM inst () Source #

valSetTTLIfExists :: Identifier (Tuple as) -> TTL -> RedisM inst Bool Source #

(Eq a, Eq (Tuple as)) => Eq (Tuple (a ': as)) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

(==) :: Tuple (a ': as) -> Tuple (a ': as) -> Bool #

(/=) :: Tuple (a ': as) -> Tuple (a ': as) -> Bool #

Eq (Tuple ('[] :: [Type])) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

(==) :: Tuple '[] -> Tuple '[] -> Bool #

(/=) :: Tuple '[] -> Tuple '[] -> Bool #

(Ord a, Ord (Tuple as)) => Ord (Tuple (a ': as)) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

compare :: Tuple (a ': as) -> Tuple (a ': as) -> Ordering #

(<) :: Tuple (a ': as) -> Tuple (a ': as) -> Bool #

(<=) :: Tuple (a ': as) -> Tuple (a ': as) -> Bool #

(>) :: Tuple (a ': as) -> Tuple (a ': as) -> Bool #

(>=) :: Tuple (a ': as) -> Tuple (a ': as) -> Bool #

max :: Tuple (a ': as) -> Tuple (a ': as) -> Tuple (a ': as) #

min :: Tuple (a ': as) -> Tuple (a ': as) -> Tuple (a ': as) #

Ord (Tuple ('[] :: [Type])) Source # 
Instance details

Defined in Database.Redis.Schema

Methods

compare :: Tuple '[] -> Tuple '[] -> Ordering #

(<) :: Tuple '[] -> Tuple '[] -> Bool #

(<=) :: Tuple '[] -> Tuple '[] -> Bool #

(>) :: Tuple '[] -> Tuple '[] -> Bool #

(>=) :: Tuple '[] -> Tuple '[] -> Bool #

max :: Tuple '[] -> Tuple '[] -> Tuple '[] #

min :: Tuple '[] -> Tuple '[] -> Tuple '[] #

Serializables as => Serializable (Tuple as) Source # 
Instance details

Defined in Database.Redis.Schema

type Identifier (Tuple as) Source # 
Instance details

Defined in Database.Redis.Schema

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.

newtype Priority Source #

Priority for a sorted set

Constructors

Priority 

Fields

Instances

Instances details
Bounded Priority Source # 
Instance details

Defined in Database.Redis.Schema

Serializable Priority Source # 
Instance details

Defined in Database.Redis.Schema

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.

Constructors

(:/) :: (Ref ref, ValueType ref ~ Map k v) => ref -> k -> MapItem ref k v infix 3 

Instances

Instances details
(Ref ref, ValueType ref ~ Map k v, Serializable k, SimpleValue (RefInstance ref) v) => Ref (MapItem ref k v) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type ValueType (MapItem ref k v) Source #

type RefInstance (MapItem ref k v) Source #

Methods

toIdentifier :: MapItem ref k v -> Identifier (ValueType (MapItem ref k v)) Source #

type ValueType (MapItem ref k v) Source # 
Instance details

Defined in Database.Redis.Schema

type ValueType (MapItem ref k v) = v
type RefInstance (MapItem ref k v) Source # 
Instance details

Defined in Database.Redis.Schema

type RefInstance (MapItem ref k v) = RefInstance ref

class RecordField (fieldF :: Type -> Type) where Source #

Class of record fields. See Record for details.

Methods

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.

Constructors

(:.) ref (fieldF val) infix 3 

Instances

Instances details
(Ref ref, ValueType ref ~ Record fieldF, SimpleValue (RefInstance ref) val, RecordField fieldF) => Ref (RecordItem ref fieldF val) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type ValueType (RecordItem ref fieldF val) Source #

type RefInstance (RecordItem ref fieldF val) Source #

Methods

toIdentifier :: RecordItem ref fieldF val -> Identifier (ValueType (RecordItem ref fieldF val)) Source #

type ValueType (RecordItem ref fieldF val) Source # 
Instance details

Defined in Database.Redis.Schema

type ValueType (RecordItem ref fieldF val) = val
type RefInstance (RecordItem ref fieldF val) Source # 
Instance details

Defined in Database.Redis.Schema

type RefInstance (RecordItem ref fieldF val) = RefInstance ref

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 associations k -> v, where all refs have the same type and all values have the same type, just like a Haskell Map.

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

Records 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

Instances details
Value (inst :: k) (Record fieldF) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (Record fieldF) Source #

Methods

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 # 
Instance details

Defined in Database.Redis.Schema

type Identifier (Record fieldF) = ByteString

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.

unliftIO :: ((forall a. RedisM inst a -> IO a) -> IO b) -> RedisM inst b Source #

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 #

data PubSub msg Source #

PubSub channels.

Instances

Instances details
Value (inst :: k1) (PubSub msg) Source # 
Instance details

Defined in Database.Redis.Schema

Associated Types

type Identifier (PubSub msg) Source #

Methods

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 # 
Instance details

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 #

Orphan instances

(RedisResult a, RedisResult b, RedisResult c) => RedisResult (a, b, c) Source # 
Instance details

Methods

decode :: Reply -> Either Reply (a, b, c)