reflex-0.1.0: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Reflex.Dynamic

Synopsis

Documentation

data Dynamic t a Source

updated :: Dynamic t a -> Event t a Source

constDyn :: Reflex t => a -> Dynamic t a Source

holdDyn :: MonadHold t m => a -> Event t a -> m (Dynamic t a) Source

nubDyn :: (Reflex t, Eq a) => Dynamic t a -> Dynamic t a Source

count :: (Reflex t, MonadHold t m, MonadFix m, Num b) => Event t a -> m (Dynamic t b) Source

toggle :: (Reflex t, MonadHold t m, MonadFix m) => Bool -> Event t a -> m (Dynamic t Bool) Source

switchPromptlyDyn :: forall t a. Reflex t => Dynamic t (Event t a) -> Event t a Source

Switches to the new event whenever it receives one. Switching occurs *before* occurring the inner event.

tagDyn :: Reflex t => Dynamic t a -> Event t b -> Event t a Source

attachDyn :: Reflex t => Dynamic t a -> Event t b -> Event t (a, b) Source

attachDynWith :: Reflex t => (a -> b -> c) -> Dynamic t a -> Event t b -> Event t c Source

attachDynWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Dynamic t a -> Event t b -> Event t c Source

mapDyn :: (Reflex t, MonadHold t m) => (a -> b) -> Dynamic t a -> m (Dynamic t b) Source

forDyn :: (Reflex t, MonadHold t m) => Dynamic t a -> (a -> b) -> m (Dynamic t b) Source

mapDynM :: forall t m a b. (Reflex t, MonadHold t m) => (forall m'. MonadSample t m' => a -> m' b) -> Dynamic t a -> m (Dynamic t b) Source

foldDyn :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> b) -> b -> Event t a -> m (Dynamic t b) Source

foldDynM :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t b) -> b -> Event t a -> m (Dynamic t b) Source

combineDyn :: forall t m a b c. (Reflex t, MonadHold t m) => (a -> b -> c) -> Dynamic t a -> Dynamic t b -> m (Dynamic t c) Source

collectDyn :: (RebuildSortedHList (HListElems b), IsHList a, IsHList b, AllAreFunctors (Dynamic t) (HListElems b), Reflex t, MonadHold t m, HListElems a ~ FunctorList (Dynamic t) (HListElems b)) => a -> m (Dynamic t b) Source

mconcatDyn :: forall t m a. (Reflex t, MonadHold t m, Monoid a) => [Dynamic t a] -> m (Dynamic t a) Source

distributeDMapOverDyn :: forall t m k. (Reflex t, MonadHold t m, GCompare k) => DMap (WrapArg (Dynamic t) k) -> m (Dynamic t (DMap k)) Source

joinDyn :: forall t a. Reflex t => Dynamic t (Dynamic t a) -> Dynamic t a Source

joinDynThroughMap :: forall t k a. (Reflex t, Ord k) => Dynamic t (Map k (Dynamic t a)) -> Dynamic t (Map k a) Source

traceDyn :: (Reflex t, Show a) => String -> Dynamic t a -> Dynamic t a Source

traceDynWith :: Reflex t => (a -> String) -> Dynamic t a -> Dynamic t a Source

splitDyn :: (Reflex t, MonadHold t m) => Dynamic t (a, b) -> m (Dynamic t a, Dynamic t b) Source

data Demux t k Source

demux :: (Reflex t, Ord k) => Dynamic t k -> Demux t k Source

getDemuxed :: (Reflex t, MonadHold t m, Eq k) => Demux t k -> k -> m (Dynamic t Bool) Source

data HList l where Source

Constructors

HNil :: HList [] 
HCons :: e -> HList l -> HList (e : l) infixr 2 

data FHList f l where Source

Constructors

FHNil :: FHList f [] 
FHCons :: f e -> FHList f l -> FHList f (e : l) 

distributeFHListOverDyn :: forall t m l. (Reflex t, MonadHold t m, RebuildSortedHList l) => FHList (Dynamic t) l -> m (Dynamic t (HList l)) Source