memcache-conduit-0.0.3: Conduit library for memcache procotol

Safe HaskellNone
LanguageHaskell98

Data.Conduit.Memcache

Description

This package provides conduit functions for memcache protocol. For detail, please see hemcached sample code (sample/hemcached.hs).

type Key = BS.ByteString
type Version = Word64
type Value = (Version, BS.ByteString)
type HashTable k v = H.BasicHashTable k v


main :: IO ()
main = do
  ht <- H.new :: IO (HashTable Key Value)
  htVar <- newMVar ht
  runResourceT $ do
    runTCPServer (serverSettings 11211 HostAny) $ \appData -> do
      (appSource appData)
        $$ getOpText
        =$ process htVar
        =$ putResponseText
        =$ (appSink appData)

process :: (MonadResource m, MonadIO m) => MVar (HashTable Key Value) -> ConduitM (Either BS.ByteString Op) Response m ()
process = ...

Synopsis

Documentation

getOpText :: (MonadIO m, MonadThrow m) => ConduitM ByteString (Either ByteString Op) m () Source

This conduit parses command messages in text protocol and generates Network.Memcache.Op.

input
Data.ByteString.Char8.ByteString
output
Network.Memcache.Op

getResponseText :: (MonadIO m, MonadThrow m) => ConduitM ByteString (Either ByteString Response) m () Source

This conduit parses response messages in text protocol and generates Network.Memcache.Response.

input
Data.ByteString.Char8.ByteString
output
Network.Memcache.Response

putOpText :: MonadIO m => ConduitM Op ByteString m () Source

This conduit generates command messages in text protocol from Network.Memcache.Op stream

input
Network.Memcache.Op
output
Data.ByteString.Char8.ByteString

putResponseText :: MonadIO m => ConduitM Response ByteString m () Source

This generates response messages in text protocol from Network.Memcache.Response stream

input
Network.Memcache.Response
output
Data.ByteString.Char8.ByteString