essence-of-live-coding-0.2.6: General purpose live coding framework
Safe HaskellSafe-Inferred
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 reloads occuring during 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

Instances

Instances details
MFunctor Handle Source # 
Instance details

Defined in LiveCoding.Handle

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> Handle m b -> Handle n b #

combineHandles :: Applicative m => Handle m h1 -> Handle m h2 -> Handle m (h1, h2) Source #

Combine two handles to one.

Handles are not quite Monoids because of the extra type parameter, but it is possible to combine them. In the combined handle, the first handle is created first and destroyed last.

Note: Handle is not an Applicative because it is not a Functor (because the destructor is contravariant in h).

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 ParametrisedHandle p m h Source #

Generalisation of Handle carrying an additional parameter which may change at runtime.

Like in a Handle, the h value of a ParametrisedHandle is preserved through live coding reloads. Additionally, the parameter p value can be adjusted, and triggers a destruction and reinitialisation whenever it changes.

Constructors

ParametrisedHandle 

Fields

Instances

Instances details
MFunctor (ParametrisedHandle p :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in LiveCoding.Handle

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> ParametrisedHandle p m b -> ParametrisedHandle p n b #

defaultChange :: (Eq p, Monad m) => (p -> m h) -> (p -> h -> m ()) -> p -> p -> h -> m h Source #

Given the methods createParametrised and destroyParametrised, build a fitting method for changeParametrised which

handlingParametrised :: (Typeable h, Typeable p, Monad m, Eq p) => ParametrisedHandle p m h -> Cell (HandlingStateT m) p h Source #

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

Upon the first tick, directly after migration, and after each parameter change, 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, or the parameter changes. A parameter change triggers the destructor immediately, but if the cell 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 parametrised handles are only migrated if they have exactly the same type.

toParametrised :: Monad m => Handle m h -> ParametrisedHandle () m h Source #

Every Handle is trivially a ParametrisedHandle when the parameter is the trivial type.