transient-0.7.0.0: composing programs with multithreading, events and distributed computing

Safe HaskellNone
LanguageHaskell2010

Transient.Logged

Description

The logged primitive is used to save the results of the subcomputations of a transient computation (including all its threads) in a log buffer. At any point, a suspend or checkpoint can be used to save the accumulated log on a persistent storage. A restore reads the saved logs and resumes the computation from the saved checkpoint. On resumption, the saved results are used for the computations which have already been performed. The log contains purely application level state, and is therefore independent of the underlying machine architecture. The saved logs can be sent across the wire to another machine and the computation can then be resumed on that machine. We can also save the log to gather diagnostic information.

The following example illustrates the APIs. In its first run suspend saves the state in a directory named logs and exits, in the second run it resumes from that point and then stops at the checkpoint, in the third run it resumes from the checkpoint and then finishes.

main= keep $ restore  $ do
     r <- logged $ choose [1..10 :: Int]
     logged $ liftIO $ print ("A",r)
     suspend ()
     logged $ liftIO $ print ("B",r)
     checkpoint
     liftIO $ print ("C",r)
Synopsis

Documentation

class (Show a, Read a, Typeable a) => Loggable a where Source #

Minimal complete definition

Nothing

Instances
Loggable Bool Source # 
Instance details

Defined in Transient.Logged

Loggable Char Source # 
Instance details

Defined in Transient.Logged

Loggable Double Source # 
Instance details

Defined in Transient.Logged

Loggable Float Source # 
Instance details

Defined in Transient.Logged

Loggable Int Source # 
Instance details

Defined in Transient.Logged

Loggable Integer Source # 
Instance details

Defined in Transient.Logged

Loggable () Source # 
Instance details

Defined in Transient.Logged

Loggable SomeException Source # 
Instance details

Defined in Transient.Logged

Loggable ByteString Source # 
Instance details

Defined in Transient.Logged

Loggable ByteString Source # 
Instance details

Defined in Transient.Logged

Loggable Raw Source # 
Instance details

Defined in Transient.Logged

(Typeable a, Loggable a) => Loggable [a] Source # 
Instance details

Defined in Transient.Logged

Loggable a => Loggable (Maybe a) Source # 
Instance details

Defined in Transient.Logged

(Loggable a, Loggable b) => Loggable (Either a b) Source # 
Instance details

Defined in Transient.Logged

(Loggable a, Loggable b) => Loggable (a, b) Source # 
Instance details

Defined in Transient.Logged

(Loggable k, Ord k, Loggable a) => Loggable (Map k a) Source # 
Instance details

Defined in Transient.Logged

(Loggable a, Loggable b, Loggable c) => Loggable (a, b, c) Source # 
Instance details

Defined in Transient.Logged

Methods

serialize :: (a, b, c) -> Builder Source #

deserializePure :: ByteString -> Maybe ((a, b, c), ByteString) Source #

deserialize :: TransIO (a, b, c) Source #

(Loggable a, Loggable b, Loggable c, Loggable d) => Loggable (a, b, c, d) Source # 
Instance details

Defined in Transient.Logged

Methods

serialize :: (a, b, c, d) -> Builder Source #

deserializePure :: ByteString -> Maybe ((a, b, c, d), ByteString) Source #

deserialize :: TransIO (a, b, c, d) Source #

(Loggable a, Loggable b, Loggable c, Loggable d, Loggable e) => Loggable (a, b, c, d, e) Source # 
Instance details

Defined in Transient.Logged

Methods

serialize :: (a, b, c, d, e) -> Builder Source #

deserializePure :: ByteString -> Maybe ((a, b, c, d, e), ByteString) Source #

deserialize :: TransIO (a, b, c, d, e) Source #

(Loggable a, Loggable b, Loggable c, Loggable d, Loggable e, Loggable f) => Loggable (a, b, c, d, e, f) Source # 
Instance details

Defined in Transient.Logged

Methods

serialize :: (a, b, c, d, e, f) -> Builder Source #

deserializePure :: ByteString -> Maybe ((a, b, c, d, e, f), ByteString) Source #

deserialize :: TransIO (a, b, c, d, e, f) Source #

(Loggable a, Loggable b, Loggable c, Loggable d, Loggable e, Loggable f, Loggable g) => Loggable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Transient.Logged

Methods

serialize :: (a, b, c, d, e, f, g) -> Builder Source #

deserializePure :: ByteString -> Maybe ((a, b, c, d, e, f, g), ByteString) Source #

deserialize :: TransIO (a, b, c, d, e, f, g) Source #

(Loggable a, Loggable b, Loggable c, Loggable d, Loggable e, Loggable f, Loggable g, Loggable h) => Loggable (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Transient.Logged

Methods

serialize :: (a, b, c, d, e, f, g, h) -> Builder Source #

deserializePure :: ByteString -> Maybe ((a, b, c, d, e, f, g, h), ByteString) Source #

deserialize :: TransIO (a, b, c, d, e, f, g, h) Source #

(Loggable a, Loggable b, Loggable c, Loggable d, Loggable e, Loggable f, Loggable g, Loggable h, Loggable i) => Loggable (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Transient.Logged

Methods

serialize :: (a, b, c, d, e, f, g, h, i) -> Builder Source #

deserializePure :: ByteString -> Maybe ((a, b, c, d, e, f, g, h, i), ByteString) Source #

deserialize :: TransIO (a, b, c, d, e, f, g, h, i) Source #

logged :: Loggable a => TransIO a -> TransIO a Source #

Run the computation, write its result in a log in the state and return the result. If the log already contains the result of this computation (restored from previous saved state) then that result is used instead of running the computation again.

logged can be used for computations inside a nother logged computation. Once the parent computation is finished its internal (subcomputation) logs are discarded.

received :: (Loggable a, Eq a) => a -> TransIO () Source #

suspend :: Typeable a => a -> TransIO a Source #

Saves the logged state of the current computation that has been accumulated using logged, and then exits using the passed parameter as the exit code. Note that all the computations before a suspend must be logged to have a consistent log state. The logs are saved in the logs subdirectory of the current directory. Each thread's log is saved in a separate file.

checkpoint :: TransIO () Source #

Saves the accumulated logs of the current computation, like suspend, but does not exit.

rerun :: String -> TransIO a -> TransIO a Source #

Reads the saved logs from the logs subdirectory of the current directory, restores the state of the computation from the logs, and runs the computation. The log files are maintained. It could be used for the initial configuration of a program.

restore :: TransIO a -> TransIO a Source #

Reads the saved logs from the logs subdirectory of the current directory, restores the state of the computation from the logs, and runs the computation. The log files are removed after the state has been restored.

data Log Source #

Constructors

Log 

toLazyByteString :: Builder -> ByteString #

Execute a Builder and return the generated chunks as a lazy ByteString. The work is performed lazy, i.e., only when a chunk of the lazy ByteString is forced.

byteString :: ByteString -> Builder #

Create a Builder denoting the same sequence of bytes as a strict ByteString. The Builder inserts large ByteStrings directly, but copies small ones to ensure that the generated chunks are large on average.

lazyByteString :: ByteString -> Builder #

Create a Builder denoting the same sequence of bytes as a lazy ByteString. The Builder inserts large chunks of the lazy ByteString directly, but copies small ones to ensure that the generated chunks are large on average.

newtype Raw Source #

Constructors

Raw ByteString 
Instances
Read Raw Source # 
Instance details

Defined in Transient.Logged

Show Raw Source # 
Instance details

Defined in Transient.Logged

Methods

showsPrec :: Int -> Raw -> ShowS #

show :: Raw -> String #

showList :: [Raw] -> ShowS #

Loggable Raw Source # 
Instance details

Defined in Transient.Logged