Make FPPrac compile against Gtk2Hs instead of WxWidgets.
[matthijs/projects/fpprac.git] / FPPrac.hs
index 628962b09bd7de2b5585f5eaddf8b200d55f5783..61fd9ef9b183f630a1ead0f1a7611880c950aeac 100644 (file)
--- a/FPPrac.hs
+++ b/FPPrac.hs
@@ -1,21 +1,52 @@
 {-# LANGUAGE RecordWildCards, ExistentialQuantification #-}
 module FPPrac (
-       module Graphics.UI.WXCore.WxcTypes,
        Request(..),
        Response(..),
        TinaProgram(..),
+       Color, Rect(..), Point(..),
+       rgb, pt, point,
        runTina
 ) where
 
-import Graphics.UI.WXCore.WxcTypes
-import Graphics.UI.WX hiding (empty)
-import Graphics.UI.WXCore hiding (empty)
+import qualified Graphics.UI.Gtk as Gtk
 import Data.IORef
 import Control.Applicative
 import Control.Monad
 import Char
 import System.Exit
 
+-- | A rectangle in two dimensional space
+data Rect = Rect 
+       { rectLeft :: !Int
+       , rectTop :: !Int
+       , rectWidth :: !Int
+       , rectHeight :: !Int
+} deriving (Show, Eq)
+
+data Point = Point !Int !Int deriving (Show, Eq)
+
+type Color = Gtk.Color
+
+-- Create a Color from Red, Green and Blue values. The inputs should be
+-- between 0 and 255 (inclusive).
+rgb :: Int -> Int -> Int -> Color
+rgb r g b = Gtk.Color (conv r) (conv g) (conv b)
+       where conv = fromInteger . toInteger . (*256)
+
+-- | Some predefined colours
+red = rgb 0xff 0 0
+green = rgb 0 0xff 0
+blue = rgb 0 0 0xff
+white = rgb 0xff 0xff 0xff
+
+-- | Helper functions for creating a Point
+point, pt :: Int -> Int -> Point
+point = Point
+pt = Point
+
+runTina :: TinaProgram -> IO ()
+runTina p = return ()
+
 data Request
        = GfxLines      Color   [Point]                 -- coloured line through a list of points
        | GfxPolygon    Color   [Point]                 -- filled polygon of given colour
@@ -65,14 +96,14 @@ testProg = Main
        }
 
 data IState = forall s. IS
-       { sFrame    :: Frame    ()
+       { {-sFrame    :: Frame    ()
        , sPanel    :: Panel    ()
        , buffer    :: MemoryDC ()
-       , postponed :: IORef [Request]
+       , -}postponed :: IORef [Request]
        , usrState  :: IORef s
        , usrProg   :: TinaStep s
        }
-
+{-
 dbgLog IS {..} s = do
        return ()
 
@@ -218,4 +249,4 @@ grow n Rect {..} = Rect
        , rectWidth  = rectWidth  + 2 * n
        , rectHeight = rectHeight + 2 * n }
 
-
+-}