2010-02-22 18:27:18 +01:00
|
|
|
{-# LANGUAGE ExistentialQuantification, DeriveDataTypeable #-}
|
2010-02-22 16:50:42 +01:00
|
|
|
|
2010-02-22 18:27:18 +01:00
|
|
|
module GLDriver ( Driver(..)
|
2010-02-23 23:31:11 +01:00
|
|
|
, SomeDriver(..)
|
2010-02-22 16:50:42 +01:00
|
|
|
, Event
|
|
|
|
, SomeEvent(..)
|
2010-02-24 03:40:06 +01:00
|
|
|
, fromEvent
|
2010-02-22 22:25:06 +01:00
|
|
|
, QuitEvent(..)
|
2010-02-24 03:40:06 +01:00
|
|
|
, Key(..)
|
|
|
|
, KeyPressEvent(..)
|
|
|
|
, KeyReleaseEvent(..)
|
2010-03-05 04:38:31 +01:00
|
|
|
, MouseMotionEvent(..)
|
2010-03-08 22:13:35 +01:00
|
|
|
, MousePressEvent(..)
|
2010-02-22 16:50:42 +01:00
|
|
|
) where
|
|
|
|
|
|
|
|
import Data.Typeable
|
|
|
|
|
|
|
|
|
2010-02-22 18:27:18 +01:00
|
|
|
class Driver a where
|
2010-02-22 16:50:42 +01:00
|
|
|
initialized :: a -> Bool
|
|
|
|
|
|
|
|
initGL :: a -> IO a
|
|
|
|
deinitGL :: a -> IO ()
|
|
|
|
|
2010-02-23 15:05:31 +01:00
|
|
|
swapBuffers :: a -> IO ()
|
|
|
|
|
2010-03-05 04:38:31 +01:00
|
|
|
nextEvent :: a -> IO (a, Maybe SomeEvent)
|
2010-02-22 16:50:42 +01:00
|
|
|
|
2010-02-23 23:31:11 +01:00
|
|
|
data SomeDriver = forall d. Driver d => SomeDriver d
|
|
|
|
|
|
|
|
instance Driver SomeDriver where
|
|
|
|
initialized (SomeDriver d) = initialized d
|
|
|
|
initGL (SomeDriver d) = initGL d >>= return . SomeDriver
|
|
|
|
deinitGL (SomeDriver d) = deinitGL d
|
|
|
|
swapBuffers (SomeDriver d) = swapBuffers d
|
2010-03-05 04:38:31 +01:00
|
|
|
nextEvent (SomeDriver d) = nextEvent d >>= \(gl, ev) -> return (SomeDriver gl, ev)
|
2010-02-23 23:31:11 +01:00
|
|
|
|
2010-02-22 16:50:42 +01:00
|
|
|
|
2010-03-02 06:10:34 +01:00
|
|
|
class (Typeable a, Show a) => Event a
|
2010-02-22 16:50:42 +01:00
|
|
|
|
|
|
|
data SomeEvent = forall a. Event a => SomeEvent a
|
2010-03-02 06:10:34 +01:00
|
|
|
instance Show SomeEvent where
|
|
|
|
show (SomeEvent a) = show a
|
2010-02-22 16:50:42 +01:00
|
|
|
|
|
|
|
fromEvent :: Event a => SomeEvent -> Maybe a
|
|
|
|
fromEvent (SomeEvent a) = cast a
|
2010-02-22 18:27:18 +01:00
|
|
|
|
|
|
|
|
2010-03-02 06:10:34 +01:00
|
|
|
data QuitEvent = QuitEvent deriving (Typeable, Show)
|
2010-02-23 20:51:30 +01:00
|
|
|
instance Event QuitEvent
|
2010-02-22 18:27:18 +01:00
|
|
|
|
2010-02-24 03:40:06 +01:00
|
|
|
|
|
|
|
data Key = KeyLeft | KeyRight | KeyUp | KeyDown
|
|
|
|
deriving (Eq, Ord, Show)
|
|
|
|
|
2010-03-02 06:10:34 +01:00
|
|
|
data KeyPressEvent = KeyPressEvent Key deriving (Typeable, Show)
|
2010-02-24 03:40:06 +01:00
|
|
|
instance Event KeyPressEvent
|
|
|
|
|
2010-03-02 06:10:34 +01:00
|
|
|
data KeyReleaseEvent = KeyReleaseEvent Key deriving (Typeable, Show)
|
2010-02-24 03:40:06 +01:00
|
|
|
instance Event KeyReleaseEvent
|
2010-03-05 04:38:31 +01:00
|
|
|
|
|
|
|
|
|
|
|
data MouseMotionEvent = MouseMotionEvent Float Float deriving (Typeable, Show)
|
2010-03-08 22:13:35 +01:00
|
|
|
instance Event MouseMotionEvent
|
|
|
|
|
|
|
|
data MousePressEvent = MousePressEvent Float Float deriving (Typeable, Show)
|
|
|
|
instance Event MousePressEvent
|