| Copyright | (c) 2011 MailRank Inc. | 
|---|---|
| License | Apache | 
| Maintainer | Mark Hibberd <mark@hibberd.id.au>, Nathan Hunter <nhunter@janrain.com> | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Network.Riak.JSON.Resolvable
Contents
Description
This module allows storage and retrieval of JSON-encoded data.
Functions automatically resolve conflicts using Resolvable
 instances.  For instance, if a get returns three siblings, a
 winner will be chosen using resolve.  If a put results in a
 conflict, a winner will be chosen using resolve, and the winner
 will be put; this will be repeated until either no conflict
 occurs or the process has been repeated too many times.
Synopsis
- class Show a => Resolvable a where- resolve :: a -> a -> a
 
- data ResolutionFailure = RetriesExceeded
- get :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> Key -> R -> IO (Maybe (c, VClock))
- getMany :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> [Key] -> R -> IO [Maybe (c, VClock)]
- modify :: (FromJSON a, ToJSON a, Resolvable a) => Connection -> Maybe BucketType -> Bucket -> Key -> R -> W -> DW -> (Maybe a -> IO (a, b)) -> IO (a, b)
- modify_ :: (MonadIO m, FromJSON a, ToJSON a, Resolvable a) => Connection -> Maybe BucketType -> Bucket -> Key -> R -> W -> DW -> (Maybe a -> m a) -> m a
- put :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> Key -> Maybe VClock -> c -> W -> DW -> IO (c, VClock)
- putIndexed :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> Key -> [IndexValue] -> Maybe VClock -> c -> W -> DW -> IO (c, VClock)
- put_ :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> Key -> Maybe VClock -> c -> W -> DW -> IO ()
- putMany :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> [(Key, Maybe VClock, c)] -> W -> DW -> IO [(c, VClock)]
- putMany_ :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> [(Key, Maybe VClock, c)] -> W -> DW -> IO ()
Documentation
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".
Instances
| Resolvable a => Resolvable (Maybe a) Source # | |
| (Show a, Monoid a) => Resolvable (ResolvableMonoid a) Source # | |
| Defined in Network.Riak.Resolvable.Internal Methods resolve :: ResolvableMonoid a -> ResolvableMonoid a -> ResolvableMonoid a Source # | |
data ResolutionFailure Source #
Automated conflict resolution failed.
Constructors
| RetriesExceeded | Too many attempts were made to resolve a conflict, with each attempt resulting in another conflict. The number of retries that the library will attempt is high
 (64). This makes it extremely unlikely that this exception will
 be thrown during normal application operation.  Instead, this
 exception is most likely to be thrown as a result of a bug in
 your application code, for example if your  | 
Instances
| Eq ResolutionFailure Source # | |
| Defined in Network.Riak.Resolvable.Internal Methods (==) :: ResolutionFailure -> ResolutionFailure -> Bool # (/=) :: ResolutionFailure -> ResolutionFailure -> Bool # | |
| Show ResolutionFailure Source # | |
| Defined in Network.Riak.Resolvable.Internal Methods showsPrec :: Int -> ResolutionFailure -> ShowS # show :: ResolutionFailure -> String # showList :: [ResolutionFailure] -> ShowS # | |
| Exception ResolutionFailure Source # | |
| Defined in Network.Riak.Resolvable.Internal Methods toException :: ResolutionFailure -> SomeException # | |
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.
Arguments
| :: (FromJSON a, ToJSON a, Resolvable a) | |
| => Connection | |
| -> Maybe BucketType | |
| -> Bucket | |
| -> Key | |
| -> R | |
| -> W | |
| -> DW | |
| -> (Maybe a -> IO (a, b)) | Modification function.  Called with  | 
| -> 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.
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.
put_ :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> Key -> Maybe VClock -> c -> W -> DW -> IO () 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.
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.
putMany_ :: (FromJSON c, ToJSON c, Resolvable c) => Connection -> Maybe BucketType -> Bucket -> [(Key, Maybe VClock, c)] -> W -> DW -> IO () 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.
If this function gives up due to apparently being stuck in a loop,
 it will throw a ResolutionFailure exception.