foundationdb-haskell-0.1.0.0: FoundationDB C client bindings
Safe HaskellNone
LanguageHaskell2010

FoundationDB.Transaction

Description

This module contains the core of the FoundationDB transaction API, including all the basic functionality to create and run transactions. Transaction is a monad, and you will generally want to use it with do-notation.

{-# LANGUAGE OverloadedStrings #-}
import FoundationDB.Transaction
import Data.ByteString

-- | Sets and gets a key in one transaction. Returns the ByteString
-- "world".
myTransaction :: Transaction ByteString
myTransaction = do
  let mykey = "hello"
  set mykey "world"
  get mykey

Run your transactions with runTransaction in the IO monad.

The documentation in this library assumes that you already have some understanding of how to work with FoundationDB. If you don't, check out the official tutorial.

Synopsis

Transactions

data Transaction a Source #

A transaction monad. This is currently exported with a MonadIO instance, but using it comes with caveats:

  • runTransaction will retry your transaction in some cases, which means any IO in your transaction will be repeated. You can disable retries by setting maxRetries in TransactionConfig to 0.
  • Transactions have strict time limits, so slow IO operations should be avoided.

Instances

Instances details
Monad Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

(>>=) :: Transaction a -> (a -> Transaction b) -> Transaction b #

(>>) :: Transaction a -> Transaction b -> Transaction b #

return :: a -> Transaction a #

Functor Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

fmap :: (a -> b) -> Transaction a -> Transaction b #

(<$) :: a -> Transaction b -> Transaction a #

Applicative Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

pure :: a -> Transaction a #

(<*>) :: Transaction (a -> b) -> Transaction a -> Transaction b #

liftA2 :: (a -> b -> c) -> Transaction a -> Transaction b -> Transaction c #

(*>) :: Transaction a -> Transaction b -> Transaction b #

(<*) :: Transaction a -> Transaction b -> Transaction a #

MonadIO Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

liftIO :: IO a -> Transaction a #

MonadThrow Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

throwM :: Exception e => e -> Transaction a #

MonadCatch Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

catch :: Exception e => Transaction a -> (e -> Transaction a) -> Transaction a #

MonadMask Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

mask :: ((forall a. Transaction a -> Transaction a) -> Transaction b) -> Transaction b #

uninterruptibleMask :: ((forall a. Transaction a -> Transaction a) -> Transaction b) -> Transaction b #

generalBracket :: Transaction a -> (a -> ExitCase b -> Transaction c) -> (a -> Transaction b) -> Transaction (b, c) #

MonadBase IO Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

liftBase :: IO α -> Transaction α #

MonadBaseControl IO Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

Associated Types

type StM Transaction a #

MonadReader TransactionEnv Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

MonadError Error Transaction Source # 
Instance details

Defined in FoundationDB.Transaction

type StM Transaction a Source # 
Instance details

Defined in FoundationDB.Transaction

runTransaction :: Database -> Transaction a -> IO a Source #

Attempts to commit a transaction against the given database. If an unretryable error occurs, throws an Error. Attempts to retry the transaction for retryable errors.

runTransaction' :: Database -> Transaction a -> IO (Either Error a) Source #

Like runTransaction, but returns a sum instead of throwing an exception on errors.

data TransactionConfig Source #

Contains useful options that are not directly exposed by the C API (for options that are, see setOption).

Constructors

TransactionConfig 

Fields

  • idempotent :: Bool

    When set to True (default is False), running the transaction will retry even on errors where the transaction may have completed successfully. When False, the transaction will retry only when it is guaranteed that the transaction was not committed.

  • snapshotReads :: Bool

    When set to True (default is False), reads will see the effects of concurrent transactions, removing the default serializable isolation guarantee. To enable this feature selectively within a transaction, see withSnapshot.

  • getConflictingKeys :: Bool

    When set to True (default is False), if a transaction fails due to a conflict, the returned NotCommittedException will include a list of key ranges that caused the transaction to conflict. This has a performance impact on both the client and the cluster. Only supported on clients and clusters running v 6.3 and later. On earlier versions, the list will always be empty.

  • maxRetries :: Int

    Max number of times to retry retryable errors. After this many retries, MaxRetriesExceeded will be thrown to the caller of runTransaction.

  • timeout :: Int

    Max number of milliseconds the transaction is allowed to run. If this number is exceeded, the transaction fails with an error.

defaultConfig :: TransactionConfig Source #

A config for a non-idempotent transaction, allowing 5 retries, with a time limit of 500 milliseconds.

runTransactionWithConfig :: TransactionConfig -> Database -> Transaction a -> IO a Source #

Attempt to commit a transaction against the given database. If an unretryable error occurs, throws an Error. Attempts to retry the transaction for retryable errors according to the maxRetries setting in the provided TransactionConfig.

runTransactionWithConfig' :: TransactionConfig -> Database -> Transaction a -> IO (Either Error a) Source #

Attempt to commit a transaction against the given database. If an unretryable error occurs, returns Left. Attempts to retry the transaction for retryable errors.

cancel :: Transaction () Source #

Cancel a transaction. The transaction will not be committed, and will throw TransactionCanceled.

reset :: Transaction () Source #

Reset the transaction. All operations prior to this will be discarded.

withSnapshot :: Transaction a -> Transaction a Source #

Runs a transaction using snapshot reads, which means that the transaction will see the results of concurrent transactions, removing the default serializable isolation guarantee.

setOption :: TransactionOption -> Transaction () Source #

Set one of the transaction options from the underlying C API.

getReadVersion :: Transaction (Future Word64) Source #

Gets the read version of the current transaction, representing all transactions that were reported committed before this one.

setReadVersion :: Word64 -> Transaction () Source #

Sets the read version on the current transaction. As the FoundationDB docs state, "this is not needed in simple cases".

getVersionstamp :: Transaction (FutureIO (Either Error TransactionVersionstamp)) Source #

Returns a FutureIO that will resolve to the versionstamp of the committed transaction. Most applications won't need this.

getApproximateSize :: Transaction (Future Word64) Source #

Returns a future that will return the size, in bytes, of the transaction so far, as a summation of the estimated size of mutations, read conflict ranges, and write conflict ranges. This can be used to decide how to split a large task into smaller transactions.

get :: ByteString -> Transaction (Future (Maybe ByteString)) Source #

Get the value of a key. If the key does not exist, returns Nothing.

set :: ByteString -> ByteString -> Transaction () Source #

Set a bytestring key to a bytestring value.

clear :: ByteString -> Transaction () Source #

Delete a key from the DB.

clearRange :: ByteString -> ByteString -> Transaction () Source #

clearRange k l deletes all keys in the half-open range [k,l).

addConflictRange :: ByteString -> ByteString -> FDBConflictRangeType -> Transaction () Source #

Tells FoundationDB to consider the given range to have been read by this transaction.

data FDBConflictRangeType Source #

Instances

Instances details
Enum FDBConflictRangeType Source # 
Instance details

Defined in FoundationDB.Internal.Bindings

Eq FDBConflictRangeType Source # 
Instance details

Defined in FoundationDB.Internal.Bindings

Ord FDBConflictRangeType Source # 
Instance details

Defined in FoundationDB.Internal.Bindings

Show FDBConflictRangeType Source # 
Instance details

Defined in FoundationDB.Internal.Bindings

addReadConflictKey :: ByteString -> Transaction () Source #

Tells FoundationDB to consider the given key to have been read by this transaction.

addWriteConflictKey :: ByteString -> Transaction () Source #

Tells FoundationDB to consider the given key to have been written by this transaction.

getKey :: KeySelector -> Transaction (Future ByteString) Source #

Gets the key specified by the given KeySelector.

getKeyAddresses :: ByteString -> Transaction (Future [ByteString]) Source #

Get the public network addresses of all nodes responsible for storing the given key.

atomicOp :: ByteString -> MutationType -> Transaction () Source #

Perform an atomic operation of MutationType on the given key. A transaction that performs only atomic operations is guaranteed not to conflict. However, it may cause other concurrent transactions to conflict.

getRange :: RangeQuery -> Transaction (Future RangeResult) Source #

Reads all key-value pairs in the specified Range which are lexicographically greater than or equal to the rangeBegin KeySelector and lexicographically less than the rangeEnd KeySelector. Uses StreamingModeIterator, which assumes that you don't know ahead of time exactly how many pairs in the range you actually need. If you need them all (and they are expected to fit in memory), use getEntireRange. For more advanced usage, use getRange'.

getRange' :: RangeQuery -> FDBStreamingMode -> Transaction (Future RangeResult) Source #

Like getRange, but allows you to specify the streaming mode as desired.

data FDBStreamingMode Source #

Instances

Instances details
Bounded FDBStreamingMode Source # 
Instance details

Defined in FoundationDB.Internal.Bindings

Enum FDBStreamingMode Source # 
Instance details

Defined in FoundationDB.Internal.Bindings

Eq FDBStreamingMode Source # 
Instance details

Defined in FoundationDB.Internal.Bindings

Ord FDBStreamingMode Source # 
Instance details

Defined in FoundationDB.Internal.Bindings

Show FDBStreamingMode Source # 
Instance details

Defined in FoundationDB.Internal.Bindings

getEntireRange :: RangeQuery -> Transaction (Seq (ByteString, ByteString)) Source #

Wrapper around getRange that reads the entire range into memory.

isRangeEmpty :: RangeQuery -> Transaction Bool Source #

Return True iff the given range is empty.

data RangeQuery Source #

Specifies a range of keys to be iterated over by getRange.

Constructors

RangeQuery 

Fields

  • rangeBegin :: KeySelector

    The beginning of the range, including the key specified by this KeySelector.

  • rangeEnd :: KeySelector

    The end of the range, not including the key specified by this KeySelector.

  • rangeLimit :: Maybe Int

    If the range contains more than n items, return only Just n. If Nothing is provided, returns the entire range.

  • rangeReverse :: Bool

    If True, return the range in reverse order.

keyRangeQuery :: ByteString -> ByteString -> RangeQuery Source #

keyRangeQuery begin end is the range of keys [begin, end).

keyRangeQueryInclusive :: ByteString -> ByteString -> RangeQuery Source #

keyRangeQuery begin end is the range of keys [begin, end].

prefixRange :: ByteString -> Maybe RangeQuery Source #

prefixRange prefix is the range of all keys of which prefix is a prefix. Returns Nothing if prefix is empty or contains only 0xff.

data RangeResult Source #

Structure for returning the result of getRange in chunks.

Instances

Instances details
Show RangeResult Source # 
Instance details

Defined in FoundationDB.Transaction

watch :: ByteString -> Transaction (FutureIO ()) Source #

Creates a future that will be fulfilled when the value associated with the given key is changed, relative to the value it had as of the current transaction's read version, or the last value to which the key was previously set within the current transaction. This future is safe to return from the transaction and await in IO. If the transaction in which it was created fails to commit, awaiting it will return the same error as running the transaction did.

Mapped ranges

data MappedKeyValue Source #

The result of a mapped key value query, containing the parent key and value (i.e., the key and value in the secondary index), and the range of key-value pairs retrieved based on the range query generated from the mapper's operation on the parent key and value.

WARNING: FDB's docs warn that the returned KeySelector fields have not yet been tested. Use them at your own risk!

data MappedRangeResult Source #

Structure for returning the result of getRange in chunks.

Instances

Instances details
Show MappedRangeResult Source # 
Instance details

Defined in FoundationDB.Transaction

newtype Mapper Source #

Constructors

Mapper ByteString 

Instances

Instances details
Eq Mapper Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

(==) :: Mapper -> Mapper -> Bool #

(/=) :: Mapper -> Mapper -> Bool #

Ord Mapper Source # 
Instance details

Defined in FoundationDB.Transaction

Show Mapper Source # 
Instance details

Defined in FoundationDB.Transaction

getMappedRange' :: RangeQuery -> Mapper -> FDBStreamingMode -> Transaction (Future MappedRangeResult) Source #

Given a range of keys in a secondary index, fetc the corresponding key/values they refer to by using a mapper. See the docs for more information.

Important: you must have read-your-writes enabled, but you must not read anything you have written in the same transaction. Snapshot isolation is not supported. See the docs linked above.

These functions are only available for FDB >= 7.1

getEntireMappedRange :: RangeQuery -> Mapper -> Transaction (Seq MappedKeyValue) Source #

Wrapper around getRange that reads the entire range into memory.

Futures

data Future a Source #

A future result of a FoundationDB call. You can block on a future with await. WARNING: returning a value of this type from runTransaction and then calling await on the value in another transaction will cause a segfault! Future versions of this library may use more sophisticated types to prevent this.

Instances

Instances details
Functor Future Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

fmap :: (a -> b) -> Future a -> Future b #

(<$) :: a -> Future b -> Future a #

Applicative Future Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

pure :: a -> Future a #

(<*>) :: Future (a -> b) -> Future a -> Future b #

liftA2 :: (a -> b -> c) -> Future a -> Future b -> Future c #

(*>) :: Future a -> Future b -> Future b #

(<*) :: Future a -> Future b -> Future a #

Show a => Show (Future a) Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

showsPrec :: Int -> Future a -> ShowS #

show :: Future a -> String #

showList :: [Future a] -> ShowS #

await :: Future a -> Transaction a Source #

Block until a future is ready. Unfortunately, does not seem to be interruptible by SIGPIPE (the interrupt sent by Control.Conccurent.Async to cancel), even when using InterruptibleFFI.

awaitInterruptible :: Future a -> Transaction a Source #

Polls a future for readiness roughly every millisecond in a loop until it is ready, then returns the value in the future. This is less resource efficient than await, but can be interrupted more easily.

cancelFuture :: Future a -> Transaction () Source #

Cancel a future. Attempting to await the future after cancellation will throw OperationCancelled.

futureIsReady :: Future a -> Transaction Bool Source #

Returns True if the future is ready. If so, calling await will not block.

data FutureIO a Source #

A future that can only be awaited after its transaction has committed. That is, in contrast to Future, this must be returned from runTransaction before it can safely be awaited. Use awaitIO to await it. This future type is not needed frequently.

All FutureIO functions work similarly to their Future counterparts.

Instances

Instances details
Functor FutureIO Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

fmap :: (a -> b) -> FutureIO a -> FutureIO b #

(<$) :: a -> FutureIO b -> FutureIO a #

Show (FutureIO a) Source # 
Instance details

Defined in FoundationDB.Transaction

Methods

showsPrec :: Int -> FutureIO a -> ShowS #

show :: FutureIO a -> String #

showList :: [FutureIO a] -> ShowS #

awaitIO :: FutureIO a -> IO (Either Error a) Source #

IO analogue to await.

cancelFutureIO :: FutureIO a -> IO () Source #

Cancel a future. Attempts to await the future after cancellation will throw OperationCancelled.

futureIsReadyIO :: FutureIO a -> IO Bool Source #

Returns True if calling awaitIO will return immediately, without blocking.

Key selectors

data KeySelector Source #

Specifies a key in the database. See the official docs for more information. These can be supplied to getKey or used to build a Range.

Constructors

LastLessThan ByteString

Selects the lexicographically greatest key less than the specified key.

LastLessOrEq ByteString

Selects the lexicographically greatest less than or equal to the specified key.

FirstGreaterThan ByteString

Selects the lexicographically least key greater than the specified key.

FirstGreaterOrEq ByteString

Selects the lexicographically least key greater than or equal to the specified key.

offset :: Int -> KeySelector -> KeySelector Source #

Increase the offset of the given KeySelector.

Advanced Usage

The functionality in this section is for more advanced use cases where you need to be able to refer to an in-progress transaction and add operations to it incrementally. This is similar to how the Python bindings work -- you pass around a transaction object and call methods on it one by one before finally calling .commit().

This functionality was needed to create the bindings tester, which is required to follow the semantics of the bindings for imperative languages more closely. You probably don't need this. In fact, it's not entirely clear that the bindings tester needs it.

data TransactionEnv Source #

The internal state of a transaction as it is being executed by runTransaction.

onEnv :: TransactionEnv -> Transaction a -> IO (Either Error a) Source #

Execute a transactional action on an existing transaction environment.

commitFuture :: Transaction (Future ()) Source #

Attempts to commit a transaction. If awaiting the returned Future works without errors, the transaction was committed.

onError :: Error -> Transaction () Source #

Calls the C API's fdb_transaction_on_error function. Re-raises unretryable errors.

getCommittedVersion :: Transaction Int Source #

Gets the committed version of a transaction. Can only be called after the transaction has committed, so must be used in conjunction with TransactionEnv, since runTransaction and its variants immediately destroy the internal TransactionEnv as soon as they return.