{-# LANGUAGE FlexibleContexts #-}
{-# 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(..)
  , Key(..), SpecialKey(..)
  , uiIntegral
  ) where

import Control.Applicative (liftA2)
import Graphics.UI.GLUT(SpecialKey(..))

import Data.VectorSpace
import FRP.Reactive

-- | Simple UI type.
data UI = UI {
  mousePosition     :: Behavior (Double,Double),
  leftMousePressed  :: Event (),
  rightMousePressed :: Event (),
  keyPressed        :: Event Key,
  framePass         :: Event ()
}

-- | Key pressed
data Key = Char Char | SpecialKey SpecialKey

-- | Integral tracking frame sampling
uiIntegral :: VectorSpace v TimeT =>
              (UI -> Behavior v) -> (UI -> Behavior v)
uiIntegral = liftA2 integral framePass