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

Safe HaskellNone
LanguageHaskell2010

Transient.Internals

Contents

Description

See http://github.com/agocorona/transient Everything in this module is exported in order to allow extensibility.

Synopsis

Documentation

(!>) :: a -> b -> a Source #

newtype TransIO a Source #

Constructors

Transient 

Fields

Instances

Monad TransIO Source # 

Methods

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

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

return :: a -> TransIO a #

fail :: String -> TransIO a #

Functor TransIO Source # 

Methods

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

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

Applicative TransIO Source # 

Methods

pure :: a -> TransIO a #

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

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

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

MonadIO TransIO Source # 

Methods

liftIO :: IO a -> TransIO a #

Alternative TransIO Source # 

Methods

empty :: TransIO a #

(<|>) :: TransIO a -> TransIO a -> TransIO a #

some :: TransIO a -> TransIO [a] #

many :: TransIO a -> TransIO [a] #

MonadPlus TransIO Source # 

Methods

mzero :: TransIO a #

mplus :: TransIO a -> TransIO a -> TransIO a #

AdditionalOperators TransIO Source # 
MonadState EventF TransIO Source # 

Methods

get :: TransIO EventF #

put :: EventF -> TransIO () #

state :: (EventF -> (a, EventF)) -> TransIO a #

(Num a, Eq a) => Num (TransIO a) Source # 

Methods

(+) :: TransIO a -> TransIO a -> TransIO a #

(-) :: TransIO a -> TransIO a -> TransIO a #

(*) :: TransIO a -> TransIO a -> TransIO a #

negate :: TransIO a -> TransIO a #

abs :: TransIO a -> TransIO a #

signum :: TransIO a -> TransIO a #

fromInteger :: Integer -> TransIO a #

Monoid a => Monoid (TransIO a) Source # 

Methods

mempty :: TransIO a #

mappend :: TransIO a -> TransIO a -> TransIO a #

mconcat :: [TransIO a] -> TransIO a #

type SData = () Source #

data EventF Source #

EventF describes the context of a TransientIO computation:

Constructors

EventF 

Fields

Instances

type Effects = forall a b c. TransIO a -> TransIO a -> (a -> TransIO b) -> StateIO (StateIO (Maybe c) -> StateIO (Maybe c), Maybe a) Source #

noTrans :: StateIO x -> TransIO x Source #

Run a "non transient" computation within the underlying state monad, so it is guaranteed that the computation neither can stop neither can trigger additional events/threads.

runTransient :: TransIO a -> IO (Maybe a, EventF) Source #

Run a transient computation with a default initial state

runTransState :: EventF -> TransIO x -> IO (Maybe x, EventF) Source #

Run a transient computation with a given initial state

getCont :: TransIO EventF Source #

Get the continuation context: closure, continuation, state, child threads etc

runCont :: EventF -> StateIO (Maybe a) Source #

Run the closure and the continuation using the state data of the calling thread

runCont' :: EventF -> IO (Maybe a, EventF) Source #

Run the closure and the continuation using its own state data.

getContinuations :: StateIO [a -> TransIO b] Source #

Warning: Radically untyped stuff. handle with care

compose :: [a -> TransIO a] -> a -> TransIO b Source #

Compose a list of continuations.

runClosure :: EventF -> StateIO (Maybe a) Source #

Run the closure (the x in 'x >>= f') of the current bind operation.

runContinuation :: EventF -> a -> StateIO (Maybe b) Source #

Run the continuation (the f in 'x >>= f') of the current bind operation with the current state.

setContinuation :: TransIO a -> (a -> TransIO b) -> [c -> TransIO c] -> StateIO () Source #

Save a closure and a continuation (x and f in 'x >>= f').

withContinuation :: b -> TransIO a -> TransIO a Source #

Save a closure and continuation, run the closure, restore the old continuation. | NOTE: The old closure is discarded.

restoreStack :: MonadState EventF m => [a -> TransIO a] -> m () Source #

Restore the continuations to the provided ones. | NOTE: Events are also cleared out.

runContinuations :: [a -> TransIO b] -> c -> TransIO d Source #

Run a chain of continuations. WARNING: It is up to the programmer to assure that each continuation typechecks with the next, and that the parameter type match the input of the first continuation. NOTE: Normally this makes sense to stop the current flow with stop after the invocation.

readWithErr :: (Typeable a, Read a) => String -> IO [(a, String)] Source #

readsPrec' :: (Read a, Typeable * a) => t -> String -> [(a, String)] Source #

type Loggable a = (Show a, Read a, Typeable a) Source #

Constraint type synonym for a value that can be logged.

data IDynamic Source #

Dynamic serializable data for logging.

Constructors

IDyns String 
Loggable a => IDynamic a 

data Log Source #

Instances

Show Log Source # 

Methods

showsPrec :: Int -> Log -> ShowS #

show :: Log -> String #

showList :: [Log] -> ShowS #

stop :: Alternative m => m stopped Source #

A synonym of empty that can be used in a monadic expression. It stops the computation, which allows the next computation in an Alternative (<|>) composition to run.

class AdditionalOperators m where Source #

Minimal complete definition

(**>), (<**), (<***)

Methods

(**>) :: m a -> m b -> m b infixr 1 Source #

Run m a discarding its result before running m b.

(<**) :: m a -> m b -> m a infixr 1 Source #

Run m b discarding its result, after the whole task set m a is done.

atEnd' :: m a -> m b -> m a Source #

(<***) :: m a -> m b -> m a infixr 1 Source #

Run m b discarding its result, once after each task in m a, and once again after the whole task set is done.

atEnd :: m a -> m b -> m a Source #

(<|) :: TransIO a -> TransIO b -> TransIO a Source #

Run b once, discarding its result when the first task in task set a has finished. Useful to start a singleton task after the first task has been setup.

setEventCont :: TransIO a -> (a -> TransIO b) -> StateIO EventF Source #

Set the current closure and continuation for the current statement

resetEventCont :: MonadState EventF m => Maybe t1 -> t -> m (a -> a) Source #

Reset the closure and continuation. Remove inner binds than the previous computations may have stacked in the list of continuations. resetEventCont :: Maybe a -> EventF -> StateIO (TransIO b -> TransIO b)

tailsafe :: [a] -> [a] Source #

Total variant of tail that returns an empty list when given an empty list.

Threads

waitQSemB :: (Num a, Ord a) => IORef a -> IO Bool Source #

signalQSemB :: Num a => IORef a -> IO () Source #

threads :: Int -> TransIO a -> TransIO a Source #

Sets the maximum number of threads that can be created for the given task set. When set to 0, new tasks start synchronously in the current thread. New threads are created by parallel, and APIs that use parallel.

oneThread :: TransIO a -> TransIO a Source #

Terminate all the child threads in the given task set and continue execution in the current thread. Useful to reap the children when a task is done.

labelState :: (MonadIO m, MonadState EventF m) => String -> m () Source #

Add a label to the current passing threads so it can be printed by debugging calls like showThreads

showThreads :: MonadIO m => EventF -> m () Source #

Show the tree of threads hanging from the state.

topState :: TransIO EventF Source #

Return the state of the thread that initiated the transient computation

showState :: (Typeable a, MonadIO m, Alternative m) => String -> EventF -> m (Maybe a) Source #

Return the state variable of the type desired with which a thread, identified by his number in the treee was initiated

addThreads' :: Int -> TransIO () Source #

Add n threads to the limit of threads. If there is no limit, the limit is set.

addThreads :: Int -> TransIO () Source #

Ensure that at least n threads are available for the current task set.

freeThreads :: TransIO a -> TransIO a Source #

Disable tracking and therefore the ability to terminate the child threads. By default, child threads are terminated automatically when the parent thread dies, or they can be terminated using the kill primitives. Disabling it may improve performance a bit, however, all threads must be well-behaved to exit on their own to avoid a leak.

hookedThreads :: TransIO a -> TransIO a Source #

Enable tracking and therefore the ability to terminate the child threads. This is the default but can be used to re-enable tracking if it was previously disabled with freeThreads.

killChilds :: TransIO () Source #

Kill all the child threads of the current thread.

killBranch :: TransIO () Source #

Kill the current thread and the childs.

killBranch' :: EventF -> IO () Source #

Kill the childs and the thread of an state

Extensible State: Session Data Management

getData :: (MonadState EventF m, Typeable a) => m (Maybe a) Source #

Same as getSData but with a more general type. If the data is found, a Just value is returned. Otherwise, a Nothing value is returned.

getSData :: Typeable a => TransIO a Source #

Retrieve a previously stored data item of the given data type from the monad state. The data type to retrieve is implicitly determined from the requested type context. If the data item is not found, an empty value (a void event) is returned. Remember that an empty value stops the monad computation. If you want to print an error message or a default value in that case, you can use an Alternative composition. For example:

getSData <|> error "no data"
getInt = getSData <|> return (0 :: Int)

setData :: (MonadState EventF m, Typeable a) => a -> m () Source #

setData stores a data item in the monad state which can be retrieved later using getData or getSData. Stored data items are keyed by their data type, and therefore only one item of a given type can be stored. A newtype wrapper can be used to distinguish two data items of the same type.

import Control.Monad.IO.Class (liftIO)
import Transient.Base
import Data.Typeable

data Person = Person
   { name :: String
   , age :: Int
   } deriving Typeable

main = keep $ do
     setData $ Person Alberto  55
     Person name age <- getSData
     liftIO $ print (name, age)

modifyData :: (MonadState EventF m, Typeable a) => (Maybe a -> Maybe a) -> m () Source #

Accepts a function that takes the current value of the stored data type and returns the modified value. If the function returns Nothing the value is deleted otherwise updated.

modifyState :: (MonadState EventF m, Typeable a) => (Maybe a -> Maybe a) -> m () Source #

Same as modifyData

setState :: (MonadState EventF m, Typeable a) => a -> m () Source #

Same as setData

delData :: (MonadState EventF m, Typeable a) => a -> m () Source #

Delete the data item of the given type from the monad state.

delState :: (MonadState EventF m, Typeable a) => a -> m () Source #

Same as delData

newtype Ref a Source #

Constructors

Ref (IORef a) 

setRState :: Typeable a => a -> TransIO () Source #

mutable state reference that can be updated (similar to STRef in the state monad)

Initialized the first time it is set.

try :: TransIO a -> TransIO a Source #

Run an action, if the result is a void action undo any state changes that it might have caused.

sandbox :: TransIO a -> TransIO a Source #

Executes the computation and reset the state either if it fails or not.

genId :: MonadState EventF m => m Int Source #

Generator of identifiers that are unique within the current monadic sequence They are not unique in the whole program.

data StreamData a Source #

StreamData represents a task in a task stream being generated.

Constructors

SMore a

More tasks to come

SLast a

This is the last task

SDone

No more tasks, we are done

SError SomeException

An error occurred

waitEvents :: IO a -> TransIO a Source #

An task stream generator that produces an infinite stream of tasks by running an IO computation in a loop. A task is triggered carrying the output of the computation. See parallel for notes on the return value.

async :: IO a -> TransIO a Source #

Run an IO computation asynchronously and generate a single task carrying the result of the computation when it completes. See parallel for notes on the return value.

sync :: TransIO a -> TransIO a Source #

Force an async computation to run synchronously. It can be useful in an Alternative composition to run the alternative only after finishing a computation. Note that in Applicatives it might result in an undesired serialization.

spawn :: IO a -> TransIO a Source #

spawn = freeThreads . waitEvents

sample :: Eq a => IO a -> Int -> TransIO a Source #

An task stream generator that produces an infinite stream of tasks by running an IO computation periodically at the specified time interval. The task carries the result of the computation. A new task is generated only if the output of the computation is different from the previous one. See parallel for notes on the return value.

parallel :: IO (StreamData b) -> TransIO (StreamData b) Source #

Run an IO action one or more times to generate a stream of tasks. The IO action returns a StreamData. When it returns an SMore or SLast a new task is triggered with the result value. If the return value is SMore, the action is run again to generate the next task, otherwise task creation stops.

Unless the maximum number of threads (set with threads) has been reached, the task is generated in a new thread and the current thread returns a void task.

loop :: EventF -> IO (StreamData t) -> IO () Source #

Execute the IO action and the continuation

killChildren :: MVar [EventF] -> IO () Source #

kill all the child threads associated with the continuation context

react :: Typeable eventdata => ((eventdata -> IO response) -> IO ()) -> IO response -> TransIO eventdata Source #

Make a transient task generator from an asynchronous callback handler.

The first parameter is a callback. The second parameter is a value to be returned to the callback; if the callback expects no return value it can just be a return (). The callback expects a setter function taking the eventdata as an argument and returning a value to the callback; this function is supplied by react.

Callbacks from foreign code can be wrapped into such a handler and hooked into the transient monad using react. Every time the callback is called it generates a new task for the transient monad.

abduce :: TransIO () Source #

Runs a computation asynchronously without generating any events. Returns empty in an Alternative composition.

non-blocking keyboard input

option :: (Typeable b, Show b, Read b, Eq b) => b -> String -> TransIO b Source #

Waits on stdin in a loop and triggers a new task every time the input data matches the first parameter. The value contained by the task is the matched value i.e. the first argument itself. The second parameter is a label for the option. The label is displayed on the console when the option is activated.

Note that if two independent invocations of option are expecting the same input, only one of them gets it and triggers a task. It cannot be predicted which one gets it.

input :: (Show a, Read a, Typeable * a) => (a -> Bool) -> String -> TransIO a Source #

Waits on stdin and triggers a task when a console input matches the predicate specified in the first argument. The second parameter is a string to be displayed on the console before waiting.

input' :: (Typeable a, Read a, Show a) => Maybe a -> (a -> Bool) -> String -> TransIO a Source #

getLine' :: (Read a, Typeable * a) => (a -> Bool) -> IO a Source #

Non blocking getLine with a validator

reads1 :: (Typeable * a, Read a) => String -> [(a, String)] Source #

stay :: MVar (Maybe a) -> IO (Maybe a) Source #

Wait for the execution of exit and return the result or the exhaustion of thread activity

newtype Exit a Source #

Constructors

Exit a 

keep :: Typeable a => TransIO a -> IO (Maybe a) Source #

Runs the transient computation in a child thread and keeps the main thread running until all the user threads exit or some thread invokes exit.

The main thread provides facilities to accept keyboard input in a non-blocking but line-oriented manner. The program reads the standard input and feeds it to all the async input consumers (e.g. option and input). All async input consumers contend for each line entered on the standard input and try to read it atomically. When a consumer consumes the input others do not get to see it, otherwise it is left in the buffer for others to consume. If nobody consumes the input, it is discarded.

A / in the input line is treated as a newline.

When using asynchronous input, regular synchronous IO APIs like getLine cannot be used as they will contend for the standard input along with the asynchronous input thread. Instead you can use the asynchronous input APIs provided by transient.

A built-in interactive command handler also reads the stdin asynchronously. All available commands handled by the command handler are displayed when the program is run. The following commands are available:

  1. ps: show threads
  2. log: inspect the log of a thread
  3. end, exit: terminate the program

An input not handled by the command handler can be handled by the program.

The program's command line is scanned for -p or --path command line options. The arguments to these options are injected into the async input channel as keyboard input to the program. Each line of input is separated by a /. For example:

 foo  -p  ps/end

keep' :: Typeable a => TransIO a -> IO (Maybe a) Source #

Same as keep but does not read from the standard input, and therefore the async input APIs (option and input) cannot be used in the monad. However, keyboard input can still be passed via command line arguments as described in keep. Useful for debugging or for creating background tasks, as well as to embed the Transient monad inside another computation. It returns either the value returned by exit. or Nothing, when there are no more threads running

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

Exit the main thread, and thus all the Transient threads (and the application if there is no more code)

onNothing :: Monad m => m (Maybe b) -> m b -> m b Source #

If the first parameter is Nothing return the second parameter otherwise return the first parameter..

data Backtrack b Source #

Constructors

Show b => Backtrack 

Fields

backCut :: (Typeable b, Show b) => b -> TransientIO () Source #

Delete all the undo actions registered till now for the given track id.

undoCut :: TransientIO () Source #

backCut for the default track; equivalent to backCut ().

onBack :: (Typeable b, Show b) => TransientIO a -> (b -> TransientIO a) -> TransientIO a Source #

Run the action in the first parameter and register the second parameter as the undo action. On undo (back) the second parameter is called with the undo track id as argument.

onUndo :: TransientIO a -> TransientIO a -> TransientIO a Source #

onBack for the default track; equivalent to onBack ().

registerBack :: (Typeable b, Show b) => b -> TransientIO a -> TransientIO a Source #

Register an undo action to be executed when backtracking. The first parameter is a "witness" whose data type is used to uniquely identify this backtracking action. The value of the witness parameter is not used.

forward :: (Typeable b, Show b) => b -> TransIO () Source #

For a given undo track id, stop executing more backtracking actions and resume normal execution in the forward direction. Used inside an undo action.

retry :: TransIO () Source #

forward for the default undo track; equivalent to forward ().

noFinish :: TransIO () Source #

Abort finish. Stop executing more finish actions and resume normal execution. Used inside onFinish actions.

back :: (Typeable b, Show b) => b -> TransientIO a Source #

Start the undo process for the given undo track id. Performs all the undo actions registered till now in reverse order. An undo action can use forward to stop the undo process and resume forward execution. If there are no more undo actions registered execution stops and a stop action is returned.

backStateOf :: (Monad m, Show a, Typeable a) => a -> m (Backtrack a) Source #

undo :: TransIO a Source #

back for the default undo track; equivalent to back ().

onFinish :: (Finish -> TransIO ()) -> TransIO () Source #

Clear all finish actions registered till now. initFinish= backCut (FinishReason Nothing)

Register an action that to be run when finish is called. onFinish can be used multiple times to register multiple actions. Actions are run in reverse order. Used in infix style.

onFinish' :: TransIO a -> (Finish -> TransIO a) -> TransIO a Source #

Run the action specified in the first parameter and register the second parameter as a finish action to be run when finish is called. Used in infix style.

initFinish :: TransIO () Source #

Execute all the finalization actions registered up to the last initFinish, in reverse order. Either an exception or Nothing can be

checkFinalize :: StreamData a -> TransIO a Source #

trigger finish when the stream of data ends

onException :: Exception e => (e -> TransIO ()) -> TransIO () Source #

Install an exception handler. Handlers are executed in reverse (i.e. last in, first out) order when such exception happens in the continuation. Note that multiple handlers can be installed for the same exception type.

The semantic is thus very different than the one of onException

onException' :: Exception e => TransIO a -> (e -> TransIO a) -> TransIO a Source #

cutExceptions :: TransIO () Source #

Delete all the exception handlers registered till now.

continue :: TransIO () Source #

Use it inside an exception handler. it stop executing any further exception handlers and resume normal execution from this point on.

catcht :: Exception e => TransIO b -> (e -> TransIO b) -> TransIO b Source #

catch an exception in a Transient block

The semantic is the same than catch but the computation and the exception handler can be multirhreaded

throwt :: Exception e => e -> TransIO a Source #

throw an exception in the Transient monad

Orphan instances