transient-0.1.0.2: 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

(!>) :: b -> b1 -> b 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

data IDynamic Source

dynamic serializable data for logging

Constructors

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

data Log Source

Instances

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 :: (Ord a, Num 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 for the

oneThread :: TransientIO a -> TransientIO a Source

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

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 Loop Source

Constructors

Once 
Loop 
Multithread 

Instances

waitEvents :: IO b -> TransientIO b Source

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

async :: IO b -> TransientIO b Source

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

data EventValue Source

Constructors

EventValue SData 

Instances

parallel :: IO (Either b b) -> TransientIO 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 finish, increase the counter of threads available, if there is a limitation of them.

loop :: EventF -> IO (Either a a1) -> 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' :: (Typeable * a, Read a) => (a -> Bool) -> IO a Source

non blocking getLine with a validator

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

keep :: TransientIO x -> IO b Source

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

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