-- | Basic storage is simply a key-value lookup in Redis.

module HLRDB.Structures.Basic where

import Database.Redis as Redis
import HLRDB.Primitives.Aggregate
import HLRDB.Primitives.Redis
import HLRDB.Internal
import Data.ByteString (ByteString)
import Data.ByteString.Char8 (pack)
import qualified Data.HashMap.Strict as HM


-- | Simple get command. Works on @RedisBasic a b@ and @RedisIntegral a b@.
get :: MonadRedis m => RedisStructure (BASIC w) a b -> a -> m b
get :: RedisStructure (BASIC w) a b -> a -> m b
get (RKeyValue (E a -> ByteString
k b -> Maybe ByteString
_ Maybe ByteString -> b
d)) a
a = Redis b -> m b
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis b -> m b) -> Redis b -> m b
forall a b. (a -> b) -> a -> b
$ ByteString -> Redis (Either Reply (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> m (f (Maybe ByteString))
Redis.get (a -> ByteString
k a
a) Redis (Either Reply (Maybe ByteString))
-> (Either Reply (Maybe ByteString) -> Redis b) -> Redis b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
  Left Reply
e -> String -> Redis b
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (Reply -> String
forall a. Show a => a -> String
show Reply
e)
  Right Maybe ByteString
r -> b -> Redis b
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ByteString -> b
d Maybe ByteString
r)
get (RKeyValueInteger a -> ByteString
k b -> Integer
_ Integer -> b
d) a
a = Redis b -> m b
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis b -> m b) -> Redis b -> m b
forall a b. (a -> b) -> a -> b
$ ByteString -> Redis (Either Reply (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> m (f (Maybe ByteString))
Redis.get (a -> ByteString
k a
a) Redis (Either Reply (Maybe ByteString))
-> (Either Reply (Maybe ByteString) -> Redis b) -> Redis b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
  Left Reply
e -> String -> Redis b
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (Reply -> String
forall a. Show a => a -> String
show Reply
e)
  Right Maybe ByteString
r -> b -> Redis b
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Redis b) -> b -> Redis b
forall a b. (a -> b) -> a -> b
$ Integer -> b
d (Integer -> b) -> (Int64 -> Integer) -> Int64 -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> b) -> Int64 -> b
forall a b. (a -> b) -> a -> b
$ Maybe ByteString -> Int64
decodeMInteger Maybe ByteString
r
get (RKeyValueByteString a -> ByteString
k) a
a = Redis ByteString -> m ByteString
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis ByteString -> m ByteString)
-> Redis ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Redis (Either Reply (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> m (f (Maybe ByteString))
Redis.get (a -> ByteString
k a
a) Redis (Either Reply (Maybe ByteString))
-> (Either Reply (Maybe ByteString) -> Redis ByteString)
-> Redis ByteString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
  Left Reply
e -> String -> Redis ByteString
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (Reply -> String
forall a. Show a => a -> String
show Reply
e)
  Right Maybe ByteString
r -> ByteString -> Redis ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString
-> (ByteString -> ByteString) -> Maybe ByteString -> ByteString
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ByteString
forall a. Monoid a => a
mempty ByteString -> ByteString
forall a. a -> a
id Maybe ByteString
r)

-- | Construct a query to be used with @mget@. You may combine many of these together to create complex queries. Use @mget@ to execute the query back in the Redis monad. Works on @RedisBasic a b@ and @RedisIntegral a b@.
liftq :: RedisStructure (BASIC w) a b -> a  b
liftq :: RedisStructure (BASIC w) a b -> a ⟿ b
liftq (RKeyValue (E a -> ByteString
k b -> Maybe ByteString
_ Maybe ByteString -> b
d)) = Traversal a b ByteString (Maybe ByteString) -> a ⟿ b
forall x y a b. Traversal a b x y -> T x y a b
T (Traversal a b ByteString (Maybe ByteString) -> a ⟿ b)
-> Traversal a b ByteString (Maybe ByteString) -> a ⟿ b
forall a b. (a -> b) -> a -> b
$ \ByteString -> f (Maybe ByteString)
f -> (Maybe ByteString -> b) -> f (Maybe ByteString) -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe ByteString -> b
d (f (Maybe ByteString) -> f b)
-> (a -> f (Maybe ByteString)) -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> f (Maybe ByteString)
f (ByteString -> f (Maybe ByteString))
-> (a -> ByteString) -> a -> f (Maybe ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
k
liftq (RKeyValueInteger a -> ByteString
k b -> Integer
_ Integer -> b
d) = Traversal a b ByteString (Maybe ByteString) -> a ⟿ b
forall x y a b. Traversal a b x y -> T x y a b
T (Traversal a b ByteString (Maybe ByteString) -> a ⟿ b)
-> Traversal a b ByteString (Maybe ByteString) -> a ⟿ b
forall a b. (a -> b) -> a -> b
$ \ByteString -> f (Maybe ByteString)
f -> (Maybe ByteString -> b) -> f (Maybe ByteString) -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer -> b
d (Integer -> b)
-> (Maybe ByteString -> Integer) -> Maybe ByteString -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Integer)
-> (Maybe ByteString -> Int64) -> Maybe ByteString -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe ByteString -> Int64
decodeMInteger) (f (Maybe ByteString) -> f b)
-> (a -> f (Maybe ByteString)) -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> f (Maybe ByteString)
f (ByteString -> f (Maybe ByteString))
-> (a -> ByteString) -> a -> f (Maybe ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
k
liftq (RKeyValueByteString a -> ByteString
k) = Traversal a b ByteString (Maybe ByteString) -> a ⟿ b
forall x y a b. Traversal a b x y -> T x y a b
T (Traversal a b ByteString (Maybe ByteString) -> a ⟿ b)
-> Traversal a b ByteString (Maybe ByteString) -> a ⟿ b
forall a b. (a -> b) -> a -> b
$ \ByteString -> f (Maybe ByteString)
f -> (Maybe b -> b) -> f (Maybe b) -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (b -> (b -> b) -> Maybe b -> b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe b
forall a. Monoid a => a
mempty b -> b
forall a. a -> a
id) (f (Maybe b) -> f b) -> (a -> f (Maybe b)) -> a -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> f (Maybe ByteString)
f (ByteString -> f (Maybe ByteString))
-> (a -> ByteString) -> a -> f (Maybe ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
k

-- | Reify a (⟿) query into the Redis monad via a single mget command.
mget :: MonadRedis m => a  b -> a -> m b
mget :: (a ⟿ b) -> a -> m b
mget = ([ByteString] -> m [Maybe ByteString]) -> (a ⟿ b) -> a -> m b
forall (f :: * -> *) x y a b.
Functor f =>
([x] -> f [y]) -> T x y a b -> a -> f b
runT (Redis [Maybe ByteString] -> m [Maybe ByteString]
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis [Maybe ByteString] -> m [Maybe ByteString])
-> ([ByteString] -> Redis [Maybe ByteString])
-> [ByteString]
-> m [Maybe ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> Redis [Maybe ByteString]
forall (f :: * -> *) a.
(RedisCtx f (Either a), MonadFail f, Show a) =>
[ByteString] -> f [Maybe ByteString]
mget')
  where
    mget' :: [ByteString] -> f [Maybe ByteString]
mget' [] = [Maybe ByteString] -> f [Maybe ByteString]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
    mget' [ByteString]
xs = [ByteString] -> f (Either a [Maybe ByteString])
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
[ByteString] -> m (f [Maybe ByteString])
Redis.mget [ByteString]
xs f (Either a [Maybe ByteString])
-> (Either a [Maybe ByteString] -> f [Maybe ByteString])
-> f [Maybe ByteString]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Left a
e -> String -> f [Maybe ByteString]
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (a -> String
forall a. Show a => a -> String
show a
e)
      Right [Maybe ByteString]
vs -> [Maybe ByteString] -> f [Maybe ByteString]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Maybe ByteString]
vs

-- | Set a value for a given key. Works on @RedisBasic a b@ and @RedisIntegral a b@.
set :: MonadRedis m => RedisStructure (BASIC w) a b -> a -> b -> m ()
set :: RedisStructure (BASIC w) a b -> a -> b -> m ()
set (RKeyValue (E a -> ByteString
k b -> Maybe ByteString
e Maybe ByteString -> b
_)) a
a b
b = Redis () -> m ()
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis () -> m ()) -> Redis () -> m ()
forall a b. (a -> b) -> a -> b
$ case b -> Maybe ByteString
e b
b of
  Just ByteString
bs -> Redis (Either Reply Status) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Status) -> Redis ())
-> Redis (Either Reply Status) -> Redis ()
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> Redis (Either Reply Status)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> ByteString -> m (f Status)
Redis.set (a -> ByteString
k a
a) ByteString
bs
  Maybe ByteString
Nothing -> Redis (Either Reply Integer) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Integer) -> Redis ())
-> Redis (Either Reply Integer) -> Redis ()
forall a b. (a -> b) -> a -> b
$ [ByteString] -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
[ByteString] -> m (f Integer)
del [ a -> ByteString
k a
a ]
set (RKeyValueInteger a -> ByteString
k b -> Integer
e Integer -> b
_) a
a b
i = Redis () -> m ()
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis () -> m ()) -> Redis () -> m ()
forall a b. (a -> b) -> a -> b
$ Redis (Either Reply Status) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Status) -> Redis ())
-> Redis (Either Reply Status) -> Redis ()
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> Redis (Either Reply Status)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> ByteString -> m (f Status)
Redis.set (a -> ByteString
k a
a) (String -> ByteString
pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Show a => a -> String
show (b -> Integer
e b
i))
set (RKeyValueByteString a -> ByteString
k) a
a b
b = Redis () -> m ()
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis () -> m ()) -> Redis () -> m ()
forall a b. (a -> b) -> a -> b
$ if b
b b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
forall a. Monoid a => a
mempty
  then Redis (Either Reply Integer) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Integer) -> Redis ())
-> Redis (Either Reply Integer) -> Redis ()
forall a b. (a -> b) -> a -> b
$ [ByteString] -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
[ByteString] -> m (f Integer)
Redis.del [ a -> ByteString
k a
a ]
  else Redis (Either Reply Status) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Status) -> Redis ())
-> Redis (Either Reply Status) -> Redis ()
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> Redis (Either Reply Status)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> ByteString -> m (f Status)
Redis.set (a -> ByteString
k a
a) b
ByteString
b

-- | Convenient alias for setting a value for an optional path
set' :: MonadRedis m => RedisBasic a (Maybe b) -> a -> b -> m ()
set' :: RedisBasic a (Maybe b) -> a -> b -> m ()
set' (RKeyValue (E a -> ByteString
k Maybe b -> Maybe ByteString
e Maybe ByteString -> Maybe b
_)) a
a b
b = Redis () -> m ()
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis () -> m ()) -> Redis () -> m ()
forall a b. (a -> b) -> a -> b
$ case Maybe b -> Maybe ByteString
e (b -> Maybe b
forall a. a -> Maybe a
Just b
b) of
  Just ByteString
bs -> Redis (Either Reply Status) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Status) -> Redis ())
-> Redis (Either Reply Status) -> Redis ()
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> Redis (Either Reply Status)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> ByteString -> m (f Status)
Redis.set (a -> ByteString
k a
a) ByteString
bs
  Maybe ByteString
Nothing -> Redis (Either Reply Integer) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Integer) -> Redis ())
-> Redis (Either Reply Integer) -> Redis ()
forall a b. (a -> b) -> a -> b
$ [ByteString] -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
[ByteString] -> m (f Integer)
del [ a -> ByteString
k a
a ]

-- | Construct a query to be used with @mset@. The @MSET@ type is a @Monoid@, so you may combine many of these together before executing the batch with the @mset@ command.
liftqs :: RedisStructure (BASIC w) a b -> (a , b) -> MSET
liftqs :: RedisStructure (BASIC w) a b -> (a, b) -> MSET
liftqs (RKeyValue (E a -> ByteString
k b -> Maybe ByteString
e Maybe ByteString -> b
_)) (a
a , b
b) = DList (ByteString, Maybe ByteString) -> MSET
MSET (DList (ByteString, Maybe ByteString) -> MSET)
-> DList (ByteString, Maybe ByteString) -> MSET
forall a b. (a -> b) -> a -> b
$ [(ByteString, Maybe ByteString)]
-> DList (ByteString, Maybe ByteString)
forall a. Semigroup a => a -> a -> a
(<>) [ (a -> ByteString
k a
a , b -> Maybe ByteString
e b
b) ]
liftqs (RKeyValueInteger a -> ByteString
k b -> Integer
e Integer -> b
_) (a
a , b
b) = DList (ByteString, Maybe ByteString) -> MSET
MSET (DList (ByteString, Maybe ByteString) -> MSET)
-> DList (ByteString, Maybe ByteString) -> MSET
forall a b. (a -> b) -> a -> b
$ [(ByteString, Maybe ByteString)]
-> DList (ByteString, Maybe ByteString)
forall a. Semigroup a => a -> a -> a
(<>) [ (a -> ByteString
k a
a , ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ String -> ByteString
pack (Integer -> String
forall a. Show a => a -> String
show (b -> Integer
e b
b))) ]
liftqs (RKeyValueByteString a -> ByteString
k) (a
a , b
b) = DList (ByteString, Maybe ByteString) -> MSET
MSET (DList (ByteString, Maybe ByteString) -> MSET)
-> DList (ByteString, Maybe ByteString) -> MSET
forall a b. (a -> b) -> a -> b
$ [(ByteString, Maybe b)]
-> [(ByteString, Maybe b)] -> [(ByteString, Maybe b)]
forall a. Semigroup a => a -> a -> a
(<>) [ (a -> ByteString
k a
a , b -> Maybe b
forall a. a -> Maybe a
Just b
b) ]

-- | Execute a @MSET@ query.
mset :: MonadRedis m => MSET -> m ()
mset :: MSET -> m ()
mset = [(ByteString, Maybe ByteString)] -> m ()
forall (m :: * -> *).
MonadRedis m =>
[(ByteString, Maybe ByteString)] -> m ()
go ([(ByteString, Maybe ByteString)] -> m ())
-> (MSET -> [(ByteString, Maybe ByteString)]) -> MSET -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MSET -> DList (ByteString, Maybe ByteString))
-> [(ByteString, Maybe ByteString)]
-> MSET
-> [(ByteString, Maybe ByteString)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip MSET -> DList (ByteString, Maybe ByteString)
runMSET []
  where
    -- need this hashmap to/from in order to make sure deleting a value after setting it
    -- performs correctly.
    go :: [(ByteString, Maybe ByteString)] -> m ()
go [(ByteString, Maybe ByteString)]
xs = case (((ByteString, Maybe ByteString)
 -> Either ByteString (ByteString, ByteString))
-> [(ByteString, Maybe ByteString)]
-> ([ByteString], [(ByteString, ByteString)])
forall a b c. (a -> Either b c) -> [a] -> ([b], [c])
splitWith (ByteString, Maybe ByteString)
-> Either ByteString (ByteString, ByteString)
forall a b. (a, Maybe b) -> Either a (a, b)
f ([(ByteString, Maybe ByteString)]
 -> ([ByteString], [(ByteString, ByteString)]))
-> DList (ByteString, Maybe ByteString)
-> [(ByteString, Maybe ByteString)]
-> ([ByteString], [(ByteString, ByteString)])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap ByteString (Maybe ByteString)
-> [(ByteString, Maybe ByteString)]
forall k v. HashMap k v -> [(k, v)]
HM.toList (HashMap ByteString (Maybe ByteString)
 -> [(ByteString, Maybe ByteString)])
-> ([(ByteString, Maybe ByteString)]
    -> HashMap ByteString (Maybe ByteString))
-> DList (ByteString, Maybe ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(ByteString, Maybe ByteString)]
-> HashMap ByteString (Maybe ByteString)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList) [(ByteString, Maybe ByteString)]
xs of
      ([ByteString]
as , [(ByteString, ByteString)]
bs) -> [ByteString] -> m Integer
forall (f :: * -> *). MonadRedis f => [ByteString] -> f Integer
mdel' [ByteString]
as m Integer -> m Status -> m Status
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [(ByteString, ByteString)] -> m Status
forall (f :: * -> *).
MonadRedis f =>
[(ByteString, ByteString)] -> f Status
mset' [(ByteString, ByteString)]
bs m Status -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
      where
        f :: (a, Maybe b) -> Either a (a, b)
f (a
x , Maybe b
Nothing) = a -> Either a (a, b)
forall a b. a -> Either a b
Left a
x
        f (a
x , Just b
y) = (a, b) -> Either a (a, b)
forall a b. b -> Either a b
Right (a
x , b
y)

    mdel' :: [ByteString] -> f Integer
mdel' [] = Integer -> f Integer
forall (f :: * -> *) a. Applicative f => a -> f a
pure Integer
0
    mdel' [ByteString]
xs = Redis (Either Reply Integer) -> f Integer
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap (Redis (Either Reply Integer) -> f Integer)
-> Redis (Either Reply Integer) -> f Integer
forall a b. (a -> b) -> a -> b
$ Redis (Either Reply Integer) -> Redis (Either Reply Integer)
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis (Either Reply Integer) -> Redis (Either Reply Integer))
-> Redis (Either Reply Integer) -> Redis (Either Reply Integer)
forall a b. (a -> b) -> a -> b
$ [ByteString] -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
[ByteString] -> m (f Integer)
Redis.del [ByteString]
xs
    
    mset' :: [(ByteString, ByteString)] -> f Status
mset' [] = Status -> f Status
forall (f :: * -> *) a. Applicative f => a -> f a
pure Status
Ok
    mset' [(ByteString, ByteString)]
xs = Redis (Either Reply Status) -> f Status
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap (Redis (Either Reply Status) -> f Status)
-> Redis (Either Reply Status) -> f Status
forall a b. (a -> b) -> a -> b
$ Redis (Either Reply Status) -> Redis (Either Reply Status)
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis (Either Reply Status) -> Redis (Either Reply Status))
-> Redis (Either Reply Status) -> Redis (Either Reply Status)
forall a b. (a -> b) -> a -> b
$ [(ByteString, ByteString)] -> Redis (Either Reply Status)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
[(ByteString, ByteString)] -> m (f Status)
Redis.mset [(ByteString, ByteString)]
xs

-- | Set a value together with a given expiration timeout (in seconds).
setex :: MonadRedis m => RedisStructure (BASIC w) a b -> a -> Integer -> b -> m ()
setex :: RedisStructure (BASIC w) a b -> a -> Integer -> b -> m ()
setex (RKeyValue (E a -> ByteString
k b -> Maybe ByteString
e Maybe ByteString -> b
_)) a
a Integer
t b
b = Redis () -> m ()
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis () -> m ()) -> Redis () -> m ()
forall a b. (a -> b) -> a -> b
$ case b -> Maybe ByteString
e b
b of
  Just ByteString
bs -> Redis (Either Reply Status) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Status) -> Redis ())
-> Redis (Either Reply Status) -> Redis ()
forall a b. (a -> b) -> a -> b
$ ByteString -> Integer -> ByteString -> Redis (Either Reply Status)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> Integer -> ByteString -> m (f Status)
Redis.setex (a -> ByteString
k a
a) Integer
t ByteString
bs
  Maybe ByteString
Nothing -> Redis (Either Reply Integer) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Integer) -> Redis ())
-> Redis (Either Reply Integer) -> Redis ()
forall a b. (a -> b) -> a -> b
$ [ByteString] -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
[ByteString] -> m (f Integer)
del [ a -> ByteString
k a
a ]
setex (RKeyValueInteger a -> ByteString
k b -> Integer
e Integer -> b
_) a
a Integer
t b
i = Redis () -> m ()
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis () -> m ()) -> Redis () -> m ()
forall a b. (a -> b) -> a -> b
$ Redis (Either Reply Status) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Status) -> Redis ())
-> Redis (Either Reply Status) -> Redis ()
forall a b. (a -> b) -> a -> b
$ ByteString -> Integer -> ByteString -> Redis (Either Reply Status)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> Integer -> ByteString -> m (f Status)
Redis.setex (a -> ByteString
k a
a) Integer
t (String -> ByteString
pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Show a => a -> String
show (b -> Integer
e b
i))
setex (RKeyValueByteString a -> ByteString
k) a
a Integer
t b
b = Redis () -> m ()
forall (m :: * -> *) a. MonadRedis m => Redis a -> m a
liftRedis (Redis () -> m ()) -> Redis () -> m ()
forall a b. (a -> b) -> a -> b
$ if b
b b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
forall a. Monoid a => a
mempty
  then Redis (Either Reply Integer) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Integer) -> Redis ())
-> Redis (Either Reply Integer) -> Redis ()
forall a b. (a -> b) -> a -> b
$ [ByteString] -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
[ByteString] -> m (f Integer)
Redis.del [ a -> ByteString
k a
a ]
  else Redis (Either Reply Status) -> Redis ()
forall (f :: * -> *) a. Functor f => f a -> f ()
ignore (Redis (Either Reply Status) -> Redis ())
-> Redis (Either Reply Status) -> Redis ()
forall a b. (a -> b) -> a -> b
$ ByteString -> Integer -> ByteString -> Redis (Either Reply Status)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> Integer -> ByteString -> m (f Status)
Redis.setex (a -> ByteString
k a
a) Integer
t b
ByteString
b

-- | Increment an Integer in Redis. Empty values are treated as 0.
incr :: MonadRedis m => RedisIntegral a b -> a -> m b
incr :: RedisIntegral a b -> a -> m b
incr (RKeyValueInteger a -> ByteString
p b -> Integer
_ Integer -> b
d) =
    (Integer -> b) -> m Integer -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> b
d
  (m Integer -> m b) -> (a -> m Integer) -> a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Redis (Either Reply Integer) -> m Integer
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap
  (Redis (Either Reply Integer) -> m Integer)
-> (a -> Redis (Either Reply Integer)) -> a -> m Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> m (f Integer)
Redis.incr
  (ByteString -> Redis (Either Reply Integer))
-> (a -> ByteString) -> a -> Redis (Either Reply Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
p

-- | Increment an Integer in Redis by a specific amount. Empty values are treated as 0.
incrby :: MonadRedis m => RedisIntegral a b -> a -> b -> m b
incrby :: RedisIntegral a b -> a -> b -> m b
incrby (RKeyValueInteger a -> ByteString
p b -> Integer
e Integer -> b
d) a
k =
    (Integer -> b) -> m Integer -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> b
d
  (m Integer -> m b) -> (b -> m Integer) -> b -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Redis (Either Reply Integer) -> m Integer
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap
  (Redis (Either Reply Integer) -> m Integer)
-> (b -> Redis (Either Reply Integer)) -> b -> m Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Integer -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> Integer -> m (f Integer)
Redis.incrby (a -> ByteString
p a
k)
  (Integer -> Redis (Either Reply Integer))
-> (b -> Integer) -> b -> Redis (Either Reply Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Integer
e

-- | Decrement an Integer in Redis. Empty values are treated as 0.
decr :: MonadRedis m => RedisIntegral a b -> a -> m b
decr :: RedisIntegral a b -> a -> m b
decr (RKeyValueInteger a -> ByteString
p b -> Integer
_ Integer -> b
d) =
    (Integer -> b) -> m Integer -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> b
d
  (m Integer -> m b) -> (a -> m Integer) -> a -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Redis (Either Reply Integer) -> m Integer
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap
  (Redis (Either Reply Integer) -> m Integer)
-> (a -> Redis (Either Reply Integer)) -> a -> m Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> m (f Integer)
Redis.decr
  (ByteString -> Redis (Either Reply Integer))
-> (a -> ByteString) -> a -> Redis (Either Reply Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
p

-- | Decrement an Integer in Redis by a specific amount. Empty values are treated as 0.
decrby :: MonadRedis m => RedisIntegral a b -> a -> b -> m b
decrby :: RedisIntegral a b -> a -> b -> m b
decrby (RKeyValueInteger a -> ByteString
p b -> Integer
e Integer -> b
d) a
k =
    (Integer -> b) -> m Integer -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> b
d
  (m Integer -> m b) -> (b -> m Integer) -> b -> m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Redis (Either Reply Integer) -> m Integer
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap
  (Redis (Either Reply Integer) -> m Integer)
-> (b -> Redis (Either Reply Integer)) -> b -> m Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Integer -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> Integer -> m (f Integer)
Redis.decrby (a -> ByteString
p a
k)
  (Integer -> Redis (Either Reply Integer))
-> (b -> Integer) -> b -> Redis (Either Reply Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Integer
e

-- | Start and end indices are inclusive. Unlike @get@, the empty bytestring is returned if the key does not exist in Redis or if the specified range is out of range.
getrange :: MonadRedis m => RedisByteString a ByteString -> a -> Integer -> Integer -> m ByteString
getrange :: RedisByteString a ByteString
-> a -> Integer -> Integer -> m ByteString
getrange (RKeyValueByteString a -> ByteString
p) a
k Integer
start =
    Redis (Either Reply ByteString) -> m ByteString
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap
  (Redis (Either Reply ByteString) -> m ByteString)
-> (Integer -> Redis (Either Reply ByteString))
-> Integer
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Integer -> Integer -> Redis (Either Reply ByteString)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> Integer -> Integer -> m (f ByteString)
Redis.getrange (a -> ByteString
p a
k) Integer
start

-- | The @Integer@ paramter is the offset. Returns the length of the string after the command has been executed.
setrange :: MonadRedis m => RedisByteString a ByteString -> a -> Integer -> ByteString -> m Integer
setrange :: RedisByteString a ByteString
-> a -> Integer -> ByteString -> m Integer
setrange (RKeyValueByteString a -> ByteString
p) a
k Integer
start =
    Redis (Either Reply Integer) -> m Integer
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap
  (Redis (Either Reply Integer) -> m Integer)
-> (ByteString -> Redis (Either Reply Integer))
-> ByteString
-> m Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Integer -> ByteString -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> Integer -> ByteString -> m (f Integer)
Redis.setrange (a -> ByteString
p a
k) Integer
start

-- | Get the bit stored at the specified offset. Note that if no value exists in Redis or if the specified range is outside the defined range, @False@ will be returned by default.
getbit :: MonadRedis m => RedisByteString a ByteString -> a -> Integer -> m Bool
getbit :: RedisByteString a ByteString -> a -> Integer -> m Bool
getbit (RKeyValueByteString a -> ByteString
p) a
k =
    (Integer -> Bool) -> m Integer -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer
1Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
==)
  (m Integer -> m Bool)
-> (Integer -> m Integer) -> Integer -> m Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Redis (Either Reply Integer) -> m Integer
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap
  (Redis (Either Reply Integer) -> m Integer)
-> (Integer -> Redis (Either Reply Integer))
-> Integer
-> m Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Integer -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> Integer -> m (f Integer)
Redis.getbit (a -> ByteString
p a
k)

-- | Set the bit at the specified offset. If the offset is outside the existing defined range of the value, 0s are implicitly inserted to fill the intermediate space. Returns the existing value of this bit, as defined by the @getbit@ semantics above.
setbit :: MonadRedis m => RedisByteString a ByteString -> a -> Integer -> Bool -> m Bool
setbit :: RedisByteString a ByteString -> a -> Integer -> Bool -> m Bool
setbit (RKeyValueByteString a -> ByteString
p) a
k Integer
i =
    (Integer -> Bool) -> m Integer -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer
1Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
==)
  (m Integer -> m Bool) -> (Bool -> m Integer) -> Bool -> m Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Redis (Either Reply Integer) -> m Integer
forall (m :: * -> *) a.
MonadRedis m =>
Redis (Either Reply a) -> m a
unwrap
  (Redis (Either Reply Integer) -> m Integer)
-> (Bool -> Redis (Either Reply Integer)) -> Bool -> m Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Integer -> ByteString -> Redis (Either Reply Integer)
forall (m :: * -> *) (f :: * -> *).
RedisCtx m f =>
ByteString -> Integer -> ByteString -> m (f Integer)
Redis.setbit (a -> ByteString
p a
k) Integer
i
  (ByteString -> Redis (Either Reply Integer))
-> (Bool -> ByteString) -> Bool -> Redis (Either Reply Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
       Bool
True -> ByteString
"1"
       Bool
False -> ByteString
"0"