Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.Memcached.Binary.Either
- data Connection
- withConnection :: ConnectInfo -> (Connection -> IO a) -> IO a
- connect :: ConnectInfo -> IO Connection
- close :: Connection -> IO ()
- get :: Key -> Connection -> IO (Either MemcachedException (Flags, Value))
- get_ :: Key -> Connection -> IO (Either MemcachedException Value)
- set :: Flags -> Expiry -> Key -> Value -> Connection -> IO (Maybe MemcachedException)
- add :: Flags -> Expiry -> Key -> Value -> Connection -> IO (Maybe MemcachedException)
- replace :: Flags -> Expiry -> Key -> Value -> Connection -> IO (Maybe MemcachedException)
- delete :: Key -> Connection -> IO (Maybe MemcachedException)
- increment :: Expiry -> Key -> Delta -> Initial -> Connection -> IO (Either MemcachedException Counter)
- decrement :: Expiry -> Key -> Delta -> Initial -> Connection -> IO (Either MemcachedException Counter)
- flushAll :: Connection -> IO (Maybe MemcachedException)
- version :: Connection -> IO (Either MemcachedException Version)
- versionString :: Connection -> IO (Either MemcachedException ByteString)
- noOp :: Connection -> IO (Maybe MemcachedException)
- append :: Key -> Value -> Connection -> IO (Maybe MemcachedException)
- prepend :: Key -> Value -> Connection -> IO (Maybe MemcachedException)
- touch :: Expiry -> Key -> Connection -> IO (Maybe MemcachedException)
- getAndTouch :: Expiry -> Key -> Connection -> IO (Either MemcachedException (Flags, Value))
- getAndTouch_ :: Expiry -> Key -> Connection -> IO (Either MemcachedException Value)
- modify :: Expiry -> Key -> (Flags -> Value -> (Flags, Value, a)) -> Connection -> IO (Either MemcachedException a)
- modify_ :: Expiry -> Key -> (Flags -> Value -> (Flags, Value)) -> Connection -> IO (Maybe MemcachedException)
- module Database.Memcached.Binary.Types
- module Database.Memcached.Binary.Types.Exception
- module Data.Default.Class
- module Network
connection
data Connection Source
withConnection :: ConnectInfo -> (Connection -> IO a) -> IO a Source
connect :: ConnectInfo -> IO Connection Source
close :: Connection -> IO () Source
get
get :: Key -> Connection -> IO (Either MemcachedException (Flags, Value)) Source
get_ :: Key -> Connection -> IO (Either MemcachedException Value) Source
set
set :: Flags -> Expiry -> Key -> Value -> Connection -> IO (Maybe MemcachedException) Source
add :: Flags -> Expiry -> Key -> Value -> Connection -> IO (Maybe MemcachedException) Source
replace :: Flags -> Expiry -> Key -> Value -> Connection -> IO (Maybe MemcachedException) Source
delete
delete :: Key -> Connection -> IO (Maybe MemcachedException) Source
increment/decrement
increment :: Expiry -> Key -> Delta -> Initial -> Connection -> IO (Either MemcachedException Counter) Source
decrement :: Expiry -> Key -> Delta -> Initial -> Connection -> IO (Either MemcachedException Counter) Source
flush
flushAll :: Connection -> IO (Maybe MemcachedException) Source
flush all value.
version
version :: Connection -> IO (Either MemcachedException Version) Source
versionString :: Connection -> IO (Either MemcachedException ByteString) Source
get version string.
noOp
noOp :: Connection -> IO (Maybe MemcachedException) Source
noop(use for keepalive).
append/prepend
append :: Key -> Value -> Connection -> IO (Maybe MemcachedException) Source
prepend :: Key -> Value -> Connection -> IO (Maybe MemcachedException) Source
touch
touch :: Expiry -> Key -> Connection -> IO (Maybe MemcachedException) Source
change expiry.
getAndTouch :: Expiry -> Key -> Connection -> IO (Either MemcachedException (Flags, Value)) Source
get value/change expiry.
getAndTouch_ :: Expiry -> Key -> Connection -> IO (Either MemcachedException Value) Source
get value/change expiry.
modify
modify :: Expiry -> Key -> (Flags -> Value -> (Flags, Value, a)) -> Connection -> IO (Either MemcachedException a) Source
modify value in transaction.
modify_ :: Expiry -> Key -> (Flags -> Value -> (Flags, Value)) -> Connection -> IO (Maybe MemcachedException) Source
modify value in transaction.
reexports
def
module Data.Default.Class
PortID(..)
module Network