rados-haskell-3.0.2: librados haskell bindings

Copyright(c) 2010-2014 Anchor
LicenseBSD-3
MaintainerChristian Marie <christian@ponies.io>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

System.Rados.Monadic

Contents

Description

Monadic interface to librados, covers async read/writes, locks and atomic writes (ensure you use the build flag).

This is the monadic API, you may use the underlying internals or FFI calls via System.Rados.Base and System.Rados.FFI.

A simple complete example:

{-# LANGUAGE OverloadedStrings #-}
module Main where
import System.Rados
import Control.Exception
import qualified Data.ByteString.Char8 as B
main :: IO ()
main = do
    kitty <- runConnect Nothing (parseConfig "ceph.conf") $
        runPool "magic_pool" . runObject "an oid" $ do
            writeFull "hello kitty!"
            readFull
    either throwIO B.putStrLn (kitty :: Either RadosError B.ByteString)

Synopsis

Initialization

runConnect Source

Arguments

:: Maybe ByteString

Optional user name

-> (Connection -> IO (Maybe RadosError))

Configuration function

-> Connection a 
-> IO a 

Run an action within the Connection monad, this may throw a RadosError to IO if the connection or configuration fails.

runConnect Nothing (parseConfig "ceph.conf") $ runPool ...

parseConfig :: FilePath -> Connection -> IO (Maybe RadosError) Source

Read a config from a relative or absolute FilePath into a Connection.

Intended for use with runConnect.

parseArgv :: Connection -> IO (Maybe RadosError) Source

Read a config from the command line, note that no help flag will be provided.

parseEnv :: Connection -> IO (Maybe RadosError) Source

Parse the contents of the environment variable CEPH_ARGS as if they were ceph command line options.

runPool :: ByteString -> Pool a -> Connection a Source

Run an action within the Pool monad.

This may throw a RadosError to IO if the pool cannot be opened.

For the following examples, we shall use:

runOurPool :: Pool a -> IO a
runOurPool = 
    runConnect Nothing parseArgv . runPool "magic_pool"

Pool enumeration

objects :: Pool [ByteString] Source

Return a strict list of pool items.

unsafeObjects :: Pool [ByteString] Source

Return a lazy list of pool items. This list must be evaluated within the pool monad, if you wish to access the list outside of the pool monad you must fully evaluate it first (which is all objects does).

Reading

A note on signatures

In order to use these functions in any RadosReader monad, the type signatures have been made generic.

This allows the same API to be used for synchronous and asynchronous requests.

Thus, a1 and a2 below have different signatures:

runOurPool $ do
    a1 <- runObject "object" $ readFull
    a2 <- runAsync . runObject "object" $ readFull
    a3 <- look a2
    a1 :: Either RadosError ByteString
    a2 :: AsyncRead ByteString
    a3 :: Either RadosError ByteString

Reading API

class Monad m => RadosReader m wrapper | m -> wrapper where Source

Minimal complete definition

readChunk, stat, unWrap, wrapFail

Methods

readChunk Source

Arguments

:: Word64

Number of bytes to read

-> Word64

Offset to read from

-> m (wrapper ByteString) 

Read a chunk of data.

The possible types of this function are:

readChunk :: Word64 -> Word64 -> Object Pool (Either RadosError ByteString)
readChunk :: Word64 -> Word64 -> Object Async (AsyncRead ByteString)

readFull :: m (wrapper ByteString) Source

Read all avaliable data.

This is implemented with a stat followed by a read.

If you call this within the Object Async monad, the async request will wait for the result of the stat. The read itself will still be asynchronous.

The possible types of this function are:

readFull :: Object Pool (Either RadosError ByteString)
readFull :: Object Async (AsyncRead ByteString)

stat :: m (wrapper StatResult) Source

Retrive the file size and mtime of an object

The possible types of this function are:

stat :: Object Pool (Either RadosError StatResult)
stat :: Object Async (AsyncRead StatResult)

Writing

A note on signatures

In order to use these functions in any RadosWriter monad, the type signatures have been made generic.

This allows the same API to be used for synchronous and asynchronous requests.

Thus, a1 and a2 below have different signatures:

runOurPool $ do
    a1 <- runObject "object" $ writeFull "hai!"
    a2 <- runAsync . runObject "object" $ writeFull "hai!"
    a3 <- waitSafe a2
    a1 :: Maybe RadosError
    a2 :: AsyncWrite
    a3 :: Maybe RadosError

Writing API

class Monad m => RadosWriter m e | m -> e where Source

Methods

writeChunk Source

Arguments

:: Word64

Offset to write at

-> ByteString

Bytes to write

-> m e 

Write a chunk of data

The possible types of this function are:

writeChunk :: Word64 -> ByteString -> Object Pool (Maybe RadosError)
writeChunk :: Word64 -> ByteString -> Object A.AsyncWrite

writeFull :: ByteString -> m e Source

Atomically replace an object

The possible types of this function are:

writeFull :: ByteString -> Object Pool (Maybe RadosError)
writeFull :: ByteString -> Object A.AsyncWrite

append :: ByteString -> m e Source

Append to the end of an object

The possible types of this function are:

append :: ByteString -> Object Pool (Maybe RadosError)
append :: ByteString -> Object A.AsyncWrite

remove :: m e Source

Delete an object

The possible types of this function are:

remove :: Object Pool (Maybe RadosError)
remove :: Object A.AsyncWrite

Asynchronous requests

async :: PoolReader m => m a -> m (Async a) Source

Wrapper for the Control.Concurrent.Async library, you must be very careful to wait for the completion of all created async actions within the pool monad, or they will run with an invalid (cleaned up) context.

This will be rectified in future versions when reference counting is implemented, for now it is very unpolished and will require you to import qualified Control.Concurrent.Async.

runAsync :: PoolReader m => Async a -> m a Source

Any read/writes within this monad will be run asynchronously.

Return values of reads and writes are wrapped within AsyncRead or AsyncWrite respectively. You should extract the actual value from a read via look and waitSafe.

The asynchronous nature of error handling means that if you fail to inspect asynchronous writes with waitSafe, you will never know if they failed.

runOurPool . runAsync . runObject "a box" $ do
  wr <- writeFull "schrodinger's hai?\n"
  writeChunk 14 "cat" -- Don't care about the cat.
  print . isNothing <$> waitSafe wr
  r <- readFull >>= look
  either throwIO print r

waitSafe :: MonadIO m => AsyncWrite -> m (Maybe RadosError) Source

Wait until a Rados write has hit stable storage on all replicas, you will only know if a write has been successful when you inspect the AsyncWrite with waitSafe.

Provides a Maybe RadosError.

runOurPool . runAsync . runObject "a box" $ do
  async_request <- writeFull "schrodinger's hai?\n"
  liftIO $ putStrLn "Write is in flight!"
  maybe_error <- waitSafe async_request
  case maybe_error of
     Just e  -> liftIO $ print e
     Nothing -> return ()

waitComplete :: MonadIO m => AsyncWrite -> m (Maybe RadosError) Source

Wait until a Rados write has hit memory on all replicas. This is less safe than waitSafe, but still pretty safe. Safe.

look :: (MonadIO m, Typeable a) => AsyncRead a -> m (Either RadosError a) Source

Take an AsyncRead a and provide Either RadosError a This function is used for retrieving the value of an async read.

runOurPool . runAsync . runObject "a box" $ do
  async_read <- readFull
  liftIO $ putStrLn "Request is in flight!"
  either_error_or_read <- look async_read
  either (liftIO . throwIO) BS.putStrLn  either_error_or_read

runObject :: PoolReader m => ByteString -> Object m a -> m a Source

Run an action within the 'Object m' monad, where m is the caller's context.

(runOurPool . runObject "an oid" :: Object Pool a -> IO a
(runOurPool . runAsync . runObject "an oid") :: Object Async a -> IO a

Locking

withExclusiveLock Source

Arguments

:: ByteString

Object ID

-> ByteString

Name of lock

-> ByteString

Description of lock (debugging)

-> Maybe Double

Optional duration of lock

-> Pool a

Action to perform with lock

-> Pool a 

Perform an action with an exclusive lock.

withSharedLock Source

Arguments

:: ByteString

Object ID

-> ByteString

Name of lock

-> ByteString

Description of lock (debugging)

-> ByteString

Tag for lock holder (debugging)

-> Maybe Double

Optional duration of lock

-> Pool a

Action to perform with lock

-> Pool a 

Perform an action with an shared lock.

Types

Data types

data StatResult Source

The result of a stat, access the contents with modifyTime and fileSize

Instances

data AsyncRead a Source

A read request in flight, access the contents of the read with look

data AsyncWrite Source

A write request in flight, access a possible error with waitSafe

Monads

Exceptions

This library should never throw an error within runPool, runPool itself may throw a RadosError should it have a problem opening the given pool.

data RadosError Source

An error indicated by librados, usually in the form of a negative return value

Constructors

Unknown 

Fields

errno :: Int

Error number (positive)

cFunction :: String

The underlying C function

strerror :: String

The "nice" error message.

NoEntity

Usually returned if a file does not exist

Fields

errno :: Int

Error number (positive)

cFunction :: String

The underlying C function

strerror :: String

The "nice" error message.

Exists

Returned if a file already exists, and should not.

Fields

errno :: Int

Error number (positive)

cFunction :: String

The underlying C function

strerror :: String

The "nice" error message.

Canceled

Returned in the event of a failed atomic transaction

Fields

errno :: Int

Error number (positive)

cFunction :: String

The underlying C function

strerror :: String

The "nice" error message.

Range

A value was out of range, returned when reading or writing from/to invalid regions.

Fields

errno :: Int

Error number (positive)

cFunction :: String

The underlying C function

strerror :: String

The "nice" error message.

User 

Fields

message :: String
 

Re-exports

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.