essence-of-live-coding-0.2.1: General purpose live coding framework

Safe HaskellSafe
LanguageHaskell2010

LiveCoding.Handle

Synopsis

Documentation

data Handle m h Source #

Container for unserialisable values, such as IORefs, threads, MVars, pointers, and device handles.

In a Handle, you can store a mechanism to create and destroy a value that survives live coding even if does not have a Data instance. Using the function handling, you can create a cell that will automatically initialise your value, and register it in the HandlingStateT monad transformer, which takes care of automatically destroying it (if necessary) when it does not occur anymore in a later revision of your live program.

Have a look at Examples for some ready-to-use implementations.

In short, Handle is an opaque, automatically constructing and garbage collecting container for arbitrary values in the live coding environment.

Constructors

Handle 

Fields

handling :: (Typeable h, Monad m) => Handle m h -> Cell (HandlingStateT m) arbitrary h Source #

Hide a handle in a cell, taking care of initialisation and destruction.

Upon the first tick (or directly after migration), the create method of the Handle is called, and the result stored. This result is then not changed anymore until the cell is removed again. Once it is removed, the destructor will be called on the next tick.

Migrations will by default not inspect the interior of a handling cell. This means that handles are only migrated if they have exactly the same type.

data HandlingState m Source #

Hold a map of registered handle keys and destructors

Constructors

HandlingState 

Fields

Instances
Typeable m => Data (HandlingState m) Source # 
Instance details

Defined in LiveCoding.Handle

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HandlingState m -> c (HandlingState m) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HandlingState m) #

toConstr :: HandlingState m -> Constr #

dataTypeOf :: HandlingState m -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HandlingState m)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HandlingState m)) #

gmapT :: (forall b. Data b => b -> b) -> HandlingState m -> HandlingState m #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HandlingState m -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HandlingState m -> r #

gmapQ :: (forall d. Data d => d -> u) -> HandlingState m -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HandlingState m -> u #

gmapM :: Monad m0 => (forall d. Data d => d -> m0 d) -> HandlingState m -> m0 (HandlingState m) #

gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> HandlingState m -> m0 (HandlingState m) #

gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> HandlingState m -> m0 (HandlingState m) #

Launchable (StateT (HandlingState IO) IO) Source # 
Instance details

Defined in LiveCoding.RuntimeIO.Launch

type HandlingStateT m = StateT (HandlingState m) m Source #

In this monad, handles can be registered, and their destructors automatically executed. It is basically a monad in which handles are automatically garbage collected.

isRegistered :: Destructor m -> Bool Source #

runHandlingState :: (Monad m, Typeable m) => LiveProgram (HandlingStateT m) -> LiveProgram m Source #

Like runHandlingStateC, but for whole live programs.

runHandlingStateC :: forall m a b. (Monad m, Typeable m) => Cell (HandlingStateT m) a b -> Cell m a b Source #

Apply this to your main live cell before passing it to the runtime.

On the first tick, it initialises the HandlingState at "no handles".

On every step, it does:

  1. Unregister all handles
  2. Register currently present handles
  3. Destroy all still unregistered handles (i.e. those that were removed in the last tick)

runHandlingStateT :: Monad m => HandlingStateT m a -> m a Source #

Handle the HandlingStateT effect _without_ garbage collection. Apply this to your main loop after calling foreground. Since there is no garbage collection, don't use this function for live coding.