[reactive] reactive-glut keyAction problem

stefan kersten sk at k-hornz.de
Thu Feb 12 06:09:39 EST 2009


hi all,

i'm having a problem with key events in reactive-glut:

import FRP.Reactive
import FRP.Reactive.LegacyAdapters
import FRP.Reactive.GLUT.Adapter

keyDown :: Event (KeyState, Key) -> Event Key
keyDown = fmap snd . filterE ((==Down) . fst)

keyUp :: Event (KeyState, Key) -> Event Key
keyUp = fmap snd . filterE ((==Up) . fst)

partitionE :: (Show a) => (a -> Bool) -> Event a -> (Event a, Event a)
partitionE p e = (filterE p e, filterE (not . p) e)

key :: Key -> Event (KeyState, Key) -> (Event (KeyState, Key), Event 
(KeyState, Key))
key k = partitionE ((==k) . snd)

keyB :: Event (KeyState, Key) -> Behavior Bool
keyB k = flipFlop (keyDown k) (keyUp k)

mainB :: UI -> Behavior Action
mainB ui = return () `stepper` (print `fmap` e)
     where
         (k1, k) = key (Char '1') (keyAction ui)
         e       = snapshot (keyB k1) k

main :: IO ()
main = adaptSimple "Testfest" mainB

on my system (osx 10.5, reactive-0.10.5, reactive-glut-0.1.6) nothing is 
printed until i press '1' a few times, then it gets stuck again. what 
i'd expect to happen is ((KeyState, Key), Bool) to be printed everytime 
i press a key different from '1', where the second tuple element is True 
as long as '1' is being held.

what am i missing? is this related to the laziness bug mentioned earlier?

many thanks,
<sk>



More information about the Reactive mailing list