module Network.Riak.JSON.Resolvable
(
Resolvable(..)
, ResolutionFailure(..)
, get
, getMany
, modify
, modify_
, put
, putIndexed
, put_
, putMany
, putMany_
) where
import Control.Monad.IO.Class
import Data.Aeson.Types (FromJSON(..), ToJSON(..))
import Network.Riak.Resolvable.Internal (ResolutionFailure(..), Resolvable(..))
import Network.Riak.Types.Internal hiding (MessageTag(..))
import qualified Network.Riak.JSON as J
import qualified Network.Riak.Resolvable.Internal as R
get :: (FromJSON c, ToJSON c, Resolvable c) =>
Connection -> Maybe BucketType -> Bucket -> Key -> R -> IO (Maybe (c, VClock))
get :: Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> IO (Maybe (c, VClock))
get = Get c
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> IO (Maybe (c, VClock))
forall a.
Resolvable a =>
Get a
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> IO (Maybe (a, VClock))
R.get Get c
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> IO (Maybe ([c], VClock))
J.get
{-# INLINE get #-}
getMany :: (FromJSON c, ToJSON c, Resolvable c)
=> Connection -> Maybe BucketType -> Bucket -> [Key] -> R -> IO [Maybe (c, VClock)]
getMany :: Connection
-> Maybe BucketType
-> BucketType
-> [BucketType]
-> R
-> IO [Maybe (c, VClock)]
getMany = (Connection
-> Maybe BucketType
-> BucketType
-> [BucketType]
-> R
-> IO [Maybe ([c], VClock)])
-> Connection
-> Maybe BucketType
-> BucketType
-> [BucketType]
-> R
-> IO [Maybe (c, VClock)]
forall a.
Resolvable a =>
(Connection
-> Maybe BucketType
-> BucketType
-> [BucketType]
-> R
-> IO [Maybe ([a], VClock)])
-> Connection
-> Maybe BucketType
-> BucketType
-> [BucketType]
-> R
-> IO [Maybe (a, VClock)]
R.getMany Connection
-> Maybe BucketType
-> BucketType
-> [BucketType]
-> R
-> IO [Maybe ([c], VClock)]
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> [BucketType]
-> R
-> IO [Maybe ([c], VClock)]
J.getMany
{-# INLINE getMany #-}
modify :: (FromJSON a, ToJSON a, Resolvable a) =>
Connection -> Maybe BucketType -> Bucket -> Key -> R -> W -> DW
-> (Maybe a -> IO (a,b))
-> IO (a,b)
modify :: Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> R
-> R
-> (Maybe a -> IO (a, b))
-> IO (a, b)
modify = Get a
-> Put a
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> R
-> R
-> (Maybe a -> IO (a, b))
-> IO (a, b)
forall (m :: * -> *) a b.
(MonadIO m, Resolvable a) =>
Get a
-> Put a
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> R
-> R
-> (Maybe a -> m (a, b))
-> m (a, b)
R.modify Get a
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> IO (Maybe ([c], VClock))
J.get Put a
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO ([c], VClock)
J.put
{-# INLINE modify #-}
modify_ :: (MonadIO m, FromJSON a, ToJSON a, Resolvable a) =>
Connection -> Maybe BucketType -> Bucket -> Key -> R -> W -> DW
-> (Maybe a -> m a) -> m a
modify_ :: Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> R
-> R
-> (Maybe a -> m a)
-> m a
modify_ = Get a
-> Put a
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> R
-> R
-> (Maybe a -> m a)
-> m a
forall (m :: * -> *) a.
(MonadIO m, Resolvable a) =>
Get a
-> Put a
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> R
-> R
-> (Maybe a -> m a)
-> m a
R.modify_ Get a
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> R
-> IO (Maybe ([c], VClock))
J.get Put a
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO ([c], VClock)
J.put
{-# INLINE modify_ #-}
put :: (FromJSON c, ToJSON c, Resolvable c) =>
Connection -> Maybe BucketType -> Bucket -> Key -> Maybe VClock -> c -> W -> DW
-> IO (c, VClock)
put :: Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO (c, VClock)
put = Put c
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO (c, VClock)
forall a.
Resolvable a =>
Put a
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> a
-> R
-> R
-> IO (a, VClock)
R.put Put c
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO ([c], VClock)
J.put
{-# INLINE put #-}
putIndexed :: (FromJSON c, ToJSON c, Resolvable c)
=> Connection -> Maybe BucketType -> Bucket -> Key -> [IndexValue]
-> Maybe VClock -> c -> W -> DW
-> IO (c, VClock)
putIndexed :: Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> [IndexValue]
-> Maybe VClock
-> c
-> R
-> R
-> IO (c, VClock)
putIndexed Connection
c Maybe BucketType
bt BucketType
b BucketType
k [IndexValue]
ixs Maybe VClock
vc c
cont R
w' R
dw' =
Put c
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO (c, VClock)
forall a.
Resolvable a =>
Put a
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> a
-> R
-> R
-> IO (a, VClock)
R.put (\Connection
conn Maybe BucketType
btype BucketType
bucket' BucketType
key' Maybe VClock
mvclock c
val R
w R
dw ->
Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> [IndexValue]
-> Maybe VClock
-> c
-> R
-> R
-> IO ([c], VClock)
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> [IndexValue]
-> Maybe VClock
-> c
-> R
-> R
-> IO ([c], VClock)
J.putIndexed Connection
conn Maybe BucketType
btype BucketType
bucket' BucketType
key' [IndexValue]
ixs Maybe VClock
mvclock c
val R
w R
dw)
Connection
c Maybe BucketType
bt BucketType
b BucketType
k Maybe VClock
vc c
cont R
w' R
dw'
{-# INLINE putIndexed #-}
put_ :: (FromJSON c, ToJSON c, Resolvable c) =>
Connection -> Maybe BucketType -> Bucket -> Key -> Maybe VClock -> c -> W -> DW
-> IO ()
put_ :: Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO ()
put_ = (Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO ([c], VClock))
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO ()
forall a.
Resolvable a =>
(Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> a
-> R
-> R
-> IO ([a], VClock))
-> Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> a
-> R
-> R
-> IO ()
R.put_ Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO ([c], VClock)
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> BucketType
-> Maybe VClock
-> c
-> R
-> R
-> IO ([c], VClock)
J.put
{-# INLINE put_ #-}
putMany :: (FromJSON c, ToJSON c, Resolvable c) =>
Connection -> Maybe BucketType -> Bucket -> [(Key, Maybe VClock, c)] -> W -> DW
-> IO [(c, VClock)]
putMany :: Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO [(c, VClock)]
putMany = (Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO [([c], VClock)])
-> Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO [(c, VClock)]
forall a.
Resolvable a =>
(Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, a)]
-> R
-> R
-> IO [([a], VClock)])
-> Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, a)]
-> R
-> R
-> IO [(a, VClock)]
R.putMany Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO [([c], VClock)]
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO [([c], VClock)]
J.putMany
{-# INLINE putMany #-}
putMany_ :: (FromJSON c, ToJSON c, Resolvable c) =>
Connection -> Maybe BucketType -> Bucket -> [(Key, Maybe VClock, c)] -> W -> DW
-> IO ()
putMany_ :: Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO ()
putMany_ = (Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO [([c], VClock)])
-> Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO ()
forall a.
Resolvable a =>
(Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, a)]
-> R
-> R
-> IO [([a], VClock)])
-> Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, a)]
-> R
-> R
-> IO ()
R.putMany_ Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO [([c], VClock)]
forall c.
(FromJSON c, ToJSON c) =>
Connection
-> Maybe BucketType
-> BucketType
-> [(BucketType, Maybe VClock, c)]
-> R
-> R
-> IO [([c], VClock)]
J.putMany
{-# INLINE putMany_ #-}