essence-of-live-coding-0.2.7: General purpose live coding framework
Safe HaskellSafe-Inferred
LanguageHaskell2010

LiveCoding.Migrate.NoMigration

Description

If a data type is wrapped in NoMigration then it can be used as the state of a Cell without requiring it to have a Data instance. The consequence is that if the type has changed in between a livereload, then the previous saved value will be discarded, and no migration attempt will happen.

LiveCoding does not export delay and changes from this module. These functions should be used with a qualified import.

Synopsis

NoMigration data type and Data instance.

data NoMigration a Source #

Isomorphic to Maybe a but has a different Data instance. The Data instance for NoMigration a doesn't require a Data instance for a.

If a data type is wrapped in NoMigration then it can be used as the state of a Cell without requiring it to have a Data instance. The consequence is that if the type has changed in between a livereload, then the previous saved value will be discarded, and no migration attempt will happen.

Constructors

Initialized a 
Uninitialized 

Instances

Instances details
Foldable NoMigration Source # 
Instance details

Defined in LiveCoding.Migrate.NoMigration

Methods

fold :: Monoid m => NoMigration m -> m #

foldMap :: Monoid m => (a -> m) -> NoMigration a -> m #

foldMap' :: Monoid m => (a -> m) -> NoMigration a -> m #

foldr :: (a -> b -> b) -> b -> NoMigration a -> b #

foldr' :: (a -> b -> b) -> b -> NoMigration a -> b #

foldl :: (b -> a -> b) -> b -> NoMigration a -> b #

foldl' :: (b -> a -> b) -> b -> NoMigration a -> b #

foldr1 :: (a -> a -> a) -> NoMigration a -> a #

foldl1 :: (a -> a -> a) -> NoMigration a -> a #

toList :: NoMigration a -> [a] #

null :: NoMigration a -> Bool #

length :: NoMigration a -> Int #

elem :: Eq a => a -> NoMigration a -> Bool #

maximum :: Ord a => NoMigration a -> a #

minimum :: Ord a => NoMigration a -> a #

sum :: Num a => NoMigration a -> a #

product :: Num a => NoMigration a -> a #

Traversable NoMigration Source # 
Instance details

Defined in LiveCoding.Migrate.NoMigration

Methods

traverse :: Applicative f => (a -> f b) -> NoMigration a -> f (NoMigration b) #

sequenceA :: Applicative f => NoMigration (f a) -> f (NoMigration a) #

mapM :: Monad m => (a -> m b) -> NoMigration a -> m (NoMigration b) #

sequence :: Monad m => NoMigration (m a) -> m (NoMigration a) #

Functor NoMigration Source # 
Instance details

Defined in LiveCoding.Migrate.NoMigration

Methods

fmap :: (a -> b) -> NoMigration a -> NoMigration b #

(<$) :: a -> NoMigration b -> NoMigration a #

Typeable a => Data (NoMigration a) Source #

The Data instance for NoMigration a doesn't require a Data instance for a.

Instance details

Defined in LiveCoding.Migrate.NoMigration

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoMigration a -> c (NoMigration a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NoMigration a) #

toConstr :: NoMigration a -> Constr #

dataTypeOf :: NoMigration a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> NoMigration a -> NoMigration a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoMigration a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoMigration a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NoMigration a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NoMigration a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoMigration a -> m (NoMigration a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoMigration a -> m (NoMigration a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoMigration a -> m (NoMigration a) #

Show a => Show (NoMigration a) Source # 
Instance details

Defined in LiveCoding.Migrate.NoMigration

Eq a => Eq (NoMigration a) Source # 
Instance details

Defined in LiveCoding.Migrate.NoMigration

Utility functions which internally use NoMigration.

delay :: (Monad m, Typeable a) => a -> Cell m a a Source #

Like delay, but doesn't require Data instance, and only migrates the last value if it still has the same type.

changes :: (Typeable a, Eq a, Monad m) => Cell m a (Maybe a) Source #

Like changes, but doesn't require Data instance, and only migrates the last value if it still is of the same type.

arrChangesM :: (Monad m, Typeable a, Typeable b, Eq a) => (a -> m b) -> Cell m a b Source #

Caching version of arrM.

Only runs the computation in m when the input value changes. Meanwhile it keeps outputing the last outputted value. Also runs the computation on the first tick. Does not require Data instance. On `:livereload` will run action again on first tick.

cellNoMigration :: (Typeable s, Functor m) => s -> (s -> a -> m (b, s)) -> Cell m a b Source #