| Copyright | (c) 2019 Commonwealth Scientific and Industrial Research Organisation (CSIRO) | 
|---|---|
| License | BSD-3 | 
| Maintainer | dave.laing.80@gmail.com | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Reflex.Host.Basic
Description
BasicGuest provides instances that most reflex programs need:
MonadIOMonadFixMonadSampleMonadHoldNotReadyPostBuildPerformEvent—hasPerformable(BasicGuestt m)MonadIOTriggerEventAdjustable
For some usage examples, see the example directory
Synopsis
- data BasicGuest t (m :: * -> *) a
 - type BasicGuestConstraints t (m :: * -> *) = (MonadReflexHost t m, MonadHold t m, MonadSample t m, Ref m ~ Ref IO, MonadRef (HostFrame t), Ref (HostFrame t) ~ Ref IO, MonadIO (HostFrame t), PrimMonad (HostFrame t), MonadIO m, MonadFix m)
 - basicHostWithQuit :: (forall t m. BasicGuestConstraints t m => BasicGuest t m (Event t ())) -> IO ()
 - basicHostForever :: (forall t m. BasicGuestConstraints t m => BasicGuest t m ()) -> IO ()
 - repeatUntilQuit :: BasicGuestConstraints t m => IO a -> Event t () -> BasicGuest t m (Event t a)
 - repeatUntilQuit_ :: BasicGuestConstraints t m => IO a -> Event t () -> BasicGuest t m ()
 
Documentation
data BasicGuest t (m :: * -> *) a Source #
Instances
type BasicGuestConstraints t (m :: * -> *) = (MonadReflexHost t m, MonadHold t m, MonadSample t m, Ref m ~ Ref IO, MonadRef (HostFrame t), Ref (HostFrame t) ~ Ref IO, MonadIO (HostFrame t), PrimMonad (HostFrame t), MonadIO m, MonadFix m) Source #
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
Arguments
| :: BasicGuestConstraints t m | |
| => IO a | Action to repeatedly run  | 
| -> Event t () | 
  | 
| -> 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
Arguments
| :: BasicGuestConstraints t m | |
| => IO a | Action to repeatedly run  | 
| -> Event t () | 
  | 
| -> 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.