transient-0.4.4.1: Making composable programs with multithreading, events and distributed computing

Safe HaskellNone
LanguageHaskell2010

Transient.Internals

Contents

Description

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

Synopsis

Documentation

(!>) :: Show a => b -> a -> b infixr 0 Source #

data TransIO x 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 #

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 #

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

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

run the transient computation with a blank state

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

run the transient computation with an 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 his own state data

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

warning: radiactive untyped stuff. handle with care

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

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

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, that the parameter type match the input of the first continuation. Normally this makes sense if it stop the current flow with stop after the invocation

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

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

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

data IDynamic Source #

dynamic serializable data for logging

Constructors

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

stop :: Alternative m => m stopped Source #

a sinonym of empty that can be used in a monadic expression. it stop the computation and execute the next alternative computation (composed with <|>)

class AdditionalOperators m where Source #

Minimal complete definition

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

Methods

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

executes the second operand even if the frist return empty. A normal imperative (monadic) sequence uses the operator (>>) which in the Transient monad does not execute the next operand if the previous one return empty.

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

forces the execution of the second operand even if the first stop. It does not execute the second operand as result of internal events occuring in the first operand. Return the first result

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

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

forces the execution of the second operand even if the first stop. Return the first result. The second operand is executed also when internal events happens in the first operand and it returns something

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

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

when the first operand is an asynchronous operation, the second operand is executed once (one single time) when the first completes his first asyncronous operation.

This is useful for spawning asynchronous or distributed tasks that are singletons and that should start when the first one is set up.

for example a streaming where the event receivers are acivated before the senders.

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 :: [t] -> [t] Source #

Threads

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

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

threads :: Int -> TransIO a -> TransIO 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 :: TransIO a -> TransientIO a Source #

delete all the previous childs generated by the expression taken as parameter 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 :: Int -> TransIO () Source #

assure that at least there are n threads available

freeThreads :: TransIO a -> TransIO a Source #

The threads generated in the process passed as parameter will not be killed by `kill*` primitives

hookedThreads :: TransIO a -> TransIO 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 threads of the current thread

extensible state: session data management

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

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

getSData :: Typeable a => TransIO a Source #

getData 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"

To have the same semantics and guarantees than get, use a default value:

getInt= getSData <|> return (0 :: Int)

The default value (0 in this case) has the same role than the initial value in a state monad. The difference is that you can define as many get as you need for all your data types.

To distingish two data with the same types, use newtype definitions.

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

set session data for this type. retrieved with getData or getSData Note that this is data in a state monad, that means that the update only affect downstream in the monad execution. it is not a global state neither a per user or per thread state it is a monadic state like the one of a state monad.

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

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

generator of identifiers that are unique withing the current monadic sequence They are not unique in the whole program.

waitEvents :: IO b -> TransIO 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 -> TransIO b Source #

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

spawn :: IO b -> TransIO b Source #

variant of waitEvents that spawn free threads. It is a little faster at the cost of no thread control

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

executes an IO action each certain interval of time and return his value if it changes

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

return empty to the current thread, in new thread, execute the IO action, this IO action modify an internal buffer. then, executes the closure where parallel is located In this new execution, since the buffer is filled, parallel return the content of this buffer. Then it launch the continuation after it with this new value returned by the closure.

If the maximum number of threads, set with threads has been reached parallel perform the work sequentially, in the current thread. So parallel means that 'it can be parallelized if there are thread available'

if there is a limitation of threads, when a thread finish, the counter of threads available is increased so another parallel can make use of it.

The behaviour of parallel depend on StreamData; If SMore, parallel will excute again the IO action. with SLast, SDone and SError, parallel will not repeat the IO action anymore.

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

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

kill all the child 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 -> TransIO eventdata Source #

deinvert an event handler.

The first parameter is the setter of the event handler to be deinverted. Usually it is the primitive provided by a framework to set an event handler

the second parameter is the value to return to the event handler. Usually it is `return()`

it configures the event handler by calling the setter of the event handler with the current continuation

non-blocking keyboard input

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

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

input :: (Typeable a, Read a, Show a) => (a -> Bool) -> String -> TransIO 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, wich watch continuously, input only wait for one valid response

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

non blocking getLine with a validator

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

stay :: MVar (Either String (Maybe b)) -> IO b Source #

wait for the execution of exit and return the result

newtype Exit a Source #

keep the main thread running, initiate the non blocking keyboard input and execute the transient computation.

It also read a slash-separated list of string that are read by option and input as if they were entered by the keyboard

 foo  -p  options/to/be/read/by/option/and/input

Constructors

Exit a 

keep :: Typeable a => TransIO a -> IO a Source #

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

same than keepbut do not initiate the asynchronous keyboard input. Useful for debugging or for creating background tasks.

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

force the finalization of the main thread and thus, all the Transient block (and the application if there is no more code)

exit' :: Typeable * a => a -> TransIO b Source #

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

alternative operator for maybe values. Used in infix mode

Orphan instances