persistent-stm-0.1.0.2: STM transactions involving persistent storage
Safe HaskellNone
LanguageHaskell2010

PersistentSTM

Description

A scheme for adding persistence to Haskell's STM transactions. A DBRef a is like a TVar (Maybe a), except that it exists (or not) in persistent storage as well as in memory.

The choice of persistent storage is up to the user, and is specified with a Persistence. There is a default implementation called filePersistence that uses files on disk. Note that filePersistence doesn't guarantee transactional atomicity in the presence of sudden termination of the process, such as in a power outage or system crash. Therefore, for serious use, it's recommended that you use a different Persistence implementation based on a storage layer with stronger transactional guarantees.

For this scheme to work at all, this process must be the only entity to access the persistent storage. You may not even use a single-writer, multiple-reader architecture, because consistency guarantees for reads, as well, depend on all writes happening in the current process.

Synopsis

Documentation

data DB Source #

A currently open database in which DBRefs can be read and written. See openDB, closeDB, and withDB to manage DB values.

openDB :: Persistence -> IO DB Source #

Opens a DB using the given Persistence. The caller should guarantee that closeDB is called when the DB is no longer needed.

closeDB :: DB -> IO () Source #

Closes a DB. When this call returns, all data will be written to persistent storage, and the program can exit without possibly losing data.

withDB :: Persistence -> (DB -> IO a) -> IO a Source #

Runs an action with a DB open. The DB will be closed when the action is finished. The DB value should not be used after the action has returned.

waitForMaxBacklog :: DB -> Int -> STM () Source #

Check that there are at most the given number of queued writes to the database, and retries the transaction if so. Adding this to the beginning of your transactions can help prevent writes from falling too far behind the live data. Prioritizing writes this way can also reduce memory usage, because unreachable DBRefs no longer need to be retained once they are written to disk.

synchronously :: DB -> STM a -> IO a Source #

Atomically performs an STM transaction just like atomically, but also waits for any changes it might have observed in the DB to be written to persistent storage before returning. This guarantees that a transaction whose results were observed will not be rolled back if the program crashes.

data DBRef a Source #

A reference to persistent data from some DB that can be accessed in STM transaction. DBRef a is similar to 'TVar (Maybe a), except that values exist in persistent storage as well as in memory.

Instances

Instances details
Eq (DBRef a) Source #

Only DBRefs in the same DB should be compared.

Instance details

Defined in PersistentSTM

Methods

(==) :: DBRef a -> DBRef a -> Bool #

(/=) :: DBRef a -> DBRef a -> Bool #

Ord (DBRef a) Source #

Only DBRefs in the same DB should be compared.

Instance details

Defined in PersistentSTM

Methods

compare :: DBRef a -> DBRef a -> Ordering #

(<) :: DBRef a -> DBRef a -> Bool #

(<=) :: DBRef a -> DBRef a -> Bool #

(>) :: DBRef a -> DBRef a -> Bool #

(>=) :: DBRef a -> DBRef a -> Bool #

max :: DBRef a -> DBRef a -> DBRef a #

min :: DBRef a -> DBRef a -> DBRef a #

Show (DBRef a) Source # 
Instance details

Defined in PersistentSTM

Methods

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

show :: DBRef a -> String #

showList :: [DBRef a] -> ShowS #

DBStorable a => DBStorable (DBRef a) Source # 
Instance details

Defined in PersistentSTM

class Typeable a => DBStorable a where Source #

A type class for things that can be stored in a DBRef. This is similar to a serialization class like Binary, but reads have access to the DB and the STM monad, which is important because it allows for one DBRef to be stored inside the value of another. (In this case, decode will call getDBRef.)

Minimal complete definition

Nothing

Methods

decode :: DB -> ByteString -> STM a Source #

default decode :: Binary a => DB -> ByteString -> STM a Source #

encode :: a -> ByteString Source #

default encode :: Binary a => a -> ByteString Source #

Instances

Instances details
DBStorable Bool Source # 
Instance details

Defined in PersistentSTM

DBStorable Char Source # 
Instance details

Defined in PersistentSTM

DBStorable Double Source # 
Instance details

Defined in PersistentSTM

DBStorable Float Source # 
Instance details

Defined in PersistentSTM

DBStorable Int Source # 
Instance details

Defined in PersistentSTM

DBStorable Int8 Source # 
Instance details

Defined in PersistentSTM

DBStorable Int16 Source # 
Instance details

Defined in PersistentSTM

DBStorable Int32 Source # 
Instance details

Defined in PersistentSTM

DBStorable Int64 Source # 
Instance details

Defined in PersistentSTM

DBStorable Integer Source # 
Instance details

Defined in PersistentSTM

DBStorable Natural Source # 
Instance details

Defined in PersistentSTM

DBStorable Ordering Source # 
Instance details

Defined in PersistentSTM

DBStorable Word Source # 
Instance details

Defined in PersistentSTM

DBStorable Word8 Source # 
Instance details

Defined in PersistentSTM

DBStorable Word16 Source # 
Instance details

Defined in PersistentSTM

DBStorable Word32 Source # 
Instance details

Defined in PersistentSTM

DBStorable Word64 Source # 
Instance details

Defined in PersistentSTM

DBStorable () Source # 
Instance details

Defined in PersistentSTM

Methods

decode :: DB -> ByteString -> STM () Source #

encode :: () -> ByteString Source #

DBStorable ShortByteString Source # 
Instance details

Defined in PersistentSTM

DBStorable ByteString Source # 
Instance details

Defined in PersistentSTM

DBStorable ByteString Source # 
Instance details

Defined in PersistentSTM

DBStorable a => DBStorable [a] Source # 
Instance details

Defined in PersistentSTM

Methods

decode :: DB -> ByteString -> STM [a] Source #

encode :: [a] -> ByteString Source #

DBStorable a => DBStorable (DBRef a) Source # 
Instance details

Defined in PersistentSTM

getDBRef :: forall a. DBStorable a => DB -> String -> STM (DBRef a) Source #

Retrieves a DBRef from a DB for the given key. Throws an exception if the DBRef requested has a different type from a previous time the key was used in this process, or if a serialized value in persistent storage cannot be parsed.

readDBRef :: DBRef a -> STM (Maybe a) Source #

Gets the value stored in a DBRef. The value is Just x if x was last value stored in the database using this key, or Nothing if there is no value stored in the database.

writeDBRef :: DBStorable a => DBRef a -> a -> STM () Source #

Updates the value stored in a DBRef. The update will be persisted to storage soon, but not synchronously.

deleteDBRef :: DBStorable a => DBRef a -> STM () Source #

Deletes the value stored in a DBRef. The delete will be persisted to storage soon, but not synchronously.

data Persistence Source #

A strategy for persisting values from DBRef to some persistent storage. The filePersistence implementation is provided as a quick way to get started, but note the weaknesses in its documentation.

A Persistence can read one value at a time, but should be able to atomically write/delete an entire set of keys at once, preferably atomically.

Constructors

Persistence 

Fields

  • persistentRead :: String -> IO (Maybe ByteString)

    Read a single value from persistent storage. Return the serialized representation if it exists, and Nothing otherwise.

  • persistentWrite :: Map String (Maybe ByteString) -> IO ()

    Write (for Just values) or delete (for Nothing values) an entire set of values to persistent storage. The values should ideally be written atomically, and if they are not then the implementation will be vulnerable to inconsistent data and corruption if the process is suddenly terminated.

  • persistentFinish :: IO ()

    Perform any cleanup that is needed after the DB is closed. This can include releasing locks, for example.

filePersistence :: FilePath -> IO Persistence Source #

A simple Persistence that stores data in a directory in the local filesystem. This is an easy way to get started. However, note that because writes are not atomic, your data can be corrupted during a crash or power outage. For this reason, it's recommended that you use a different Persistence for most applications.