| Portability | unknown |
|---|---|
| Stability | experimental |
| Maintainer | n.ohkawa@gmail.com |
| Safe Haskell | None |
Database.Monarch
Description
Provide TokyoTyrant monadic access interface.
- type Monarch = MonarchT IO
- data MonarchT m a
- data Connection
- type ConnectionPool = Pool Connection
- withMonarchConn :: (MonadBaseControl IO m, MonadIO m) => String -> Int -> (Connection -> m a) -> m a
- withMonarchPool :: (MonadBaseControl IO m, MonadIO m) => String -> Int -> Int -> (ConnectionPool -> m a) -> m a
- runMonarchConn :: (MonadBaseControl IO m, MonadIO m) => MonarchT m a -> Connection -> m (Either Code a)
- runMonarchPool :: (MonadBaseControl IO m, MonadIO m) => MonarchT m a -> ConnectionPool -> m (Either Code a)
- data ExtOption
- data RestoreOption = ConsistencyChecking
- data MiscOption = NoUpdateLog
- data Code
- class Monad m => MonadMonarch m where
- put :: ByteString -> ByteString -> m ()
- multiplePut :: [(ByteString, ByteString)] -> m ()
- putKeep :: ByteString -> ByteString -> m ()
- putCat :: ByteString -> ByteString -> m ()
- putShiftLeft :: ByteString -> ByteString -> Int -> m ()
- putNoResponse :: ByteString -> ByteString -> m ()
- out :: ByteString -> m ()
- multipleOut :: [ByteString] -> m ()
- get :: ByteString -> m (Maybe ByteString)
- multipleGet :: [ByteString] -> m [(ByteString, ByteString)]
- valueSize :: ByteString -> m (Maybe Int)
- iterInit :: m ()
- iterNext :: m (Maybe ByteString)
- forwardMatchingKeys :: ByteString -> Maybe Int -> m [ByteString]
- addInt :: ByteString -> Int -> m Int
- addDouble :: ByteString -> Double -> m Double
- ext :: ByteString -> [ExtOption] -> ByteString -> ByteString -> m ByteString
- sync :: m ()
- optimize :: ByteString -> m ()
- vanish :: m ()
- copy :: ByteString -> m ()
- restore :: Integral a => ByteString -> a -> [RestoreOption] -> m ()
- setMaster :: Integral a => ByteString -> Int -> a -> [RestoreOption] -> m ()
- recordNum :: m Int64
- size :: m Int64
- status :: m ByteString
- misc :: ByteString -> [MiscOption] -> [ByteString] -> m [ByteString]
Documentation
The Monarch monad transformer to provide TokyoTyrant access.
Instances
| MonadTrans MonarchT | |
| MonadTransControl MonarchT | |
| MonadBase base m => MonadBase base (MonarchT m) | |
| MonadBaseControl base m => MonadBaseControl base (MonarchT m) | |
| Monad m => MonadError Code (MonarchT m) | |
| Monad m => MonadReader Connection (MonarchT m) | |
| Monad m => Monad (MonarchT m) | |
| Functor m => Functor (MonarchT m) | |
| (Monad m, Functor m) => Applicative (MonarchT m) | |
| MonadIO m => MonadIO (MonarchT m) | |
| (MonadBaseControl IO m, MonadIO m) => MonadMonarch (MonarchT m) |
data Connection Source
Connection with TokyoTyrant
Instances
| Monad m => MonadReader Connection (MonarchT m) |
type ConnectionPool = Pool ConnectionSource
Connection pool with TokyoTyrant
Arguments
| :: (MonadBaseControl IO m, MonadIO m) | |
| => String | host |
| -> Int | port |
| -> (Connection -> m a) | |
| -> m a |
Create a TokyoTyrant connection and run the given action.
Don't use the given Connection outside the action.
Arguments
| :: (MonadBaseControl IO m, MonadIO m) | |
| => String | host |
| -> Int | port |
| -> Int | number of connections |
| -> (ConnectionPool -> m a) | |
| -> m a |
Create a TokyoTyrant connection pool and run the given action.
Don't use the given ConnectionPool outside the action.
Arguments
| :: (MonadBaseControl IO m, MonadIO m) | |
| => MonarchT m a | action |
| -> Connection | connection |
| -> m (Either Code a) |
Run action with a connection.
Arguments
| :: (MonadBaseControl IO m, MonadIO m) | |
| => MonarchT m a | action |
| -> ConnectionPool | connection pool |
| -> m (Either Code a) |
Run action with a unused connection from the pool.
Options for scripting extension
Constructors
| RecordLocking | record locking |
| GlobalLocking | global locking |
data MiscOption Source
Options for miscellaneous operation
Constructors
| NoUpdateLog | omission of update log |
Error code
class Monad m => MonadMonarch m whereSource
Monad Monarch interfaces
Methods
Arguments
| :: ByteString | key |
| -> ByteString | value |
| -> m () |
Store a record. If a record with the same key exists in the database, it is overwritten.
Arguments
| :: [(ByteString, ByteString)] | key & value pairs |
| -> m () |
Store records. If a record with the same key exists in the database, it is overwritten.
Arguments
| :: ByteString | key |
| -> ByteString | value |
| -> m () |
Store a new record. If a record with the same key exists in the database, this function has no effect.
Arguments
| :: ByteString | key |
| -> ByteString | value |
| -> m () |
Concatenate a value at the end of the existing record. If there is no corresponding record, a new record is created.
Arguments
| :: ByteString | key |
| -> ByteString | value |
| -> Int | width |
| -> m () |
Concatenate a value at the end of the existing record and shift it to the left. If there is no corresponding record, a new record is created.
Arguments
| :: ByteString | key |
| -> ByteString | value |
| -> m () |
Store a record without response. If a record with the same key exists in the database, it is overwritten.
Arguments
| :: ByteString | key |
| -> m () |
Remove a record.
Arguments
| :: [ByteString] | keys |
| -> m () |
Remove records.
Arguments
| :: ByteString | key |
| -> m (Maybe ByteString) |
Retrieve a record.
Arguments
| :: [ByteString] | keys |
| -> m [(ByteString, ByteString)] |
Retrieve records.
Arguments
| :: ByteString | key |
| -> m (Maybe Int) |
Get the size of the value of a record.
Initialize the iterator.
iterNext :: m (Maybe ByteString)Source
Get the next key of the iterator. The iterator can be updated by multiple connections and then it is not assured that every record is traversed.
Arguments
| :: ByteString | key prefix |
| -> Maybe Int | maximum number of keys to be fetched. |
| -> m [ByteString] |
Get forward matching keys.
Arguments
| :: ByteString | key |
| -> Int | value |
| -> m Int |
Add an integer to a record. If the corresponding record exists, the value is treated as an integer and is added to. If no record corresponds, a new record of the additional value is stored.
Arguments
| :: ByteString | key |
| -> Double | value |
| -> m Double |
Add a real number to a record. If the corresponding record exists, the value is treated as a real number and is added to. If no record corresponds, a new record of the additional value is stored.
Arguments
| :: ByteString | function |
| -> [ExtOption] | option flags |
| -> ByteString | key |
| -> ByteString | value |
| -> m ByteString |
Call a function of the script language extension.
Synchronize updated contents with the file and the device.
Arguments
| :: ByteString | parameter |
| -> m () |
Optimize the storage.
Remove all records.
Arguments
| :: ByteString | path |
| -> m () |
Copy the database file.
Arguments
| :: Integral a | |
| => ByteString | path |
| -> a | beginning time stamp in microseconds |
| -> [RestoreOption] | option flags |
| -> m () |
Restore the database file from the update log.
Arguments
| :: Integral a | |
| => ByteString | host |
| -> Int | port |
| -> a | beginning time stamp in microseconds |
| -> [RestoreOption] | option flags |
| -> m () |
Set the replication master.
Get the number of records.
Get the size of the database.
status :: m ByteStringSource
Get the status string of the database.
Arguments
| :: ByteString | function name |
| -> [MiscOption] | option flags |
| -> [ByteString] | arguments |
| -> m [ByteString] |
Call a versatile function for miscellaneous operations.
Instances
| (MonadBaseControl IO m, MonadIO m) => MonadMonarch (MonarchT m) | |
| (MonadBaseControl IO m, MonadIO m) => MonadMonarch (MockT m) |