-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Principled practical FRP -- -- FRP with first-class behaviors and interalized IO, without space leaks @package frpnow @version 0.18 module Control.FRPNow.Core -- | An event is a value that is known from some point in time on. data Event a -- | An behavior is a value that changes over time. data Behavior a -- | A never occuring event never :: Event a -- | Introduce a change over time. -- --
--   b `switch` e 
--   
-- -- Gives a behavior that acts as b initially, and switches to -- the behavior inside e as soon as e occurs. switch :: Behavior a -> Event (Behavior a) -> Behavior a -- | Observe a change over time. -- -- The behavior whenJust b gives at any point in time the event -- that the behavior b is Just at that time or -- afterwards. -- -- As an example, -- --
--   let getPos x 
--           | x > 0 = Just x
--           | otherwise = Nothing
--   in whenJust (getPos <$> b)
--   
-- -- Gives gives the event that the behavior b is positive. If -- b is currently positive then the event will occur now, -- otherwise it will be the first time that b becomes positive -- in the future. If b never again is positive then the result -- is never. whenJust :: Behavior (Maybe a) -> Behavior (Event a) -- | Not typically needed, used for event streams. -- -- If we have a behavior giving events, such that each time the behavior -- is sampled the obtained event is in the future, then this function -- ensures that we can use the event without inspecting it (i.e. before -- binding it). -- -- If the implementation samples such an event and it turns out the event -- does actually occur at the time the behavior is sampled, an error is -- thrown. futuristic :: Behavior (Event a) -> Behavior (Event a) -- | A monad that alows you to: -- -- -- -- All actions in the Now monad are conceptually instantaneous, -- which entails it is guaranteed that for any behavior b and -- Now action m: -- --
--      do x <- sample b; m ; y <- sample b; return (x,y) 
--   == do x <- sample b; m ; return (x,x) 
--   
data Now a -- | Asynchronously execte an IO action, and obtain the event that it is -- done. -- -- Starts a seperate thread for the IO action, and then immediatly -- returns the event that the IO action is done. Since all actions in the -- Now monad are instantaneous, the resulting event is guaranteed -- to occur in the future (not now). -- -- Use this for IO actions which might take a long time, such as waiting -- for a network message, reading a large file, or expensive -- computations. -- -- Note:Use this only when using FRPNow with Gloss or something -- else that does not block haskell threads. For use with GTK or other -- GUI libraries that do block Haskell threads, use asyncOS -- instead. async :: IO a -> Now (Event a) -- | Like async, but uses an OS thread instead of a regular -- lightweight thread. -- -- Useful when interacting with GUI systems that claim the main loop, -- such as GTK. asyncOS :: IO a -> Now (Event a) -- | Create an event that occurs when the callback is called. -- -- The callback can be safely called from any thread. An error occurs if -- the callback is called more than once. -- -- See callbackStream for a callback that can be called -- repeatidly. -- -- The event occurs strictly later than the time that the callback was -- created, even if the callback is called immediately. callback :: Now (Event a, a -> IO ()) -- | Sample the present value of a behavior sampleNow :: Behavior a -> Now a -- | Plan to execute a Now computation. -- -- When given a event carrying a now computation, execute that now -- computation as soon as the event occurs. If the event has already -- occured when planNow is called, then the Now computation -- will be executed immediatly. planNow :: Event (Now a) -> Now (Event a) -- | Synchronously execte an IO action. -- -- Use this is for IO actions which do not take a long time, such as -- opening a file or creating a widget. sync :: IO a -> Now a -- | Run the FRP system in master mode. -- -- Typically, you don't need this function, but instead use a function -- for whatever library you want to use FRPNow with such as -- runNowGTK, runNowGloss. This function can be used in -- case you are not interacting with any GUI library, only using FRPNow. -- -- Runs the given Now computation and the plans it makes until -- the ending event (given by the inital Now computation) -- occurs. Returns the value of the ending event. runNowMaster :: Now (Event a) -> IO a -- | General interface to interact with the FRP system. -- -- Typically, you don't need this function, but instead use a specialized -- function for whatever library you want to use FRPNow with such as -- runNowGTK or runNowGloss, which themselves are -- implemented using this function. initNow :: (IO (Maybe a) -> IO ()) -> Now (Event a) -> IO () instance GHC.Show.Show Control.FRPNow.Core.FRPWaitsForNeverException instance Control.Monad.IO.Class.MonadIO Control.FRPNow.Core.Now instance Control.Monad.Fix.MonadFix Control.FRPNow.Core.Now instance GHC.Base.Monad Control.FRPNow.Core.Now instance GHC.Base.Applicative Control.FRPNow.Core.Now instance GHC.Base.Functor Control.FRPNow.Core.Now instance GHC.Base.Monad Control.FRPNow.Core.Event instance GHC.Base.Monad Control.FRPNow.Core.Behavior instance Control.Monad.Fix.MonadFix Control.FRPNow.Core.Behavior instance GHC.Exception.Exception Control.FRPNow.Core.FRPWaitsForNeverException instance GHC.Base.Functor Control.FRPNow.Core.Behavior instance GHC.Base.Applicative Control.FRPNow.Core.Behavior instance GHC.Base.Functor Control.FRPNow.Core.Event instance GHC.Base.Applicative Control.FRPNow.Core.Event -- | Utility FRPNow functions module Control.FRPNow.Lib -- | Start with a constant and then switch -- -- Defined as: -- --
--   step a s = pure a `switch` s
--   
step :: a -> Event (Behavior a) -> Behavior a -- | Start with a constant, and switch to another constant when the event -- arrives. -- -- Defined as: -- --
--   cstep x e y = pure x `switch` (pure y <$ e)
--   
cstep :: a -> Event x -> a -> Behavior a -- | Like whenJust but on behaviors of type Bool instead of -- Maybe. -- -- Gives the event that the input behavior is True when :: Behavior Bool -> Behavior (Event ()) -- | Gives at any point in time the event that the input behavior changes, -- and the new value of the input behavior. change :: Eq a => Behavior a -> Behavior (Event a) -- | The resulting behavior gives at any point in time, the event that the -- input behavior next becomes true. I.e. the next event that -- there is an edge from False to True. If the input behavior is True -- already, the event gives the time that it is True again, after first -- being False for a period of time. edge :: Behavior Bool -> Behavior (Event ()) -- | Convert an event into a behavior that gives Nothing if the -- event has not occured yet, and Just the value of the event if -- the event has already occured. tryGetEv :: Event a -> Behavior (Maybe a) -- | The resulting behavior states wheter the input event has already -- occured. hasOccured :: Event x -> Behavior Bool -- | Gives the first of two events. -- -- If either of the events lies in the future, then the result will be -- the first of these events. If both events have already occured, the -- left event is returned. first :: Event a -> Event a -> Behavior (Event a) -- | Compare the time of two events. -- -- The resulting behavior gives an event, occuring at the same time as -- the earliest input event, of which the value indicates if the event -- where simultanious, or if one was earlier. -- -- If at the time of sampling both event lie in the past, then the result -- is that they are simulatinous. cmpTime :: Event a -> Event b -> Behavior (Event (EvOrd a b)) -- | The outcome of a cmpTime: the events occur simultanious, left -- is earlier or right is earlier. data EvOrd l r Simul :: l -> r -> EvOrd l r LeftEarlier :: l -> EvOrd l r RightEarlier :: r -> EvOrd l r -- | Gives the previous value of the behavior, starting with given value. -- -- This cannot be used to prevent immediate feedback loop! Use -- delay instead! prev :: Eq a => a -> Behavior a -> Behavior (Behavior a) -- | A (left) fold over a behavior. -- -- The inital value of the resulting behavior is f i x where -- i the initial value given, and x is the current -- value of the behavior. foldB :: Eq a => (b -> a -> b) -> b -> Behavior a -> Behavior (Behavior b) -- | When sampled at a point in time t, the behavior gives an event with -- the list of all values of the input behavior between time t and the -- time that the argument event occurs (including the value when the -- event occurs). sampleUntil :: Eq a => Behavior a -> Event () -> Behavior (Event [a]) -- | Plan to sample the behavior carried by the event as soon as possible. -- -- If the resulting behavior is sampled after the event occurs, then the -- behavior carried by the event will be sampled now. planB :: Event (Behavior a) -> Behavior (Event a) -- | Obtain the value of the behavior at the time the event occurs -- -- If the event has already occured when sampling the resulting behavior, -- we sample not the past, but the current value of the input behavior. snapshot :: Behavior a -> Event () -> Behavior (Event a) -- | Like snapshot, but feeds the result of the event to the value -- of the given behavior at that time. (<@>) :: Behavior (a -> b) -> Event a -> Behavior (Event b) -- | A type class to unifying planNow and planB class Monad b => Plan b plan :: Plan b => Event (b a) -> b (Event a) -- | A type class for behavior-like monads, such Now and the monads -- from Control.FRPNow.BehaviorEnd class Monad n => Sample n sample :: Sample n => Behavior a -> n a -- | A debug function, prints all values of the behavior to stderr, -- prepended with the given string. traceChanges :: (Eq a, Show a) => String -> Behavior a -> Now () instance Control.FRPNow.Lib.Plan Control.FRPNow.Core.Now instance Control.FRPNow.Lib.Plan Control.FRPNow.Core.Behavior instance Control.FRPNow.Lib.Sample Control.FRPNow.Core.Behavior instance Control.FRPNow.Lib.Sample Control.FRPNow.Core.Now -- | Event streams for FRPNow module Control.FRPNow.EvStream -- | The (abstract) type of event streams. -- -- Denotationally, one can think of an eventstream a value of type -- --
--   [(Time,a)]
--   
-- -- Where the points in time are non-strictly increasing. There can be -- multiple simulatinous events in an event stream. data EvStream a -- | Obtain the next element of the event stream. The obtained event is -- guaranteed to lie in the future. next :: EvStream a -> Behavior (Event a) -- | Obtain all simultaneous next elements of the event stream. The -- obtained event is guaranteed to lie in the future. nextAll :: EvStream a -> Behavior (Event [a]) -- | The empty event stream emptyEs :: EvStream a -- | Merge two event stream. -- -- In case of simultaneity, the left elements come first merge :: EvStream a -> EvStream a -> EvStream a -- | Collapses each set simultanious events into a single event carrying -- the list of occurances. collapseSimul :: EvStream a -> EvStream [a] dropEv :: Int -> EvStream a -> EvStream a -- | Get the event stream of changes to the input behavior. toChanges :: Eq a => Behavior a -> EvStream a -- | Get the events that the behavior changes from False to -- True edges :: Behavior Bool -> EvStream () -- | Turns an event of an event stream into an event stream. joinEs :: Event (EvStream b) -> EvStream b -- | A left scan over an event stream scanlEv :: (a -> b -> a) -> a -> EvStream b -> Behavior (EvStream a) -- | Right fold over an eventstream -- -- The result of folding over the rest of the event stream is in an -- event, since it can be only known in the future. -- -- No initial value needs to be given, since the initial value is -- never foldrEv :: (a -> Event b -> b) -> EvStream a -> Behavior (Event b) -- | Right fold over an eventstream with a left initial value -- -- Defined as: -- --
--   foldriEv i f ev =  f i <$> foldrEv f es
--   
foldriEv :: a -> (a -> Event b -> b) -> EvStream a -> Behavior b -- | Create a behavior from an initial value and a event stream of updates. fromChanges :: a -> EvStream a -> Behavior (Behavior a) -- | Start with the argument behavior, and switch to a new behavior each -- time an event in the event stream occurs. -- -- Defined as: -- --
--   foldrSwitch b = foldriEv b switch
--   
foldrSwitch :: Behavior a -> EvStream (Behavior a) -> Behavior (Behavior a) -- | Left fold over an eventstream to create a behavior (behavior depends -- on when the fold started). foldEs :: (a -> b -> a) -> a -> EvStream b -> Behavior (Behavior a) -- | Yet another type of fold. -- -- Defined as: -- --
--   foldBs b f es = scanlEv f b es >>= foldrSwitch b
--   
foldBs :: Behavior a -> (Behavior a -> b -> Behavior a) -> EvStream b -> Behavior (Behavior a) -- | Filter the Just values from an event stream. catMaybesEs :: EvStream (Maybe a) -> EvStream a -- | Filter events from an event stream filterEs :: (a -> Bool) -> EvStream a -> EvStream a -- | Shorthand for -- --
--   filterMapEs f e = catMaybesEs $ f <$> e
--   
filterMapEs :: (a -> Maybe b) -> EvStream a -> EvStream b -- | Shorthand for -- --
--   filterMapEs b e = catMaybesEs $ b <@@> e
--   
filterMapEsB :: Behavior (a -> Maybe b) -> EvStream a -> EvStream b -- | Filter events from an eventstream based on a function that changes -- over time filterB :: Behavior (a -> Bool) -> EvStream a -> EvStream a -- | Obtain only the events from input stream that occur while the input -- behavior is True during :: EvStream a -> Behavior Bool -> EvStream a -- | An event stream with only elements that occur before the argument -- event. beforeEs :: EvStream a -> Event () -> EvStream a -- | Sample the behavior each time an event in the stream occurs, and -- combine the outcomes. (<@@>) :: Behavior (a -> b) -> EvStream a -> EvStream b -- | Sample the behavior each time an event in the stream occurs. snapshots :: Behavior a -> EvStream () -> EvStream a -- | Delay a behavior by one tick of the `clock'. -- -- The event stream functions as the `clock': the input behavior -- is sampled on each event, and the current value of the output behavior -- is always the previously sample. -- -- Occasionally useful to prevent immediate feedback loops. delay :: EvStream x -> a -> Behavior a -> Behavior (Behavior a) -- | Create an event stream that has an event each time the returned -- function is called. The function can be called from any thread. callbackStream :: Now (EvStream a, a -> IO ()) -- | Call the given function each time an event occurs, and execute the -- resulting Now computation callStream :: ([a] -> Now ()) -> EvStream a -> Now () -- | Execute the given IO action each time an event occurs. The IO action -- is executed on the main thread, so it should not take a long time. callIOStream :: (a -> IO ()) -> EvStream a -> Now () -- | Debug function, print all values in the event stream to stderr, -- prepended with the given string. traceEs :: (Show a, Eq a) => String -> EvStream a -> Now () instance GHC.Base.Functor Control.FRPNow.EvStream.EvStream instance GHC.Base.Monoid (Control.FRPNow.EvStream.EvStream a) -- | Various utility functions for FRPNow related to the passing of time. -- All take a "clock" as an argument, i.e. a behavior that gives the -- seconds since the program started. -- -- The clock itself is created by a function specialized to the GUI -- library you are using FRP with such as getClock module Control.FRPNow.Time -- | When sampled at time t, gives the time since time t localTime :: (Floating time, Ord time) => Behavior time -> Behavior (Behavior time) -- | Gives a behavior that linearly increases from 0 to 1 in the specified -- duration timeFrac :: (Floating time, Ord time) => Behavior time -> time -> Behavior (Behavior time) -- | Gives a behavior containing the values of the events in the stream -- that occured in the last n seconds lastInputs :: (Floating time, Ord time) => Behavior time -> time -> EvStream a -> Behavior (Behavior [a]) -- | Gives a behavior containing the values of the behavior during the last -- n seconds, with time stamps bufferBehavior :: (Floating time, Ord time) => Behavior time -> time -> Behavior a -> Behavior (Behavior [(time, a)]) -- | Give a version of the behavior delayed by n seconds delayBy :: (Floating time, Ord time) => Behavior time -> time -> Behavior a -> Behavior (Behavior a) -- | Give n delayed versions of the behavior, each with the given duration -- in delay between them. delayByN :: (Floating time, Ord time) => Behavior time -> time -> Integer -> Behavior a -> Behavior (Behavior [a]) -- | Delay a behavior by one tick of the clock. Occasionally useful to -- prevent immediate feedback loops. Like delay, but uses the -- changes of the clock as an event stream. delayTime :: Eq time => Behavior time -> a -> Behavior a -> Behavior (Behavior a) -- | Integration using rectangle rule approximation. Integration depends on -- when we start integrating so the result is Behavior (Behavior -- v). integrate :: (VectorSpace v time) => Behavior time -> Behavior v -> Behavior (Behavior v) -- | A type class for vector spaces. Stolen from Yampa. Thanks Henrik :) class (Eq a, Eq v, Ord v, Ord a, Floating a) => VectorSpace v a | v -> a where v ^/ a = (1 / a) *^ v negateVector v = (- 1) *^ v v1 ^-^ v2 = v1 ^+^ negateVector v2 norm v = sqrt (v `dot` v) normalize v = if nv /= 0 then v ^/ nv else error "normalize: zero vector" where nv = norm v zeroVector :: VectorSpace v a => v (*^) :: VectorSpace v a => a -> v -> v (^/) :: VectorSpace v a => v -> a -> v negateVector :: VectorSpace v a => v -> v (^+^) :: VectorSpace v a => v -> v -> v (^-^) :: VectorSpace v a => v -> v -> v dot :: VectorSpace v a => v -> v -> a norm :: VectorSpace v a => v -> a normalize :: VectorSpace v a => v -> v instance GHC.Classes.Eq t => GHC.Classes.Eq (Control.FRPNow.Time.TimeTag t a) instance Control.FRPNow.Time.VectorSpace GHC.Types.Float GHC.Types.Float instance Control.FRPNow.Time.VectorSpace GHC.Types.Double GHC.Types.Double instance (GHC.Classes.Eq a, GHC.Float.Floating a, GHC.Classes.Ord a) => Control.FRPNow.Time.VectorSpace (a, a) a instance (GHC.Classes.Eq a, GHC.Float.Floating a, GHC.Classes.Ord a) => Control.FRPNow.Time.VectorSpace (a, a, a) a instance (GHC.Classes.Eq a, GHC.Float.Floating a, GHC.Classes.Ord a) => Control.FRPNow.Time.VectorSpace (a, a, a, a) a instance (GHC.Classes.Eq a, GHC.Float.Floating a, GHC.Classes.Ord a) => Control.FRPNow.Time.VectorSpace (a, a, a, a, a) a -- | The until abstraction, and related definitions. -- -- A value of type BehaviorEnd is a behavior and an ending -- event. This also forms a monad, such that we can write -- --
--   do a1 `Until` e1
--      b1 `Until` e2
--   
-- -- for behaviors consisting of multiple phases. This concept is similar -- to "Monadic FRP" (Haskell symposium 2013, van der Ploeg) and the Task -- monad abstraction (Lambda in motion: Controlling robots with haskell, -- Peterson, Hudak and Elliot, PADL 1999) module Control.FRPNow.BehaviorEnd data BehaviorEnd x a Until :: Behavior x -> Event a -> BehaviorEnd x a [behavior] :: BehaviorEnd x a -> Behavior x [end] :: BehaviorEnd x a -> Event a -- | Combine the behavior of the Until and the other behavior -- until the with the given function until the end event happens. combineUntil :: (a -> b -> b) -> BehaviorEnd a x -> Behavior b -> Behavior b -- | Add the values in the behavior of the Until to the front of -- the list until the end event happsens. (.:) :: BehaviorEnd a x -> Behavior [a] -> Behavior [a] -- | Given an eventstream that spawns behaviors with an end, returns a -- behavior with list of the values of currently active behavior ends. parList :: EvStream (BehaviorEnd b ()) -> Behavior (Behavior [b]) -- | Like Until, but the event can now be generated by a behavior -- (Behavior (Event a)) or even (Now (Event a)). -- -- Name is not "until" to prevent a clash with until. till :: Swap b (BehaviorEnd x) => Behavior x -> b (Event a) -> (b :. BehaviorEnd x) a -- | Composition of functors. newtype (:.) f g x Close :: f (g x) -> (:.) f g x [open] :: (:.) f g x -> f (g x) class (Monad f, Monad g) => Swap f g -- | Swap the composition of two monads. Laws (from Composing Monads, Jones -- and Duponcheel) -- --
--   swap . fmap (fmap f) == fmap (fmap f) . swap
--   swap . return        == fmap unit
--   swap . fmap return   == return
--   prod . fmap dorp     == dorp . prod 
--              where prod = fmap join . swap
--                    dorp = join . fmap swap
--   
swap :: Swap f g => g (f a) -> f (g a) -- | Lift a value from the left monad into the composite monad. liftLeft :: (Monad f, Monad g) => f x -> (f :. g) x -- | Lift a value from the right monad into the composite monad. liftRight :: Monad f => g x -> (f :. g) x instance GHC.Base.Monad (Control.FRPNow.BehaviorEnd.BehaviorEnd x) instance GHC.Base.Functor (Control.FRPNow.BehaviorEnd.BehaviorEnd x) instance GHC.Base.Applicative (Control.FRPNow.BehaviorEnd.BehaviorEnd x) instance (Control.FRPNow.BehaviorEnd.Swap b e, Control.FRPNow.Lib.Sample b) => Control.FRPNow.Lib.Sample (b Control.FRPNow.BehaviorEnd.:. e) instance (GHC.Base.Functor a, GHC.Base.Functor b) => GHC.Base.Functor (a Control.FRPNow.BehaviorEnd.:. b) instance Control.FRPNow.Lib.Plan b => Control.FRPNow.BehaviorEnd.Swap b Control.FRPNow.Core.Event instance (GHC.Base.Monad b, Control.FRPNow.Lib.Plan b) => Control.FRPNow.BehaviorEnd.Swap b (Control.FRPNow.BehaviorEnd.BehaviorEnd x) instance Control.FRPNow.BehaviorEnd.Swap f g => GHC.Base.Monad (f Control.FRPNow.BehaviorEnd.:. g) instance (GHC.Base.Applicative b, GHC.Base.Applicative e) => GHC.Base.Applicative (b Control.FRPNow.BehaviorEnd.:. e) -- | An FRP library with first-class and higher-order behaviors, and -- interalized IO. -- -- Based on the paper Principled Practical FRP: Forget the past, -- Change the future, FRPNow!, ICFP 2015, by Atze van der Ploeg and -- Koenem Claessem. -- -- The packages FRPNow-GTK and FRPNow-Gloss hook up -- FRPNow to GUI toolkits via the functions runNowGTK and -- runNowGloss -- -- To understand what is going on, I suggest you look at the -- examples, and read section 1-5 of the paper. -- -- The package contains the following modules: -- -- module Control.FRPNow