riak-1.1.1.0: A Haskell client for the Riak decentralized data store

Copyright(c) 2011 MailRank, Inc.
LicenseApache
MaintainerMark Hibberd <mark@hibberd.id.au>, Nathan Hunter <nhunter@janrain.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Network.Riak

Contents

Description

A client for the Riak decentralized data store.

The functions in this module use JSON as the storage representation, and automatically perform conflict resolution during storage and retrieval.

This library is organized to allow a tradeoff between power and ease of use. If you would like a different degree of automation with storage and conflict resolution, you may want to use one of the following modules (ranked from easiest to most tricky to use):

Network.Riak.JSON.Resolvable
JSON for storage, automatic conflict resolution. (This module actually re-exports its definitions.) This is the easiest module to work with.
Network.Riak.JSON
JSON for storage, manual conflict resolution.
Network.Riak.Value.Resolvable
More complex (but still automatic) storage, automatic conflict resolution.
Network.Riak.Value
More complex (but still automatic) storage, manual conflict resolution.
Network.Riak.Basic
manual storage, manual conflict resolution. This is the most demanding module to work with, as you must encode and decode data yourself, and handle all conflict resolution yourself.
Network.Riak.CRDT
CRDT operations.

A short getting started guide is available at http://docs.basho.com/riak/latest/dev/taste-of-riak/haskell/

Synopsis

Client configuration and identification

type ClientID = ByteString Source #

A client identifier. This is used by the Riak cluster when logging vector clock changes, and should be unique for each client.

data Client Source #

Constructors

Client 

Fields

Instances

defaultClient :: Client Source #

Default client configuration. Talks to localhost, port 8087, with a randomly chosen client ID.

getClientID :: Connection -> IO ClientID Source #

Find out from the server what client ID this connection is using.

Connection management

data Connection Source #

A connection to a Riak server.

Constructors

Connection 

Fields

connect :: Client -> IO Connection Source #

Connect to a server.

disconnect :: Connection -> IO () Source #

Disconnect from a server.

ping :: Connection -> IO () Source #

Check to see if the connection to the server is alive.

getServerInfo :: Connection -> IO ServerInfo Source #

Retrieve information about the server.

Data management

data Quorum Source #

A read/write quorum. The quantity of replicas that must respond to a read or write request before it is considered successful. This is defined as a bucket property or as one of the relevant parameters to a single request (R,W,DW,RW).

Constructors

Default

Use the default quorum settings for the bucket.

One

Success after one server has responded.

Quorum

Success after a quorum of servers has responded.

All

Success after all servers have responded.

class Show a => Resolvable a where Source #

A type that can automatically resolve a vector clock conflict between two or more versions of a value.

Instances must be symmetric in their behaviour, such that the following law is obeyed:

resolve a b == resolve b a

Otherwise, there are no restrictions on the behaviour of resolve. The result may be a, b, a value derived from a and b, or something else.

If several conflicting siblings are found, resolve will be applied over all of them using a fold, to yield a single "winner".

Minimal complete definition

resolve

Methods

resolve :: a -> a -> a Source #

Resolve a conflict between two values.

get :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> Key -> R -> IO (Maybe (c, VClock)) Source #

Retrieve a single value. If conflicting values are returned, resolve is used to choose a winner.

getMany :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> [Key] -> R -> IO [Maybe (c, VClock)] Source #

Retrieve multiple values. If conflicting values are returned for a key, resolve is used to choose a winner.

getByIndex :: Connection -> Bucket -> IndexQuery -> IO [Key] Source #

Retrieve list of keys matching some index query.

addIndexes :: [IndexValue] -> Content -> Content Source #

Add indexes to a content value for a further put request.

modify Source #

Arguments

:: (FromJSON a, ToJSON a, Resolvable a) 
=> Connection 
-> Maybe BucketType 
-> Bucket 
-> Key 
-> R 
-> W 
-> DW 
-> (Maybe a -> IO (a, b))

Modification function. Called with Just the value if the key is present, Nothing otherwise.

-> IO (a, b) 

Modify a single value. The value, if any, is retrieved using get; conflict resolution is performed if necessary. The modification function is called on the resulting value, and its result is stored using put, which may again perform conflict resolution.

The result of this function is whatever was returned by put, along with the auxiliary value returned by the modification function.

If the put phase of this function gives up due to apparently being stuck in a conflict resolution loop, it will throw a ResolutionFailure exception.

modify_ :: (MonadIO m, FromJSON a, ToJSON a, Resolvable a) => Connection -> Maybe BucketType -> Bucket -> Key -> R -> W -> DW -> (Maybe a -> m a) -> m a Source #

Modify a single value. The value, if any, is retrieved using get; conflict resolution is performed if necessary. The modification function is called on the resulting value, and its result is stored using put, which may again perform conflict resolution.

The result of this function is whatever was returned by put.

If the put phase of this function gives up due to apparently being stuck in a conflict resolution loop, it will throw a ResolutionFailure exception.

delete :: Connection -> Maybe BucketType -> Bucket -> Key -> RW -> IO () Source #

Delete a value.

Low-level modification functions

put :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> Key -> Maybe VClock -> c -> W -> DW -> IO (c, VClock) Source #

Store a single value, automatically resolving any vector clock conflicts that arise. A single invocation of this function may involve several roundtrips to the server to resolve conflicts.

If a conflict arises, a winner will be chosen using resolve, and the winner will be stored; this will be repeated until no conflict occurs or a (fairly large) number of retries has been attempted without success.

If this function gives up due to apparently being stuck in a conflict resolution loop, it will throw a ResolutionFailure exception.

putIndexed :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> Key -> [IndexValue] -> Maybe VClock -> c -> W -> DW -> IO (c, VClock) Source #

Store a single value indexed.

putMany :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> [(Key, Maybe VClock, c)] -> W -> DW -> IO [(c, VClock)] Source #

Store multiple values, resolving any vector clock conflicts that arise. A single invocation of this function may involve several roundtrips to the server to resolve conflicts.

If any conflicts arise, a winner will be chosen in each case using resolve, and the winners will be stored; this will be repeated until either no conflicts occur or a (fairly large) number of retries has been attempted without success.

For each original value to be stored, the final value that was stored at the end of any conflict resolution is returned.

If this function gives up due to apparently being stuck in a loop, it will throw a ResolutionFailure exception.

Metadata

listBuckets :: Connection -> Maybe BucketType -> IO (Seq Bucket) Source #

List the buckets in the cluster.

Note: this operation is expensive. Do not use it in production.

foldKeys :: MonadIO m => Connection -> Maybe BucketType -> Bucket -> (a -> Key -> m a) -> a -> m a Source #

Fold over the keys in a bucket.

Note: this operation is expensive. Do not use it in production.

getBucket :: Connection -> Maybe BucketType -> Bucket -> IO BucketProps Source #

Retrieve the properties of a bucket.

setBucket :: Connection -> Maybe BucketType -> Bucket -> BucketProps -> IO () Source #

Store new properties for a bucket.

Map/reduce

mapReduce :: Connection -> Job -> (a -> MapReduce -> a) -> a -> IO a Source #

Run a MapReduce job. Its result is consumed via a strict left fold.

Types

data IndexQuery Source #

Index query. Can be exact or range, int or bin. Index name should not contain the "_bin" or "_int" part, since it's determined from data constructor.