reflex-0.6.4.1: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell2010

Reflex.BehaviorWriter.Base

Description

 
Synopsis

Documentation

newtype BehaviorWriterT t w m a Source #

A basic implementation of MonadBehaviorWriter.

Constructors

BehaviorWriterT 

Fields

Instances
(Monad m, Monoid w, Reflex t) => MonadBehaviorWriter t w (BehaviorWriterT t w m) Source # 
Instance details

Defined in Reflex.BehaviorWriter.Base

Methods

tellBehavior :: Behavior t w -> BehaviorWriterT t w m () Source #

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

Defined in Reflex.BehaviorWriter.Base

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

Defined in Reflex.BehaviorWriter.Base

Methods

ask :: BehaviorWriterT t w m r #

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

get :: BehaviorWriterT t w m s #

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

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

(Adjustable t m, Monoid w, MonadHold t m, Reflex t) => Adjustable t (BehaviorWriterT t w m) Source # 
Instance details

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

Defined in Reflex.BehaviorWriter.Base

Associated Types

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

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

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

Defined in Reflex.BehaviorWriter.Base

Associated Types

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

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

Defined in Reflex.NotReady.Class

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

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

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

MonadTrans (BehaviorWriterT t w) Source # 
Instance details

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

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

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

Defined in Reflex.BehaviorWriter.Base

Associated Types

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

Methods

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

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

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

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

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

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

Defined in Reflex.BehaviorWriter.Base

Methods

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

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

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

Defined in Reflex.BehaviorWriter.Base

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

Defined in Reflex.BehaviorWriter.Base

type Response (BehaviorWriterT t w m) Source # 
Instance details

Defined in Reflex.BehaviorWriter.Base

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

Defined in Reflex.BehaviorWriter.Base

runBehaviorWriterT :: (Monad m, Reflex t, Monoid w) => BehaviorWriterT t w m a -> m (a, Behavior t w) Source #

Run a BehaviorWriterT action. The behavior writer output will be provided along with the result of the action.

withBehaviorWriterT :: (Monoid w, Monoid w', Reflex t, MonadHold t m) => (w -> w') -> BehaviorWriterT t w m a -> BehaviorWriterT t w' m a Source #

Map a function over the output of a BehaviorWriterT.