Safe Haskell | None |
---|
- class SafeCopy (Update d) => Persistable d where
- data Database d
- openDatabase :: Persistable d => FilePath -> d -> IO (Database d)
- closeDatabase :: Database d -> IO ()
- withUserData :: Database d -> (d -> a) -> a
- data TX d a
- persistently :: Database d -> TX d a -> IO a
- record :: Update d -> TX d ()
- getData :: TX d d
- liftSTM :: STM a -> TX d a
- throwTX :: Exception e => e -> TX d a
- unsafeIOToTX :: IO a -> TX d a
- (<?>) :: Exception e => TX d (Maybe a) -> e -> TX d a
Documentation
class SafeCopy (Update d) => Persistable d whereSource
The type family at the heart of TX.
You make any data type you want to use with the TX monad an instance of
Persistable
and define Update
constructors for each of the methods
acting on this type that you want to be able to record during a transaction.
Then you implement replay
in such a way that for each of the Update
constructors, the appropiate method is called.
Example:
data MyDB = MyDB { posts :: TVar [String] } instance Persistable MyDB where data Update MyDB = CreatePost String | ModifyPost Int String replay (CreatePost p) = void $ createPost p replay (ModifyPost n p) = modifyPost n p
where createPost
and modifyPost
are functions in the TX monad:
createPost :: String -> TX MyDB Int createPost p = do record (CreatePost p) (MyDB posts) <- getData liftSTM $ do ps <- readTVar posts writeTVar posts (ps ++ [p]) return $ length ps modifyPost :: Int -> String -> TX MyDB () modifyPost n p = do record (ModifyPost n p) (MyDB posts) <- getData liftSTM $ do ps <- readTVar posts let (xs,ys) = splitAt n ps ps' = xs ++ p : (tail ys) writeTVar posts ps'
Note that Update
also needs to be an instance of SafeCopy
. Currently,
it's not possible to derive SafeCopy instances for associated types
automatically, so you have to do it by hand:
instance SafeCopy (Update MyDB) where putCopy (CreatePost p) = contain $ putWord8 0 >> safePut p putCopy (ModifyPost n p) = contain $ putWord8 1 >> safePut n >> safePut p getCopy = contain $ do tag <- getWord8 case tag of 0 -> CreatePost <$> safeGet 1 -> ModifyPost <$> safeGet <*> safeGet _ -> fail $ "unknown tag: " ++ show tag
Managing the database
:: Persistable d | |
=> FilePath | Location of the log file. |
-> d | Base data. Any existing log is replayed on top of this. |
-> IO (Database d) |
Opens the database at the given path or creates a new one.
closeDatabase :: Database d -> IO ()Source
Close a database. Blocks until all pending recordings been serialized. Using a database after it has been closed is an error.
withUserData :: Database d -> (d -> a) -> aSource
Operate non-persistently on the user data contained in the database.
The TX monad
A thin wrapper around STM. The main feature is the ability to record
updates of the underlying data.
persistently :: Database d -> TX d a -> IO aSource
Perform a series of TX actions persistently.
Note that there is no guarantee that all recorded updates have been serialized when the functions returns. As such, durability is only partially guaranteed.
Since this calls atomically
on the underlying STM actions,
the same caveats apply (e.g. you can't use it inside unsafePerformIO
).
record :: Update d -> TX d ()Source
Record an Update
to be serialized to disk when the transaction commits.
If the transaction retries, the update is still only recorded once.
If the transaction aborts, the update is not recorded at all.
throwTX :: Exception e => e -> TX d aSource
Throw an exception in TX, which will abort the transaction.
throwTX = liftSTM . throwSTM
unsafeIOToTX :: IO a -> TX d aSource
Unsafely performs IO in the TX monad. Highly dangerous!
The same caveats as with unsafeIOToSTM
apply.
unsafeIOToTX = liftSTM . unsafeIOToSTM