rocksdb-query-0.1.2: RocksDB database querying library for Haskell

Safe HaskellNone
LanguageHaskell2010

Database.RocksDB.Query

Synopsis

Documentation

class Key key Source #

class KeyValue key value Source #

retrieve :: (MonadIO m, KeyValue key value, Serialize key, Serialize value) => DB -> Maybe Snapshot -> key -> m (Maybe value) Source #

Read a value from the database, or Nothing if not found.

matchRecursive :: (MonadIO m, KeyValue key value, Serialize key, Serialize value) => key -> Iterator -> ConduitT () (key, value) m () Source #

matching :: (MonadResource m, KeyValue key value, Serialize key, Serialize value) => DB -> Maybe Snapshot -> key -> ConduitT () (key, value) m () Source #

Use the passed key to filter all the elements whose key prefix match it. Use a sum type for keys that allows to set a version of the key that has a shorter length when serialized..

#!/usr/bin/env stack
{- stack
  --resolver lts-12.9
  --install-ghc
  runghc
  --package base
  --package cereal
  --package conduit
  --package rocksdb-haskell-1.0.1
  --package rocksdb-query-0.1.2
  --
  -hide-all-packages
  -}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
import           Conduit
import           Data.Serialize
import           Database.RocksDB       (createIfMissing, defaultOptions, open)
import           Database.RocksDB.Query (KeyValue, insert, matching)
data MyKey = ShortKey String | FullKey String String deriving Show
instance Serialize MyKey where
  put (ShortKey a)  = put a
  put (FullKey a b) = put a >> put b
  get = FullKey <$> get <*> get
instance KeyValue MyKey String
main = do
  db <- open "test-db" defaultOptions {createIfMissing = True}
  insert db (FullKey "hello" "world") "despite all my rage"
  Just record <- runResourceT . runConduit $
    matching db Nothing (ShortKey "hello") .| headC
  print (record :: (MyKey, String))

In this example you may serialize the ShortKey and match all the elements in the database that start with it as a prefix. Deserializing will always yield a FullKey.

matchingSkip :: (MonadResource m, KeyValue key value, Serialize key, Serialize value) => DB -> Maybe Snapshot -> key -> key -> ConduitT () (key, value) m () Source #

Like matching, but skip to the second key passed as argument, or after if there is no entry for the second key.

insert :: (MonadIO m, KeyValue key value, Serialize key, Serialize value) => DB -> key -> value -> m () Source #

Insert a record into the database.

remove :: (MonadIO m, Key key, Serialize key) => DB -> key -> m () Source #

Delete a record from the database.

insertOp :: (KeyValue key value, Serialize key, Serialize value) => key -> value -> BatchOp Source #

Get the BatchOp to insert a record in the database.

deleteOp :: (Key key, Serialize key) => key -> BatchOp Source #

Get the BatchOp to delete a record from the database.

writeBatch :: MonadIO m => DB -> WriteBatch -> m () Source #

Write a batch to the database.

firstMatching :: (MonadUnliftIO m, KeyValue key value, Serialize key, Serialize value) => DB -> Maybe Snapshot -> key -> m (Maybe (key, value)) Source #

Like matching but return the first element only.

firstMatchingSkip :: (MonadUnliftIO m, KeyValue key value, Serialize key, Serialize value) => DB -> Maybe Snapshot -> key -> key -> m (Maybe (key, value)) Source #

Like matchingSkip, but return the first element only.

matchingAsList :: (MonadUnliftIO m, KeyValue key value, Serialize key, Serialize value) => DB -> Maybe Snapshot -> key -> m [(key, value)] Source #

Like matching but return a list.

matchingSkipAsList :: (MonadUnliftIO m, KeyValue key value, Serialize key, Serialize value) => DB -> Maybe Snapshot -> key -> key -> m [(key, value)] Source #

Like matchingSkip, but return a list.