reflex-0.5.0.1: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Reflex.DynamicWriter.Base

Synopsis

Documentation

newtype DynamicWriterT t w m a Source #

A basic implementation of MonadDynamicWriter.

Constructors

DynamicWriterT 

Fields

Instances
EventWriter t w m => EventWriter t w (DynamicWriterT t v m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

tellEvent :: Event t w -> DynamicWriterT t v m () Source #

(Monad m, Monoid w, Reflex t) => MonadDynamicWriter t w (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

tellDyn :: Dynamic t w -> DynamicWriterT t w m () Source #

(MonadQuery t q m, Monad m) => MonadQuery t q (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

MonadReader r m => MonadReader r (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

ask :: DynamicWriterT t w m r #

local :: (r -> r) -> DynamicWriterT t w m a -> DynamicWriterT t w m a #

reader :: (r -> a) -> DynamicWriterT t w m a #

MonadState s m => MonadState s (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

get :: DynamicWriterT t w m s #

put :: s -> DynamicWriterT t w m () #

state :: (s -> (a, s)) -> DynamicWriterT t w m a #

MonadReflexCreateTrigger t m => MonadReflexCreateTrigger t (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

newEventWithTrigger :: (EventTrigger t a -> IO (IO ())) -> DynamicWriterT t w m (Event t a) Source #

newFanEventWithTrigger :: GCompare k => (forall a. k a -> EventTrigger t a -> IO (IO ())) -> DynamicWriterT t w m (EventSelector t k) Source #

(Adjustable t m, MonadFix m, Monoid w, MonadHold t m, Reflex t) => Adjustable t (DynamicWriterT t w m) Source #

When the execution of a DynamicWriterT action is adjusted using Adjustable, the Dynamic output of that action will also be updated to match.

Instance details

Defined in Reflex.DynamicWriter.Base

Methods

runWithReplace :: DynamicWriterT t w m a -> Event t (DynamicWriterT t w m b) -> DynamicWriterT t w m (a, Event t b) Source #

traverseIntMapWithKeyWithAdjust :: (Key -> v -> DynamicWriterT t w m v') -> IntMap v -> Event t (PatchIntMap v) -> DynamicWriterT t w m (IntMap v', Event t (PatchIntMap v')) Source #

traverseDMapWithKeyWithAdjust :: GCompare k => (forall a. k a -> v a -> DynamicWriterT t w m (v' a)) -> DMap k v -> Event t (PatchDMap k v) -> DynamicWriterT t w m (DMap k v', Event t (PatchDMap k v')) Source #

traverseDMapWithKeyWithAdjustWithMove :: GCompare k => (forall a. k a -> v a -> DynamicWriterT t w m (v' a)) -> DMap k v -> Event t (PatchDMapWithMove k v) -> DynamicWriterT t w m (DMap k v', Event t (PatchDMapWithMove k v')) Source #

PostBuild t m => PostBuild t (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

getPostBuild :: DynamicWriterT t w m (Event t ()) Source #

Requester t m => Requester t (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Associated Types

type Request (DynamicWriterT t w m) :: Type -> Type Source #

type Response (DynamicWriterT t w m) :: Type -> Type Source #

TriggerEvent t m => TriggerEvent t (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

newTriggerEvent :: DynamicWriterT t w m (Event t a, a -> IO ()) Source #

newTriggerEventWithOnComplete :: DynamicWriterT t w m (Event t a, a -> IO () -> IO ()) Source #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> DynamicWriterT t w m (Event t a) Source #

PerformEvent t m => PerformEvent t (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Associated Types

type Performable (DynamicWriterT t w m) :: Type -> Type Source #

NotReady t m => NotReady t (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.NotReady.Class

MonadHold t m => MonadHold (t :: Type) (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

hold :: a -> Event t a -> DynamicWriterT t w m (Behavior t a) Source #

holdDyn :: a -> Event t a -> DynamicWriterT t w m (Dynamic t a) Source #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> DynamicWriterT t w m (Incremental t p) Source #

buildDynamic :: PushM t a -> Event t a -> DynamicWriterT t w m (Dynamic t a) Source #

headE :: Event t a -> DynamicWriterT t w m (Event t a) Source #

MonadSample t m => MonadSample (t :: Type) (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

sample :: Behavior t a -> DynamicWriterT t w m a Source #

MonadTrans (DynamicWriterT t w) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

lift :: Monad m => m a -> DynamicWriterT t w m a #

Monad m => Monad (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

(>>=) :: DynamicWriterT t w m a -> (a -> DynamicWriterT t w m b) -> DynamicWriterT t w m b #

(>>) :: DynamicWriterT t w m a -> DynamicWriterT t w m b -> DynamicWriterT t w m b #

return :: a -> DynamicWriterT t w m a #

fail :: String -> DynamicWriterT t w m a #

Functor m => Functor (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

fmap :: (a -> b) -> DynamicWriterT t w m a -> DynamicWriterT t w m b #

(<$) :: a -> DynamicWriterT t w m b -> DynamicWriterT t w m a #

MonadFix m => MonadFix (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

mfix :: (a -> DynamicWriterT t w m a) -> DynamicWriterT t w m a #

Monad m => Applicative (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

pure :: a -> DynamicWriterT t w m a #

(<*>) :: DynamicWriterT t w m (a -> b) -> DynamicWriterT t w m a -> DynamicWriterT t w m b #

liftA2 :: (a -> b -> c) -> DynamicWriterT t w m a -> DynamicWriterT t w m b -> DynamicWriterT t w m c #

(*>) :: DynamicWriterT t w m a -> DynamicWriterT t w m b -> DynamicWriterT t w m b #

(<*) :: DynamicWriterT t w m a -> DynamicWriterT t w m b -> DynamicWriterT t w m a #

MonadIO m => MonadIO (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

liftIO :: IO a -> DynamicWriterT t w m a #

MonadException m => MonadException (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

throw :: Exception e => e -> DynamicWriterT t w m a #

catch :: Exception e => DynamicWriterT t w m a -> (e -> DynamicWriterT t w m a) -> DynamicWriterT t w m a #

finally :: DynamicWriterT t w m a -> DynamicWriterT t w m b -> DynamicWriterT t w m a #

MonadAsyncException m => MonadAsyncException (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

mask :: ((forall a. DynamicWriterT t w m a -> DynamicWriterT t w m a) -> DynamicWriterT t w m b) -> DynamicWriterT t w m b #

MonadRef m => MonadRef (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Associated Types

type Ref (DynamicWriterT t w m) :: Type -> Type #

Methods

newRef :: a -> DynamicWriterT t w m (Ref (DynamicWriterT t w m) a) #

readRef :: Ref (DynamicWriterT t w m) a -> DynamicWriterT t w m a #

writeRef :: Ref (DynamicWriterT t w m) a -> a -> DynamicWriterT t w m () #

modifyRef :: Ref (DynamicWriterT t w m) a -> (a -> a) -> DynamicWriterT t w m () #

modifyRef' :: Ref (DynamicWriterT t w m) a -> (a -> a) -> DynamicWriterT t w m () #

MonadAtomicRef m => MonadAtomicRef (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Methods

atomicModifyRef :: Ref (DynamicWriterT t w m) a -> (a -> (a, b)) -> DynamicWriterT t w m b #

atomicModifyRef' :: Ref (DynamicWriterT t w m) a -> (a -> (a, b)) -> DynamicWriterT t w m b #

type Ref (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

type Ref (DynamicWriterT t w m) = Ref m
type Request (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

type Request (DynamicWriterT t w m) = Request m
type Response (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

type Performable (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

runDynamicWriterT :: (MonadFix m, Reflex t, Monoid w) => DynamicWriterT t w m a -> m (a, Dynamic t w) Source #

Run a DynamicWriterT action. The dynamic writer output will be provided along with the result of the action.

withDynamicWriterT :: (Monoid w, Monoid w', Reflex t, MonadHold t m, MonadFix m) => (w -> w') -> DynamicWriterT t w m a -> DynamicWriterT t w' m a Source #

Map a function over the output of a DynamicWriterT.