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

Database.Redis.Schema.Lock

Synopsis

Documentation

withExclusiveLock Source #

Arguments

:: (MonadCatch m, MonadThrow m, MonadMask m, MonadIO m, Ref ref, ValueType ref ~ ExclusiveLock) 
=> Pool (RefInstance ref) 
-> LockParams

Params of the lock, such as timeouts or TTL.

-> ref

Lock ref

-> m a

The action to perform under lock

-> m a 

Execute the given action in an exclusively locked context.

This is useful mainly for operations that need to be atomic while manipulating *both* Redis and database (such as various commit scripts).

withShareableLock Source #

Arguments

:: (MonadCatch m, MonadThrow m, MonadMask m, MonadIO m, Ref ref, ValueType ref ~ ShareableLock, SimpleValue (RefInstance ref) (MetaLock ref)) 
=> Pool (RefInstance ref) 
-> ShareableLockParams

Params of the lock, such as timeouts or TTL.

-> LockSharing

Shared / Exclusive

-> ref

Lock ref

-> m a

The action to perform under lock

-> m a 

Execute the given action in a locked, possibly shared context.

This is useful mainly for operations that need to be atomic while manipulating *both* Redis and database (such as various commit scripts).

  • For Redis-only transactions, use atomically.
  • For database-only transactions, use database transactions.
  • For exclusive locks, withExclusiveLock is more efficient.

NOTE: the shareable lock seems to have quite a lot of performance overhead. Always benchmark first whether the exclusive lock would perform better in your scenario, even when a shareable lock would be sufficient in theory.

data LockSharing Source #

Constructors

Shared 
Exclusive 

Instances

Instances details
Eq LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Ord LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Read LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Show LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Generic LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

Associated Types

type Rep LockSharing :: Type -> Type #

Serializable LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

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

Defined in Database.Redis.Schema.Lock

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

Defined in Database.Redis.Schema.Lock

Associated Types

type Identifier LockSharing Source #

type Rep LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock

type Rep LockSharing = D1 ('MetaData "LockSharing" "Database.Redis.Schema.Lock" "redis-schema-0.1.0-inplace" 'False) (C1 ('MetaCons "Shared" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exclusive" 'PrefixI 'False) (U1 :: Type -> Type))
type Identifier LockSharing Source # 
Instance details

Defined in Database.Redis.Schema.Lock