reflex-0.6.1: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Reflex.Spider

Contents

Description

 
Synopsis

Documentation

type Spider = SpiderTimeline Global Source #

The default, global Spider environment

data SpiderTimeline x Source #

Designates the default, global Spider timeline

Instances
HasSpiderTimeline x => ReflexHost (SpiderTimeline x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Associated Types

type EventTrigger (SpiderTimeline x) :: * -> * Source #

type EventHandle (SpiderTimeline x) :: * -> * Source #

type HostFrame (SpiderTimeline x) :: * -> * Source #

HasSpiderTimeline x => Reflex (SpiderTimeline x :: *) Source # 
Instance details

Defined in Reflex.Spider.Internal

Associated Types

data Behavior (SpiderTimeline x) a :: * Source #

data Event (SpiderTimeline x) a :: * Source #

data Dynamic (SpiderTimeline x) a :: * Source #

data Incremental (SpiderTimeline x) a :: * Source #

type PushM (SpiderTimeline x) :: * -> * Source #

type PullM (SpiderTimeline x) :: * -> * Source #

Methods

never :: Event (SpiderTimeline x) a Source #

constant :: a -> Behavior (SpiderTimeline x) a Source #

push :: (a -> PushM (SpiderTimeline x) (Maybe b)) -> Event (SpiderTimeline x) a -> Event (SpiderTimeline x) b Source #

pushCheap :: (a -> PushM (SpiderTimeline x) (Maybe b)) -> Event (SpiderTimeline x) a -> Event (SpiderTimeline x) b Source #

pull :: PullM (SpiderTimeline x) a -> Behavior (SpiderTimeline x) a Source #

merge :: GCompare k => DMap k (Event (SpiderTimeline x)) -> Event (SpiderTimeline x) (DMap k Identity) Source #

fan :: GCompare k => Event (SpiderTimeline x) (DMap k Identity) -> EventSelector (SpiderTimeline x) k Source #

switch :: Behavior (SpiderTimeline x) (Event (SpiderTimeline x) a) -> Event (SpiderTimeline x) a Source #

coincidence :: Event (SpiderTimeline x) (Event (SpiderTimeline x) a) -> Event (SpiderTimeline x) a Source #

current :: Dynamic (SpiderTimeline x) a -> Behavior (SpiderTimeline x) a Source #

updated :: Dynamic (SpiderTimeline x) a -> Event (SpiderTimeline x) a Source #

unsafeBuildDynamic :: PullM (SpiderTimeline x) a -> Event (SpiderTimeline x) a -> Dynamic (SpiderTimeline x) a Source #

unsafeBuildIncremental :: Patch p => PullM (SpiderTimeline x) (PatchTarget p) -> Event (SpiderTimeline x) p -> Incremental (SpiderTimeline x) p Source #

mergeIncremental :: GCompare k => Incremental (SpiderTimeline x) (PatchDMap k (Event (SpiderTimeline x))) -> Event (SpiderTimeline x) (DMap k Identity) Source #

mergeIncrementalWithMove :: GCompare k => Incremental (SpiderTimeline x) (PatchDMapWithMove k (Event (SpiderTimeline x))) -> Event (SpiderTimeline x) (DMap k Identity) Source #

currentIncremental :: Patch p => Incremental (SpiderTimeline x) p -> Behavior (SpiderTimeline x) (PatchTarget p) Source #

updatedIncremental :: Patch p => Incremental (SpiderTimeline x) p -> Event (SpiderTimeline x) p Source #

incrementalToDynamic :: Patch p => Incremental (SpiderTimeline x) p -> Dynamic (SpiderTimeline x) (PatchTarget p) Source #

behaviorCoercion :: Coercion a b -> Coercion (Behavior (SpiderTimeline x) a) (Behavior (SpiderTimeline x) b) Source #

eventCoercion :: Coercion a b -> Coercion (Event (SpiderTimeline x) a) (Event (SpiderTimeline x) b) Source #

dynamicCoercion :: Coercion a b -> Coercion (Dynamic (SpiderTimeline x) a) (Dynamic (SpiderTimeline x) b) Source #

mergeIntIncremental :: Incremental (SpiderTimeline x) (PatchIntMap (Event (SpiderTimeline x) a)) -> Event (SpiderTimeline x) (IntMap a) Source #

fanInt :: Event (SpiderTimeline x) (IntMap a) -> EventSelectorInt (SpiderTimeline x) a Source #

HasSpiderTimeline x => MonadReflexHost (SpiderTimeline x) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Associated Types

type ReadPhase (SpiderHost x) :: * -> * Source #

MonadReflexCreateTrigger (SpiderTimeline x) (SpiderHostFrame x) Source # 
Instance details

Defined in Reflex.Spider.Internal

MonadReflexCreateTrigger (SpiderTimeline x) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadReadEvent (SpiderTimeline x) (ReadPhase x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadSubscribeEvent (SpiderTimeline x) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadSubscribeEvent (SpiderTimeline x) (SpiderHostFrame x) Source # 
Instance details

Defined in Reflex.Spider.Internal

NotReady (SpiderTimeline x) (SpiderHostFrame x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadHold (SpiderTimeline x :: *) (ReadPhase x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadHold (SpiderTimeline x :: *) (SpiderHostFrame x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadHold (SpiderTimeline x :: *) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadHold (SpiderTimeline x :: *) (SpiderPushM x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadHold (SpiderTimeline x :: *) (EventM x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadSample (SpiderTimeline x :: *) (ReadPhase x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadSample (SpiderTimeline x :: *) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadSample (SpiderTimeline x :: *) (SpiderHostFrame x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadSample (SpiderTimeline x :: *) (SpiderPushM x) Source # 
Instance details

Defined in Reflex.Spider.Internal

MonadSample (SpiderTimeline x :: *) (SpiderPullM x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadSample (SpiderTimeline x :: *) (EventM x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

sample :: Behavior (SpiderTimeline x) a -> EventM x a Source #

HasSpiderTimeline x => Monad (Dynamic (SpiderTimeline x)) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => Functor (Dynamic (SpiderTimeline x)) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

fmap :: (a -> b) -> Dynamic (SpiderTimeline x) a -> Dynamic (SpiderTimeline x) b #

(<$) :: a -> Dynamic (SpiderTimeline x) b -> Dynamic (SpiderTimeline x) a #

HasSpiderTimeline x => Applicative (Dynamic (SpiderTimeline x)) Source # 
Instance details

Defined in Reflex.Spider.Internal

type EventTrigger (SpiderTimeline x) Source # 
Instance details

Defined in Reflex.Spider.Internal

type EventHandle (SpiderTimeline x) Source # 
Instance details

Defined in Reflex.Spider.Internal

type HostFrame (SpiderTimeline x) Source # 
Instance details

Defined in Reflex.Spider.Internal

data Behavior (SpiderTimeline x :: *) a Source # 
Instance details

Defined in Reflex.Spider.Internal

data Event (SpiderTimeline x :: *) a Source # 
Instance details

Defined in Reflex.Spider.Internal

data Dynamic (SpiderTimeline x :: *) a Source # 
Instance details

Defined in Reflex.Spider.Internal

data Incremental (SpiderTimeline x :: *) p Source # 
Instance details

Defined in Reflex.Spider.Internal

type PushM (SpiderTimeline x :: *) Source # 
Instance details

Defined in Reflex.Spider.Internal

type PullM (SpiderTimeline x :: *) Source # 
Instance details

Defined in Reflex.Spider.Internal

data Global Source #

A statically allocated SpiderTimeline

data SpiderHost x a Source #

The monad for actions that manipulate a Spider timeline identified by x

Instances
Monad (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

(>>=) :: SpiderHost x a -> (a -> SpiderHost x b) -> SpiderHost x b #

(>>) :: SpiderHost x a -> SpiderHost x b -> SpiderHost x b #

return :: a -> SpiderHost x a #

fail :: String -> SpiderHost x a #

Functor (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

fmap :: (a -> b) -> SpiderHost x a -> SpiderHost x b #

(<$) :: a -> SpiderHost x b -> SpiderHost x a #

MonadFix (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

mfix :: (a -> SpiderHost x a) -> SpiderHost x a #

Applicative (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

pure :: a -> SpiderHost x a #

(<*>) :: SpiderHost x (a -> b) -> SpiderHost x a -> SpiderHost x b #

liftA2 :: (a -> b -> c) -> SpiderHost x a -> SpiderHost x b -> SpiderHost x c #

(*>) :: SpiderHost x a -> SpiderHost x b -> SpiderHost x b #

(<*) :: SpiderHost x a -> SpiderHost x b -> SpiderHost x a #

MonadIO (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

liftIO :: IO a -> SpiderHost x a #

MonadException (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

throw :: Exception e => e -> SpiderHost x a #

catch :: Exception e => SpiderHost x a -> (e -> SpiderHost x a) -> SpiderHost x a #

finally :: SpiderHost x a -> SpiderHost x b -> SpiderHost x a #

MonadAsyncException (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

mask :: ((forall a. SpiderHost x a -> SpiderHost x a) -> SpiderHost x b) -> SpiderHost x b #

MonadRef (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Associated Types

type Ref (SpiderHost x) :: * -> * #

Methods

newRef :: a -> SpiderHost x (Ref (SpiderHost x) a) #

readRef :: Ref (SpiderHost x) a -> SpiderHost x a #

writeRef :: Ref (SpiderHost x) a -> a -> SpiderHost x () #

modifyRef :: Ref (SpiderHost x) a -> (a -> a) -> SpiderHost x () #

modifyRef' :: Ref (SpiderHost x) a -> (a -> a) -> SpiderHost x () #

MonadAtomicRef (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Methods

atomicModifyRef :: Ref (SpiderHost x) a -> (a -> (a, b)) -> SpiderHost x b #

atomicModifyRef' :: Ref (SpiderHost x) a -> (a -> (a, b)) -> SpiderHost x b #

HasSpiderTimeline x => MonadReflexHost (SpiderTimeline x) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

Associated Types

type ReadPhase (SpiderHost x) :: * -> * Source #

MonadReflexCreateTrigger (SpiderTimeline x) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadSubscribeEvent (SpiderTimeline x) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadHold (SpiderTimeline x :: *) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

HasSpiderTimeline x => MonadSample (SpiderTimeline x :: *) (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

type Ref (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

type Ref (SpiderHost x) = Ref IO
type ReadPhase (SpiderHost x) Source # 
Instance details

Defined in Reflex.Spider.Internal

runSpiderHost :: SpiderHost Global a -> IO a Source #

Run an action affecting the global Spider timeline; this will be guarded by a mutex for that timeline

runSpiderHostForTimeline :: SpiderHost x a -> SpiderTimelineEnv x -> IO a Source #

Run an action affecting a given Spider timeline; this will be guarded by a mutex for that timeline

newSpiderTimeline :: IO (Some SpiderTimelineEnv) Source #

Create a new SpiderTimelineEnv

withSpiderTimeline :: (forall x. HasSpiderTimeline x => SpiderTimelineEnv x -> IO r) -> IO r Source #

Pass a new timeline to the given function.

Deprecated

type SpiderEnv = SpiderTimeline Source #

Deprecated: Use SpiderTimelineEnv instead

SpiderEnv is the old name for SpiderTimeline