snaplet-riak-0.2.1.0: A Snaplet for the Riak database

Safe HaskellNone
LanguageHaskell98

Snap.Snaplet.Riak

Description

A Snaplet for using the Riak database (via the riak package) Modelled on snaplet-postgresql-simple

Synopsis

Documentation

data RiakDB Source

Riak Snaplet state. Stores a connection pool shared between handlers.

withRiak :: HasRiak m => (Connection -> IO a) -> m a Source

Perform an action using a Riak Connection in the Riak snaplet

result <- withRiak $ \c -> get c "myBucket" "myKey" Default

riakInit :: Pool -> SnapletInit b RiakDB Source

Initialize the Riak snaplet

riakCreate :: Client -> Int -> NominalDiffTime -> Int -> SnapletInit b RiakDB Source

Thin wrapper around create to run within SnapletInit

class MonadIO m => HasRiak m where Source

A class which, when implemented, allows the wrapper functions below to be used without explicitly managing the connection and having to use liftIO.

get :: (HasRiak m, FromJSON a, ToJSON a, Resolvable a) => Bucket -> Key -> R -> m (Maybe (a, VClock)) Source

getMany :: (HasRiak m, FromJSON a, ToJSON a, Resolvable a) => Bucket -> [Key] -> R -> m [Maybe (a, VClock)] Source

modify :: (HasRiak m, FromJSON a, ToJSON a, Resolvable a) => Bucket -> Key -> R -> W -> DW -> (Maybe a -> IO (a, b)) -> m (a, b) Source

modify_ :: (HasRiak m, FromJSON a, ToJSON a, Resolvable a) => Bucket -> Key -> R -> W -> DW -> (Maybe a -> IO a) -> m a Source

delete :: HasRiak m => Bucket -> Key -> RW -> m () Source

put :: (HasRiak m, Eq a, FromJSON a, ToJSON a, Resolvable a) => Bucket -> Key -> Maybe VClock -> a -> W -> DW -> m (a, VClock) Source

putMany :: (HasRiak m, Eq a, FromJSON a, ToJSON a, Resolvable a) => Bucket -> [(Key, Maybe VClock, a)] -> W -> DW -> m [(a, VClock)] Source

foldKeys :: HasRiak m => Bucket -> (a -> Key -> IO a) -> a -> m a Source

mapReduce :: HasRiak m => Job -> (a -> MapReduce -> a) -> a -> m a Source