Inputs to classic FRP: unsafeInterleaveIO/unsafePerformIO

As far as I can tell, with classic FRP implementations (those which use behaviors as a first-class abstraction), the only way to create a behavior or event based on some external input (for instance keypresses or microphone input) is to do something with unsafePerformIO or unsafeInterleaveIO. A behavior is a value, which when evaluated at a specific time would have to either block its evaluation until input could be read, or check the input at that particular time. Is there any other way of implementing external behaviors besides that? -- Edward Amsden Student Computer Science Rochester Institute of Technology www.edwardamsden.com

Of course, you could have the 'interpretation' function be non-pure.
For example:
-- Library functions for a hypothetical FRP system
pollEvent :: IO [a] -> Event a
behavior :: a -> Event a -> Behavior a
accumB :: b -> (b -> a -> b) -> Event a -> Behavior b
accumE :: b -> (b -> a -> b) -> Event a -> Event b
union :: Event a -> Event a -> Event a
runFRP :: (a -> IO Bool) -> Behavior a -> IO ()
-- Event & Behavior become instances of Functor & Applicative
-- and now a hypothetical implementation
data Event a where
Event :: s -- initial state
-> (s -> IO ([a], s)) -- tick
-> Event a
data Behavior a = Behavior a (Event a)
pollEvent act = Event () $ \() -> do
xs <- act
return (xs, ())
behavior = Behavior
union (Event sL0 tickL) (Event sR0 tickR) = Event (sL0,sR0) tick where
tick (sL, sR) = do
(ls, sL') <- tickL sL
(rs, sR') <- tickR sR
return (ls ++ rs, (sL', sR'))
accumB b0 f e = Behavior b0 $ accumE b f e
accumE b0 f (Event s0 tickE) = Event (b0, s0) tick where
tick (b, s) = do
(as, s') <- tickE s
let bs = scanl f b as
return (bs, (last bs, s'))
-- Functor, Applicative instances are pretty easy and left as an exercise
runFRP tick (Behavior b0 (Event s0 e)) = runFRP' b0 s0 where
runFRP' b s = do
(bs, s') <- e s0
let val = last (b:bs)
k <- tick b
when k $ runFRP tick (Behavior
k <- tick b
-- sample application
keypress :: Event Char
keypress = pollEvent getCurrentPressedKeys where
getCurrentPressedKeys = undefined -- exercise for the reader
On Mon, Apr 25, 2011 at 5:28 PM, Edward Amsden
As far as I can tell, with classic FRP implementations (those which use behaviors as a first-class abstraction), the only way to create a behavior or event based on some external input (for instance keypresses or microphone input) is to do something with unsafePerformIO or unsafeInterleaveIO. A behavior is a value, which when evaluated at a specific time would have to either block its evaluation until input could be read, or check the input at that particular time.
Is there any other way of implementing external behaviors besides that?
-- Edward Amsden Student Computer Science Rochester Institute of Technology www.edwardamsden.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Mail fail, haha. Code fixed. For example: -- Library functions for a hypothetical FRP system pollEvent :: IO [a] -> Event a behavior :: a -> Event a -> Behavior a accumB :: b -> (b -> a -> b) -> Event a -> Behavior b accumE :: b -> (b -> a -> b) -> Event a -> Event b union :: Event a -> Event a -> Event a runFRP :: (a -> IO Bool) -> Behavior a -> IO () -- Event & Behavior become instances of Functor & Applicative -- and now a hypothetical implementation data Event a where Event :: s -- initial state -> (s -> IO ([a], s)) -- tick -> Event a data Behavior a = Behavior a (Event a) pollEvent act = Event () $ \() -> do xs <- act return (xs, ()) behavior = Behavior union (Event sL0 tickL) (Event sR0 tickR) = Event (sL0,sR0) tick where tick (sL, sR) = do (ls, sL') <- tickL sL (rs, sR') <- tickR sR return (ls ++ rs, (sL', sR')) accumB b0 f e = Behavior b0 $ accumE b f e accumE b0 f (Event s0 tickE) = Event (b0, s0) tick where tick (b, s) = do (as, s') <- tickE s let bs = scanl f b as return (bs, (last bs, s')) -- Functor, Applicative instances are pretty easy and left as an exercise runFRP tick (Behavior b0 (Event s0 e)) = runFRP' b0 s0 where runFRP' b s = do (bs, s') <- e s0 let b' = last (b:bs) k <- tick b' when k $ runFRP' b' s' -- sample application keypress :: Event Char keypress = pollEvent getCurrentPressedKeys where getCurrentPressedKeys = undefined -- exercise for the reader -- application prints the last key you pressed until you press 'q' main = runFRP tick keypress where tick k = print k >> return (k /= 'q')

Edward Amsden wrote:
As far as I can tell, with classic FRP implementations (those which use behaviors as a first-class abstraction), the only way to create a behavior or event based on some external input (for instance keypresses or microphone input) is to do something with unsafePerformIO or unsafeInterleaveIO. A behavior is a value, which when evaluated at a specific time would have to either block its evaluation until input could be read, or check the input at that particular time.
Is there any other way of implementing external behaviors besides that?
Yes, there are other ways, see for example the implementation here: http://tinyurl.com/frp-automaton . This is essentially a pure variant of Ryan's implementation. My implementation has a serious problem, namely that sharing is lost. I think this is the case for Ryan's implementation as well. The state of a behavior will be duplicated and updates multiple times. This can be fixed by observing sharing, of course. I'm currently working on a push-driven FRP implementation. (Though I'm getting second thoughts as to whether the small increase in efficiency is worth the implementation cost.) See also http://apfelmus.nfshost.com/blog/2011/04/24-frp-push-driven-sharing.html Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Apfelmus, I hope you don't abandon your efforts, at least for the selfish reason that I enjoy reading your blog entries about trying to implement it! I was looking at your last entry and trying to understand if/how you solve the order-dependency problem for events. In particular: source events e1, e2 e3 = e1 union e2 e4 = e2 union e1 e5 = e3 union e4 The graph from your description would look something like e1 e2 | \-A / \ A-\ e3 e3 e4 e4 | | | | e5 e5 e5 e5 When I was looking at the FRP problem before, it felt a lot like the 'adaptive' problem, so I was looking at Umut Acar's papers and trying to build something along those lines. But perhaps your API is simple enough that you don't need that degree of complexity. -- ryan On Tue, Apr 26, 2011 at 12:29 AM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
Edward Amsden wrote:
As far as I can tell, with classic FRP implementations (those which use behaviors as a first-class abstraction), the only way to create a behavior or event based on some external input (for instance keypresses or microphone input) is to do something with unsafePerformIO or unsafeInterleaveIO. A behavior is a value, which when evaluated at a specific time would have to either block its evaluation until input could be read, or check the input at that particular time.
Is there any other way of implementing external behaviors besides that?
Yes, there are other ways, see for example the implementation here: http://tinyurl.com/frp-automaton . This is essentially a pure variant of Ryan's implementation.
My implementation has a serious problem, namely that sharing is lost. I think this is the case for Ryan's implementation as well. The state of a behavior will be duplicated and updates multiple times. This can be fixed by observing sharing, of course.
I'm currently working on a push-driven FRP implementation. (Though I'm getting second thoughts as to whether the small increase in efficiency is worth the implementation cost.) See also
http://apfelmus.nfshost.com/blog/2011/04/24-frp-push-driven-sharing.html
Best regards, Heinrich Apfelmus
-- http://apfelmus.nfshost.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ryan Ingram wrote:
Apfelmus, I hope you don't abandon your efforts, at least for the selfish reason that I enjoy reading your blog entries about trying to implement it!
:D My reasoning was that a temporary demand-driven implementation would allow me to release the library sooner; I want people to start using the library and experiment with FRP. I can always add the push-driven implementation later. However, even in a demand-driven implementation, there is one optimization that I would like make: when there are multiple external events, say e1 and e2, the network splits into subnetworks that react only to one of the inputs. For instance, your example would split into two graphs e1 e2 | \ | \ e3 e4 and e3 e4 | | | | e5 e5 e5 e5 that are independent of each other. Unlike successful filters, these subnetworks are known *statically* and it's worth splitting them out. That said, it appears to me that this optimization is quite tricky even in a demand-driven setting! I can as well stick to the push-driven implementation I have already started.
I was looking at your last entry and trying to understand if/how you solve the order-dependency problem for events. In particular:
source events e1, e2
e3 = e1 union e2 e4 = e2 union e1
e5 = e3 union e4
The graph from your description would look something like
e1 e2 | \-A / \ A-\ e3 e3 e4 e4 | | | | e5 e5 e5 e5
When I was looking at the FRP problem before, it felt a lot like the 'adaptive' problem, so I was looking at Umut Acar's papers and trying to build something along those lines. But perhaps your API is simple enough that you don't need that degree of complexity.
Thanks, I'll have a look at his work. It's really very similar to some kind of adaptive computation. What currently irks me about my push-driven implementation is that it is ad-hoc. I would really like to start from a demand-driven implementation and systematically transform it into a push-driven one. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Tue, Apr 26, 2011 at 11:44 PM, Heinrich Apfelmus < apfelmus@quantentunnel.de> wrote:
However, even in a demand-driven implementation, there is one optimization that I would like make: when there are multiple external events, say e1 and e2, the network splits into subnetworks that react only to one of the inputs. For instance, your example would split into two graphs
e1 e2 | \ | \ e3 e4 and e3 e4 | | | | e5 e5 e5 e5
that are independent of each other. Unlike successful filters, these subnetworks are known *statically* and it's worth splitting them out.
Yeah, I realize that as well, although you can get the same problem with a single source, it just makes the network a bit more complicated: e0 = source e1 = fromLeft <$> filter isLeft e1 e2 = fromRight <$> filter isRight e1 -- rest of network the same Anyways, the problem I was getting at is that lets say that e1 and e2 are both Event Bool, and e1 has a True event at the same time that e2 has a False event. Then a behavior derived from e3 is False for that time (assuming behaviors take the 'last' event in the list?), and a behavior from e4 is True for that time. -- ryan

Ryan Ingram wrote:
Heinrich Apfelmus wrote:
However, even in a demand-driven implementation, there is one optimization that I would like make: when there are multiple external events, say e1 and e2, the network splits into subnetworks that react only to one of the inputs. For instance, your example would split into two graphs
e1 e2 | \ | \ e3 e4 and e3 e4 | | | | e5 e5 e5 e5
that are independent of each other. Unlike successful filters, these subnetworks are known *statically* and it's worth splitting them out.
Yeah, I realize that as well, although you can get the same problem with a single source, it just makes the network a bit more complicated:
e0 = source e1 = fromLeft <$> filter isLeft e1 e2 = fromRight <$> filter isRight e1 -- rest of network the same
Anyways, the problem I was getting at is that lets say that e1 and e2 are both Event Bool, and e1 has a True event at the same time that e2 has a False event.
Then a behavior derived from e3 is False for that time (assuming behaviors take the 'last' event in the list?), and a behavior from e4 is True for that time.
Yep, that's precisely what will happen. Internally, the four "pillars" in the graph e1 e2 | \-A | \ A-\ e3 e3 e4 e4 | | | | e5 e5 e5 e5 1 2 3 4 -- pillar will simply be executed from left to right (in particular not in depth-first search order). The edge connecting e1 and e4 signifies that the value of e1 will be cached when the first pillar is executed, so that it is available again a few pillars later when it's time for the fourth pillar. Concerning the behaviors, also note that a behaviors change "slightly" later than the events from which they are derived. Semantically, we have stepper x ex = \time -> last $ x : [y | (time', y) <- ex, time' < time] In particular, the strict comparison < means that the behavior still has the previous value when the event happens. So, indeed, a behavior derived from e3 will pick up the last False while a behavior derived from e4 will pick up the last True. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (3)
-
Edward Amsden
-
Heinrich Apfelmus
-
Ryan Ingram