transient-0.1.0.8: A monad for extensible effects and primitives for unrestricted composability of applications

Safe HaskellNone
LanguageHaskell2010

Transient.Base

Contents

Description

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

Synopsis

Documentation

(!>) :: a -> b -> a infixr 0 Source

(!!>) :: c -> String -> c infixr 0 Source

type SData = () Source

type P = IORef Source

newp :: a -> IO (IORef a) Source

(=:) :: MonadIO m => IORef a -> (a -> a) -> m () Source

getCont :: MonadState EventF m => m EventF Source

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

runCont :: EventF -> StateIO () Source

run the continuation context

compose :: (Monad f, Alternative f) => [a1 -> f a1] -> a1 -> f a 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

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

run a chain of continuations. It is up to the programmer to assure by construction that each continuation type-check with the next and the parameter type match the input of the first continuation and that the output is of the type intended.

data IDynamic Source

dynamic serializable data for logging

Constructors

IDyns String 
forall a . (Read a, Show a, Typeable a) => IDynamic a 

stop :: TransientIO a Source

a sinonym of empty that can be used in a monadic expression. it stop the computation

setEventCont :: TransientIO a -> (a -> TransientIO b) -> StateIO () Source

set the current closure and continuation for the current statement

resetEventCont :: Maybe a -> StateIO () Source

reset the closure and continuation. remove inner binds than the prevous computations may have stacked in the list of continuations.

Threads

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

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

threads :: Int -> TransientIO a -> TransientIO a Source

set the maximun number of threads for a procedure. It is useful to limit the parallelization of transient code that uses parallel spawn and waitEvents

oneThread :: TransientIO a -> TransientIO a Source

delete all the previous childs generated by the expressions and continue execution of the current thread.

addThreads' :: Int -> TransIO () Source

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

addThreads :: (MonadIO m, MonadState EventF m) => Int -> m () Source

assure that at least there are n threads left

freeThreads :: TransientIO a -> TransientIO a Source

The threads generated in the process passed as parameter will not be killed.

hookedThreads :: TransientIO a -> TransientIO a Source

The threads will be killed when the parent thread dies. That is the default. This can be invoked to revert the effect of freeThreads

killChilds :: TransientIO () Source

kill all the child processes

extensible state: session data management

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

Get the session data for the desired type if there is any.

getSData :: Typeable a => TransIO a Source

getSessionData specialized for the Transient monad. if Nothing, the monadic computation does not continue.

If there is no such data, getSData silently stop the computation. That may or may not be the desired behaviour. To make sure that this does not get unnoticed, use this construction:

 getSData <|> error "no data"

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

set session data for this type. retrieved with getSessionData orr getSData

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

a shorter name for setSessionData

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

genNewId :: MonadIO m => MonadState EventF m => m Int Source

generator of identifiers

data StreamData a Source

async calls

Constructors

SMore a 
SLast a 
SDone 
SError String 

Instances

waitEvents :: IO b -> TransientIO b Source

variant of parallel that repeatedly executes the IO computation and kill the previously created childs

It is useful in single threaded problems where each event discard the computations spawned by previous events

async :: IO b -> TransientIO b Source

variant of + parallel` that execute the IO computation once, and kill the previous child threads

spawn :: IO b -> TransientIO b Source

variant that spawn free threads. Since there is not thread control, this is faster

parallel :: IO (StreamData b) -> TransientIO (StreamData b) Source

return empty to the current thread and launch the IO action in a new thread and attaches the continuation after it. if the result of the action is Right the process is repeated. if not, it finish.

If the maximum number of threads, set with threads has been reached parallel perform the work sequentially, in the current thread.

When parallelfinish, increase the counter of threads available, if there is a limitation of them.

The behaviour of parallel depend on StreamData if SMore, parallel will excute again the IO action. with SLast, SDone and SError, parallel will execute the continuation and will stop.

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

killChildren :: EventF -> IO () Source

kill all the threads associated with the continuation context

type EventSetter eventdata response = (eventdata -> IO response) -> IO () Source

type ToReturn response = IO response Source

react :: Typeable eventdata => EventSetter eventdata response -> ToReturn response -> TransientIO eventdata Source

deinvert an event handler. The first parameter is the event handler to be deinverted the second is the value to return to the event handler it configures the event handler by calling the first parameter, that set the event handler, with the current continuation

non-blocking keyboard input

option :: (Typeable b, Show b, Read b, Eq b) => b -> [Char] -> TransientIO b Source

install a event receiver that wait for a string and trigger the continuation when this string arrives.

input :: (Typeable a, Read a) => (a -> Bool) -> TransientIO a Source

validates an input entered in the keyboard in non blocking mode. non blocking means that the user can enter also anything else to activate other option unlike option, input only wait for one valid response

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

non blocking getLine with a validator

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

keep :: TransIO a -> IO a Source

keep the main thread running, initiate the asynchronous keyboard input and execute the transient computation. It also read a slash separated list of string that are interpreted by option and input as if they were entered by the keyboard

keep' :: TransIO a -> IO a Source

same than keepbut do not initiate the asynchronous keyboard input. Useful for debugging

exit :: TransientIO a Source

force the finalization of the main thread and thus, all the application

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

alternative operator for maybe values. Used in infix mode