reflex-external-ref-1.1.0.0: External reference with reactivity support

Safe HaskellNone
LanguageHaskell2010

Reflex.ExternalRef

Description

External reference with reactivity support. The reference is needed in glue code between reflex and external libs where you cannot sample from dynamics with MonadSample.

Synopsis

Documentation

data ExternalRef t a Source #

Holds value of type a and provides ways for notifying FRP network about changes of the variable.

This abstraction is helpful for storing counters, lists of internal resources and so on. It is designed to be updated from outputs of FRP network, not from outer world.

Constructors

ExternalRef 

Fields

Instances
Generic (ExternalRef t a) Source # 
Instance details

Defined in Reflex.ExternalRef

Associated Types

type Rep (ExternalRef t a) :: Type -> Type #

Methods

from :: ExternalRef t a -> Rep (ExternalRef t a) x #

to :: Rep (ExternalRef t a) x -> ExternalRef t a #

NFData (ExternalRef t a) Source # 
Instance details

Defined in Reflex.ExternalRef

Methods

rnf :: ExternalRef t a -> () #

type Rep (ExternalRef t a) Source # 
Instance details

Defined in Reflex.ExternalRef

type Rep (ExternalRef t a) = D1 (MetaData "ExternalRef" "Reflex.ExternalRef" "reflex-external-ref-1.1.0.0-inplace" False) (C1 (MetaCons "ExternalRef" PrefixI True) (S1 (MetaSel (Just "externalRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IORef a)) :*: (S1 (MetaSel (Just "externalEvent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Event t a)) :*: S1 (MetaSel (Just "externalFire") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (a -> IO ())))))

newExternalRef :: (MonadIO m, TriggerEvent t m) => a -> m (ExternalRef t a) Source #

Creation of external ref in host monad

readExternalRef :: MonadIO m => ExternalRef t a -> m a Source #

Read current value of external reference

writeExternalRef :: MonadIO m => ExternalRef t a -> a -> m () Source #

Write new value to external reference and notify FRP network. The function evaluates the value to WNF.

modifyExternalRef :: MonadIO m => ExternalRef t a -> (a -> (a, b)) -> m b Source #

Atomically modify an external ref and notify FRP network. The function evaluates the value to WNF.

modifyExternalRef_ :: MonadIO m => ExternalRef t a -> (a -> a) -> m () Source #

Atomically modify an external ref and notify FRP network. The function evaluates the value to WNF. Returns nothing

modifyExternalRefMaybe :: MonadIO m => ExternalRef t a -> (a -> Maybe (a, b)) -> m (Maybe b) Source #

If the function evaluates to Just then Atomically modify an external ref and notify FRP network. The function evaluates the value to WNF. Return the Maybe result of function's evaluation

modifyExternalRefMaybe_ :: MonadIO m => ExternalRef t a -> (a -> Maybe a) -> m () Source #

If the function evaluates to Just then Atomically modify an external ref and notify FRP network. The function evaluates the value to WNF. Returns nothing The function discards the result

modifyExternalRefM :: MonadIO m => ExternalRef t a -> (a -> m (a, b)) -> m b Source #

Modify (not atomically) an external ref and notify FRP network. The function evaluates the value to WNF.

modifyExternalRefM_ :: MonadIO m => ExternalRef t a -> (a -> m a) -> m () Source #

Modify (not atomically) an external ref and notify FRP network. The function evaluates the value to WNF.

modifyExternalRefMaybeM :: MonadIO m => ExternalRef t a -> (a -> m (Maybe (a, b))) -> m (Maybe b) Source #

If the function evaluates to Just then Modify (not atomically) an external ref and notify FRP network. The function evaluates the value to WNF.

modifyExternalRefMaybeM_ :: MonadIO m => ExternalRef t a -> (a -> m (Maybe a)) -> m () Source #

If the function evaluates to Just then Modify (not atomically) an external ref and notify FRP network. The function evaluates the value to WNF. The function discards the result

externalRefBehavior :: (MonadHold t m, MonadIO m) => ExternalRef t a -> m (Behavior t a) Source #

Construct a behavior from external reference

externalRefDynamic :: (MonadHold t m, MonadIO m) => ExternalRef t a -> m (Dynamic t a) Source #

Get dynamic that tracks value of the internal ref

externalFromDynamic :: (MonadHold t m, TriggerEvent t m, PerformEvent t m, Reflex t, MonadIO m, MonadIO (Performable m)) => Dynamic t a -> m (ExternalRef t a) Source #

Create external ref that tracks content of dynamic. Editing of the ref has no effect on the original dynamic.

fmapExternalRef :: (MonadIO m, TriggerEvent t m, PerformEvent t m, MonadIO (Performable m)) => (a -> b) -> ExternalRef t a -> m (ExternalRef t b) Source #

Creates external ref as a result of "fmapping" a function to the original ref. ExternalRef t is not a true Functior, since it requres monadic action to "fmap" Editing of the new ref has no effect on the original dynamic.