reflex-basic-host-0.2: A basic `reflex` host for backend work

Copyright(c) 2019 Commonwealth Scientific and Industrial Research Organisation (CSIRO)
LicenseBSD-3
Maintainerdave.laing.80@gmail.com
Safe HaskellNone
LanguageHaskell2010

Reflex.Host.Basic

Description

BasicGuest provides instances that most reflex programs need:

For some usage examples, see the example directory

Synopsis

Documentation

data BasicGuest t (m :: * -> *) a Source #

Instances
ReflexHost t => NotReady t (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

notReadyUntil :: Event t a -> BasicGuest t m () #

notReady :: BasicGuest t m () #

(ReflexHost t, Ref m ~ Ref IO, MonadRef (HostFrame t), Ref (HostFrame t) ~ Ref IO, MonadIO (HostFrame t), PrimMonad (HostFrame t), MonadIO m) => PerformEvent t (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Associated Types

type Performable (BasicGuest t m) :: Type -> Type #

Methods

performEvent :: Event t (Performable (BasicGuest t m) a) -> BasicGuest t m (Event t a) #

performEvent_ :: Event t (Performable (BasicGuest t m) ()) -> BasicGuest t m () #

(ReflexHost t, MonadRef (HostFrame t), Ref (HostFrame t) ~ Ref IO) => TriggerEvent t (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

newTriggerEvent :: BasicGuest t m (Event t a, a -> IO ()) #

newTriggerEventWithOnComplete :: BasicGuest t m (Event t a, a -> IO () -> IO ()) #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> BasicGuest t m (Event t a) #

ReflexHost t => PostBuild t (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

getPostBuild :: BasicGuest t m (Event t ()) #

(ReflexHost t, Ref m ~ Ref IO, MonadHold t m, PrimMonad (HostFrame t)) => Adjustable t (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

runWithReplace :: BasicGuest t m a -> Event t (BasicGuest t m b) -> BasicGuest t m (a, Event t b) #

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

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

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

ReflexHost t => MonadSample (t :: Type) (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

sample :: Behavior t a -> BasicGuest t m a #

(ReflexHost t, MonadHold t m) => MonadHold (t :: Type) (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

hold :: a -> Event t a -> BasicGuest t m (Behavior t a) #

holdDyn :: a -> Event t a -> BasicGuest t m (Dynamic t a) #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> BasicGuest t m (Incremental t p) #

buildDynamic :: PushM t a -> Event t a -> BasicGuest t m (Dynamic t a) #

headE :: Event t a -> BasicGuest t m (Event t a) #

ReflexHost t => Monad (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

(>>=) :: BasicGuest t m a -> (a -> BasicGuest t m b) -> BasicGuest t m b #

(>>) :: BasicGuest t m a -> BasicGuest t m b -> BasicGuest t m b #

return :: a -> BasicGuest t m a #

fail :: String -> BasicGuest t m a #

ReflexHost t => Functor (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

fmap :: (a -> b) -> BasicGuest t m a -> BasicGuest t m b #

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

ReflexHost t => MonadFix (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

mfix :: (a -> BasicGuest t m a) -> BasicGuest t m a #

ReflexHost t => Applicative (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

pure :: a -> BasicGuest t m a #

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

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

(*>) :: BasicGuest t m a -> BasicGuest t m b -> BasicGuest t m b #

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

(ReflexHost t, MonadIO (HostFrame t)) => MonadIO (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

Methods

liftIO :: IO a -> BasicGuest t m a #

type Performable (BasicGuest t m) Source # 
Instance details

Defined in Reflex.Host.Basic

basicHostWithQuit :: (forall t m. BasicGuestConstraints t m => BasicGuest t m (Event t ())) -> IO () Source #

Run a BasicGuest, and return when the Event returned by the BasicGuest fires.

Each call runs on a separate spider timeline, so you can launch multiple hosts via forkIO or forkOS and they will not mutex each other.

NOTE: If you want to capture values from a build before the network starts firing (e.g., to hand off event triggers to another thread), populate an MVar (if threading) or IORef as you build the network. If you receive errors about untouchable type variables while doing this, add type annotations to constrain the MVar or IORef contents before passing them to the function that returns your BasicGuest. See the Multithread.hs example for a demonstration of this pattern, and where to put the type annotations.

basicHostForever :: (forall t m. BasicGuestConstraints t m => BasicGuest t m ()) -> IO () Source #

Run a BasicGuest without a quit Event.

basicHostForever guest = basicHostWithQuit $ never <$ guest

repeatUntilQuit Source #

Arguments

:: BasicGuestConstraints t m 
=> IO a

Action to repeatedly run

-> Event t ()

Event to stop the action

-> BasicGuest t m (Event t a) 

Augment a BasicGuest with an action that is repeatedly run until the provided Event fires. Each time the action completes, the returned Event will fire.

Example - providing a 'tick' Event to a network

myNetwork
  :: (Reflex t, MonadHold t m, MonadFix m)
  => Event t ()
  -> m (Dynamic t Int)
myNetwork = count

myGuest :: BasicGuestConstraints t m => BasicGuest t m (Event t ())
myGuest = mdo
  eTick <- repeatUntilQuit (void $ threadDelay 1000000) eQuit
  let
    eCountUpdated = updated dCount
    eQuit = () <$ ffilter (==5) eCountUpdated
  dCount <- myNetwork eTick

  performEvent_ $ liftIO . print <$> eCountUpdated
  pure eQuit

main :: IO ()
main = basicHostWithQuit myGuest

repeatUntilQuit_ Source #

Arguments

:: BasicGuestConstraints t m 
=> IO a

Action to repeatedly run

-> Event t ()

Event to stop the action

-> BasicGuest t m () 

Like repeatUntilQuit, but it doesn't do anything with the result of the action. May be a little more efficient if you don't need it.