{-# OPTIONS_GHC -Wall #-}
----------------------------------------------------------------------
-- |
-- Module      :  FRP.Reactive.FieldTrip.Adapter
-- Copyright   :  (c) Conal Elliott 2008
-- License     :  BSD3
-- 
-- Maintainer  :  conal@conal.net
-- Stability   :  experimental
-- 
-- Simple Reactive/FieldTrip adapter
----------------------------------------------------------------------

module FRP.Reactive.FieldTrip.Adapter
  ( Anim, Anim2, Anim3
  , anim2, anim3
  ) where

import Graphics.FieldTrip
import FRP.Reactive
import FRP.Reactive.GLUT.Adapter

-- | Simple viewing transformation.  Just moves geometry away from the user.
view :: Filter3
view = move3Z (-3 :: R)

-- | Interactive animation
type Anim a = UI -> Behavior a

-- | Interactive 2D animation
type Anim2 = Anim Geometry2

-- | Interactive 3D animation
type Anim3 = Anim Geometry3

-- | Present an animation, given a way to render a value.
animate :: Sink a -> Sink (Anim a)
animate f anim = adaptSimple "Reactive + FieldTrip" ((fmap.fmap) f anim)

-- | Present a 2D animation.
anim2 :: Sink Anim2
anim2 = anim3 . (fmap.fmap) flatG

-- | Present a 2D animation.
anim3 :: Sink Anim3
anim3 = animate (renderWith3 gc . view)
 where
   gc = defaultGC { gcErr = 0.005 }