7e5a6914225519e0d3056b50344467794f405091
[matthijs/projects/fpprac.git] / FPPrac.hs
1 {-# LANGUAGE RecordWildCards, ExistentialQuantification #-}
2 module FPPrac (
3         Request(..),
4         Response(..),
5         TinaProgram(..),
6         Color, Rect(..), Point(..),
7         rgb, pt, point,
8         runTina
9 ) where
10
11 import qualified Graphics.UI.Gtk as Gtk
12 import Graphics.UI.Gtk (AttrOp(..)) -- For the := constructor
13 import qualified Graphics.Rendering.Cairo as Cairo
14 import qualified Graphics.UI.Gtk.Gdk.EventM as EventM
15
16 import Control.Monad.Trans -- for liftIO
17 import Data.IORef
18 import Control.Applicative
19 import Control.Monad
20 import Char
21 import System.Exit
22
23 -- | A rectangle in two dimensional space
24 data Rect = Rect 
25         { rectLeft :: !Int
26         , rectTop :: !Int
27         , rectWidth :: !Int
28         , rectHeight :: !Int
29 } deriving (Show, Eq)
30
31 data Point = Point !Int !Int deriving (Show, Eq)
32
33 -- A color, with RGB values from 0 to 1
34 data Color = Color Double Double Double deriving (Show, Eq)
35
36 -- Create a Color from Red, Green and Blue values. The inputs should be
37 -- between 0 and 255 (inclusive).
38 rgb :: Int -> Int -> Int -> Color
39 rgb r g b = Color (conv r) (conv g) (conv b)
40         where conv = (/256) . fromIntegral
41
42 -- | Some predefined colours
43 red = rgb 0xff 0 0
44 green = rgb 0 0xff 0
45 blue = rgb 0 0 0xff
46 white = rgb 0xff 0xff 0xff
47
48 -- | Helper functions for creating a Point
49 point, pt :: Int -> Int -> Point
50 point = Point
51 pt = Point
52
53 data Request
54         = GfxLines      Color   [Point]                 -- coloured line through a list of points
55         | GfxPolygon    Color   [Point]                 -- filled polygon of given colour
56         | GfxPicture    FilePath Point                  -- shows a picture
57         | GfxText       Color    Point  String          -- coloured string on position Point
58         | GfxRectangle  Color    Rect                   -- filled rectangle of given colour
59         | GfxEllipse    Color    Rect                   -- ellipse within given rectangle
60         | GfxDisc       Color    Rect                   -- filled ellipse within given rectangle
61         | GfxClear                                      -- clears the graphical window
62         -- | GfxInstance   Bool
63         | GfxFont       String   Int                    -- changes to fontname of given size
64         | WinPrompt     String   String String          -- pops up a window with an edit field
65         -- | WinFilePrompt Bool
66         | WinMenu       [(String,[String])]             -- adds a menu list to the graphical window
67         | WinTitle      String                          -- gives a title to the graphical window
68         | FRead         String                          -- read file with a given name
69         | FWrite        String   String                 -- writes a text file with a given filename
70         | ReqQuit                                       -- quits the graphical system
71         deriving Show
72
73 data Response
74         = KeyIn            Char                         -- touched key with given character
75         | MouseDoubleClick Point                        -- mouse event on position Point
76         | MouseDragged     Point                        -- ibid
77         | MouseDown        Point                        -- ibid
78         | MouseUp          Point                        -- ibid
79         | MenuItem         String String                -- selected item from WinMenu with a given name
80         | PromptResponse   String String String         -- response to WinPrompt request
81         | FileContents     String String                -- response to FRead request
82         deriving Show
83
84 type TinaStep s = s -> Response -> (s,[Request])
85 data TinaProgram = forall s. Main
86         { initialState    :: s
87         , initialRequests :: [Request]
88         , eventHandler    :: TinaStep s
89         , windowWidth
90         , windowHeight    :: Int
91         }
92
93 testProg = Main
94         { initialState    = 1
95         , initialRequests = [GfxText red (pt 0 0) "foo", GfxText blue (pt 100 100) "bar"]
96         , eventHandler    = \s e -> (s+1,[GfxText green (pt 50 50) $ show (s,e)])
97         , windowWidth     = 200
98         , windowHeight    = 200
99         }
100
101 data IState = forall s. IS
102         { window    :: Gtk.Window
103         , buffer    :: IORef Cairo.Surface
104         , postponed :: IORef [Request]
105         , usrState  :: IORef s
106         , usrProg   :: TinaStep s
107         }
108
109 processPostponed :: IState -> IO ()
110 processPostponed s@IS {..} = do
111         ps <- readIORef postponed
112         unless (null ps) $ do
113                 writeIORef postponed (tail ps)
114                 rs  <- handle s (head ps)
115                 mapM (stepUserProgram s) rs
116                 processPostponed s
117
118 post s r = stepUserProgram s r >> processPostponed s
119
120 stepUserProgram :: IState -> Response -> IO ()
121 stepUserProgram IS {..} r = do
122         state <- readIORef usrState
123         let (state',reqs) = usrProg state r
124         writeIORef usrState state'
125         readIORef postponed >>= writeIORef postponed . (++ reqs)
126
127 handle :: IState -> Request -> IO [Response]
128 handle s@IS {..} r = do
129         resps <- maybe (fail $ "No handler for request " ++ show r) id $
130                 fmap (>> return []) (gfxHandler s r <|> winHandler s r <|> miscHandler s r)
131         return resps
132
133 runTina :: TinaProgram -> IO ()
134 runTina Main {..} = do
135         usrState  <- newIORef initialState
136         postponed <- newIORef (GfxText (rgb 0 0 0) (pt 50 50) "foo" : GfxClear :initialRequests)
137         let state = IS { window = undefined, buffer = undefined, usrProg = eventHandler, .. }
138         runGUI windowWidth windowHeight state
139
140 runGUI :: Int -> Int -> IState -> IO ()
141 runGUI w h (IS { .. }) = do
142         -- Init GTK.
143         Gtk.initGUI
144         
145         -- Create a window, which will make the mainloop terminated when
146         -- it is closed.
147         window <- Gtk.windowNew
148                 
149         Gtk.set window [ Gtk.containerBorderWidth := 10
150                        , Gtk.windowTitle := "FP Practicum" 
151                        , Gtk.windowDefaultWidth := w
152                        , Gtk.windowDefaultHeight := h
153                        ]
154         Gtk.onDestroy window Gtk.mainQuit
155         
156         -- Create a buffer to draw on (name the actual buffer buffer', so we
157         -- can use IS { .. } syntax below to pack the state. Using a record update
158         -- wouldn't work, probably because Cairo.Surface contains an existential
159         -- type...
160         -- We put the buffer in an IORef, so we can change it for a new one
161         -- later on (on window resizes).
162         buffer' <- Cairo.createImageSurface Cairo.FormatARGB32 w h
163         buffer <- newIORef buffer'
164
165         -- Register events
166         Gtk.on window Gtk.exposeEvent $ onExpose buffer
167         Gtk.on window Gtk.configureEvent $ onResize buffer
168
169         -- Repack state
170         let state = IS { .. }
171         
172         -- Process any initial requests
173         processPostponed state
174
175         -- Show the window and start the Gtk mainloop.
176         Gtk.widgetShowAll window
177         Gtk.mainGUI
178         
179
180 -- | Copy the given surface to the exposed window on an expose event.
181 onExpose :: IORef Cairo.Surface -> EventM.EventM EventM.EExpose Bool
182 onExpose buffer = do
183         current_buffer <- liftIO $ readIORef buffer
184         dw <- EventM.eventWindow
185         -- Copy the buffer to the window
186         liftIO $ Gtk.renderWithDrawable dw $ do
187                 Cairo.setSourceSurface current_buffer 0 0
188                 Cairo.paint
189         return True -- No clue what this means
190
191 -- | Called when the window is resized. Resize the given buffer if needed.
192 onResize :: IORef Cairo.Surface -> EventM.EventM EventM.EConfigure Bool
193 onResize buffer = do
194         -- Get the current buffer and see if it's still big enough
195         current_buffer <- liftIO $ readIORef buffer
196         sw <- Cairo.imageSurfaceGetWidth current_buffer
197         sh <- Cairo.imageSurfaceGetHeight current_buffer
198         -- Get the current drawwindow and its size
199         dw <- EventM.eventWindow
200         (w, h) <- liftIO $ Gtk.drawableGetSize dw
201         when (w > sw || h > sh) $ liftIO $ do
202                 -- Buffer is too small, expand it.
203                 new_buffer <- Cairo.createImageSurface Cairo.FormatARGB32 w h
204                 -- Fill it with white and copy the old buffer
205                 Cairo.renderWith new_buffer $ do
206                         Cairo.setSourceRGB 1 1 1
207                         Cairo.paint
208                         Cairo.setSourceSurface current_buffer 0 0
209                         Cairo.paint
210                 -- Clean up the old buffer
211                 Cairo.surfaceFinish current_buffer
212                 -- Store and return the new buffer
213                 writeIORef buffer new_buffer
214         return True -- No clue what this means
215                                 
216
217 {-
218 runGUI s IS {..} = do
219         sFrame <- frame
220                 [ text       := "FP Practicum"
221                 , size       := s
222                 ]
223         buffer <- memoryDCCreate
224         bitmapCreateEmpty s 24 >>= memoryDCSelectObject buffer
225         withBrushStyle (BrushStyle BrushSolid white) (dcSetBackground buffer)
226         dcClear buffer
227         buffer `set`
228                 [ fontFace   := "Courier New"
229                 , fontSize   := 10
230                 , brushColor := rgb 0 0 0
231                 , brushKind  := BrushSolid
232                 , penColor   := rgb 0 0 0
233                 , penKind    := PenSolid
234                 ]
235         sPanel <- panel sFrame [ size := s ]
236         let state = IS {..}
237         sPanel `set`
238                 [ on paint       := onPaint state
239                 , on doubleClick := post state . MouseDoubleClick
240                 , on click       := post state . MouseDown
241                 , on drag        := post state . MouseDragged
242                 , on unclick     := post state . MouseUp
243                 , on anyKey      := transKey (post state . KeyIn)
244                 ]
245         sFrame `set`
246                 [ on closing := sFrame `set` [ visible := False ] >> wxcAppExit
247                 , on anyKey  := transKey (post state . KeyIn)
248                 , layout     := widget sPanel
249                 ]
250         windowSetFocus sFrame
251         processPostponed state
252 onPaint :: IState -> DC a -> Rect -> IO ()
253 onPaint IS {..} dest va = do
254         dcBlit dest va buffer (Point 0 0) wxCOPY False >> return ()
255
256 transKey :: (Char -> IO ()) -> Key -> IO ()
257 transKey prod (KeyChar c) = prod c
258 transKey prod  KeySpace   = prod ' '
259 transKey prod  KeyEscape  = prod '\ESC'
260 transKey prod  KeyReturn  = prod '\n'
261 transKey prod  KeyTab     = prod '\t'
262 transKey _ _ = return ()
263
264 -}
265
266 -- | Handlers for various requests.
267 miscHandler, winHandler, gfxHandler :: IState -> Request -> Maybe (IO ())
268 {-
269 miscHandler s@IS {..} (FRead  fn     ) = Just $ readFile fn >>= post s . FileContents fn
270 miscHandler   IS {..} (FWrite fn cnts) = Just $ writeFile fn cnts
271 miscHandler   IS {..} ReqQuit = Just $ putStrLn "Quiting" >> wxcAppExit
272 -}
273 miscHandler   IS {..} _ = Nothing
274
275 {-
276 winHandler s@IS {..} (WinPrompt st1 st2 st3) = Just $ textDialog sFrame st1 st2 st3 >>= post s . PromptResponse st1 st2
277 winHandler   IS {..} (WinTitle     st) = Just $ sFrame `set` [text := st]
278 winHandler s@IS {..} (WinMenu      ms) = Just $ mkMenu >>= \ms' -> sFrame `set` [menuBar := ms']
279         where
280         mkMenu = sequence
281                 [ do
282                         p  <- menuPane [ text := name ]
283                         sequence
284                                 [ do
285                                         i <- menuItem p [ text := item ]
286                                         sFrame `set` [on (menu i) := post s (MenuItem name item)]
287                                  | item <- items ]
288                         return p
289                  | (name,items) <- ms ]
290 -}
291 winHandler _        _                = Nothing
292
293 gfxHandler s req = case gfxHandler' req of
294         Nothing -> Nothing
295         Just render -> Just $ do
296                 buf <- readIORef (buffer s)
297                 Cairo.renderWith buf render
298                 Gtk.widgetQueueDraw (window s)
299                 
300 {-
301 gfxHandler IS {..} (GfxLines     col ps)    = Just $ polyline buffer ps [penColor := col] >> dirtyPts sPanel ps
302 gfxHandler IS {..} (GfxPolygon   col ps)    = Just $ polygon  buffer ps [penColor := col, brushColor := col] >> dirtyPts sPanel ps
303 gfxHandler IS {..} (GfxText      col xy st) = Just $ drawText buffer st xy [textColor := col] >> getTextExtent buffer st >>= dirtyRect' sPanel xy
304 gfxHandler IS {..} (GfxRectangle col rt)    = Just $ drawRect buffer rt [penColor := col, brushColor := col] >> dirtyRect sPanel rt
305 gfxHandler IS {..} (GfxEllipse   col rt)    = Just $ ellipse buffer rt [penColor := col, brushKind := BrushTransparent] >> dirtyRect sPanel rt
306 gfxHandler IS {..} (GfxDisc      col rt)    = Just $ ellipse buffer rt [penColor := col, brushColor := col] >> dirtyRect sPanel rt
307 gfxHandler IS {..} (GfxFont      st  sz)    = Just $ buffer `set` [ fontSize := sz, fontFace := st ]
308 gfxHandler IS {..} (GfxPicture   fd  pt)    = Just $ bitmapCreateFromFile fd >>= \bm -> drawBitmap buffer bm pt False [] >> bitmapGetSize bm >>= dirtyRect' sPanel pt
309 -}
310 -- | Helper function for gfxHanlder
311 gfxHandler' :: Request -> Maybe (Cairo.Render ())
312 gfxHandler' (GfxText col (Point x y) st) = Just $ do
313         -- Set the source color, move to the requested position and draw the
314         -- text
315         setSourceColor col
316         Cairo.moveTo (fromIntegral x) (fromIntegral y)
317         Cairo.showText st 
318 gfxHandler' GfxClear = Just $ do
319         -- Set the source to white and paint the entire surface with it
320         Cairo.setSourceRGB 1 1 1
321         Cairo.paint
322 gfxHandler' _ = Nothing
323
324 -- | Sets the source to a pattern fill of the given color
325 setSourceColor :: Color -> Cairo.Render ()
326 setSourceColor (Color r g b) =
327         Cairo.setSourceRGB r g b
328
329 {-
330 dirtyPts :: Window a -> [Point] -> IO ()
331 dirtyPts dc ps = dirtyRect' dc (pt x y) Size {..}
332         where
333         xs     = map pointX ps
334         ys     = map pointY ps
335         x      = minimum xs
336         y      = minimum ys
337         sizeW  = maximum xs - x
338         sizeH  = maximum ys - y
339
340 dirtyRect' :: Window a -> Point -> Size -> IO ()
341 dirtyRect' dc Point {..} Size {..} = dirtyRect dc $ Rect pointX pointY sizeW sizeH
342
343 dirtyRect :: Window a -> Rect -> IO ()
344 dirtyRect dc rect = windowRefreshRect dc False (grow 2 rect)
345
346 rectanglify :: Point -> Size -> Rect
347 rectanglify Point {..} Size {..} = Rect pointX pointY sizeW sizeH
348
349 grow :: Int -> Rect -> Rect
350 grow n Rect {..} = Rect
351         { rectLeft   = rectLeft   - n
352         , rectTop    = rectTop    - n
353         , rectWidth  = rectWidth  + 2 * n
354         , rectHeight = rectHeight + 2 * n }
355
356 -}