Copyright | PublicDomain |
---|---|
Maintainer | lemmih@gmail.com |
Portability | non-portable (uses GHC extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Low-level controls for transaction-based state changes. This module defines
structures and tools for running state modifiers indexed either by an Method
or a serialized Method. This module should rarely be used directly although
the Method
class is needed when defining events manually.
The term 'Event' is loosely used for transactions with ACID guarantees. 'Method' is loosely used for state operations without ACID guarantees
Synopsis
- data Core st
- class Method ev where
- type MethodResult ev
- type MethodState ev
- methodTag :: ev -> Tag
- data MethodContainer st where
- Method :: Method method => MethodBody method -> MethodSerialiser method -> MethodContainer (MethodState method)
- type Tagged a = (Tag, a)
- mkCore :: [MethodContainer st] -> st -> IO (Core st)
- closeCore :: Core st -> IO ()
- closeCore' :: Core st -> (st -> IO ()) -> IO ()
- modifyCoreState :: Core st -> (st -> IO (st, a)) -> IO a
- modifyCoreState_ :: Core st -> (st -> IO st) -> IO ()
- withCoreState :: Core st -> (st -> IO a) -> IO a
- lookupHotMethod :: Method method => MethodMap (MethodState method) -> method -> State (MethodState method) (MethodResult method)
- lookupHotMethodAndSerialiser :: Method method => MethodMap (MethodState method) -> method -> (State (MethodState method) (MethodResult method), MethodSerialiser method)
- lookupColdMethod :: Core st -> Tagged ByteString -> State st ByteString
- runHotMethod :: Method method => Core (MethodState method) -> method -> IO (MethodResult method)
- runColdMethod :: Core st -> Tagged ByteString -> IO ByteString
- type MethodMap st = Map Tag (MethodContainer st)
- mkMethodMap :: [MethodContainer st] -> MethodMap st
- data Serialiser a = Serialiser {
- serialiserEncode :: a -> ByteString
- serialiserDecode :: ByteString -> Either String a
- safeCopySerialiser :: SafeCopy a => Serialiser a
- data MethodSerialiser method = MethodSerialiser {
- methodSerialiser :: Serialiser method
- resultSerialiser :: Serialiser (MethodResult method)
- safeCopyMethodSerialiser :: (SafeCopy method, SafeCopy (MethodResult method)) => MethodSerialiser method
- encodeMethod :: MethodSerialiser method -> method -> ByteString
- decodeMethod :: MethodSerialiser method -> ByteString -> Either String method
- encodeResult :: MethodSerialiser method -> MethodResult method -> ByteString
- decodeResult :: MethodSerialiser method -> ByteString -> Either String (MethodResult method)
Documentation
The control structure at the very center of acid-state. This module provides access to a mutable state through methods. No efforts towards durability, checkpointing or sharding happens at this level. Important things to keep in mind in this module: * We don't distinguish between updates and queries. * We allow direct access to the core state as well as through events.
class Method ev where Source #
The basic Method class. Each Method has an indexed result type and a unique tag.
Nothing
type MethodResult ev Source #
type MethodState ev Source #
data MethodContainer st where Source #
Method container structure that hides the exact type of the method.
Method :: Method method => MethodBody method -> MethodSerialiser method -> MethodContainer (MethodState method) |
:: [MethodContainer st] | List of methods capable of modifying the state. |
-> st | Initial state value. |
-> IO (Core st) |
Construct a new Core using an initial state and a list of Methods.
closeCore :: Core st -> IO () Source #
Mark Core as closed. Any subsequent use will throw an exception.
closeCore' :: Core st -> (st -> IO ()) -> IO () Source #
Access the state and then mark the Core as closed. Any subsequent use will throw an exception.
modifyCoreState :: Core st -> (st -> IO (st, a)) -> IO a Source #
Modify the state component. The resulting state is ensured to be in WHNF.
modifyCoreState_ :: Core st -> (st -> IO st) -> IO () Source #
Modify the state component. The resulting state is ensured to be in WHNF.
withCoreState :: Core st -> (st -> IO a) -> IO a Source #
Access the state component.
lookupHotMethod :: Method method => MethodMap (MethodState method) -> method -> State (MethodState method) (MethodResult method) Source #
Find the state action that corresponds to an in-memory method.
lookupHotMethodAndSerialiser :: Method method => MethodMap (MethodState method) -> method -> (State (MethodState method) (MethodResult method), MethodSerialiser method) Source #
Find the state action and serialiser that correspond to an in-memory method.
lookupColdMethod :: Core st -> Tagged ByteString -> State st ByteString Source #
Find the state action that corresponds to a tagged and serialized method.
runHotMethod :: Method method => Core (MethodState method) -> method -> IO (MethodResult method) Source #
Apply an in-memory method to the state.
runColdMethod :: Core st -> Tagged ByteString -> IO ByteString Source #
Execute a method as given by a type identifier and an encoded string.
The exact format of the encoded string depends on the type identifier.
Results are encoded and type tagged before they're handed back out.
This function is used when running events from a log-file or from another
server. Events that originate locally are most likely executed with
the faster runHotMethod
.
type MethodMap st = Map Tag (MethodContainer st) Source #
Collection of Methods indexed by a Tag.
mkMethodMap :: [MethodContainer st] -> MethodMap st Source #
Construct a MethodMap
from a list of Methods using their associated tag.
data Serialiser a Source #
Interface for (de)serialising values of type a
.
A
must
satisfy the round-trip property:Serialiser
{ serialiserEncode
, serialiserDecode
}
forall x . serialiserDecode (serialiserEncode x) == Right x
Serialiser | |
|
safeCopySerialiser :: SafeCopy a => Serialiser a Source #
Default implementation of Serialiser
interface using SafeCopy
.
data MethodSerialiser method Source #
Interface for (de)serialising a method, namely Serialiser
s for
its arguments type and its result type.
MethodSerialiser | |
|
safeCopyMethodSerialiser :: (SafeCopy method, SafeCopy (MethodResult method)) => MethodSerialiser method Source #
Default implementation of MethodSerialiser
interface using SafeCopy
.
encodeMethod :: MethodSerialiser method -> method -> ByteString Source #
Encode the arguments of a method using the given serialisation strategy.
decodeMethod :: MethodSerialiser method -> ByteString -> Either String method Source #
Decode the arguments of a method using the given serialisation strategy.
encodeResult :: MethodSerialiser method -> MethodResult method -> ByteString Source #
Encode the result of a method using the given serialisation strategy.
decodeResult :: MethodSerialiser method -> ByteString -> Either String (MethodResult method) Source #
Decode the result of a method using the given serialisation strategy.