{-# LANGUAGE FlexibleContexts, TypeFamilies #-} {-# OPTIONS -Wall #-} ---------------------------------------------------------------------- -- | -- Module : FRP.Reactive.GLUT.UI -- Copyright : (c) Conal Elliott 2008 -- License : BSD3 -- -- Maintainer : conal@conal.net -- Stability : experimental -- -- Simple UI type. -- -- Based on code from David Sankel. ---------------------------------------------------------------------- module FRP.Reactive.GLUT.UI ( UI(..) , KeyState(..), Key(..), G.SpecialKey(..) , keyPressed , uiIntegral ) where import Control.Applicative (liftA2) import qualified Graphics.UI.GLUT as G import Data.VectorSpace import FRP.Reactive -- | Simple UI type. data UI = UI { mousePosition :: Behavior (Double,Double), leftButtonPressed :: Event (), rightButtonPressed :: Event (), keyAction :: Event (KeyState, Key), framePass :: Event () } -- TODO: make button and key interfaces alike -- | Key pressed data Key = Char Char | SpecialKey G.SpecialKey deriving (Eq, Ord, Show) data KeyState = Down | Up deriving (Eq, Ord, Show) -- | Key press events. keyPressed :: UI -> Event Key keyPressed = fmap snd . filterE ((==Down) . fst) . keyAction -- | Integral tracking frame sampling uiIntegral :: (VectorSpace v, Scalar v ~ TimeT) => (UI -> Behavior v) -> (UI -> Behavior v) uiIntegral = liftA2 integral framePass