1 {-# LANGUAGE FlexibleContexts, MultiParamTypeClasses #-}
3 -- This module contains function that allow the particular geometry of
4 -- the board to not cause too much problems.
6 -- They are stolen from the gtk-helpers library.
8 module RMCA.GUI.HelpersRewrite where
12 import Control.Monad.IO.Class
17 import Game.Board.BasicTurnGame
18 import Graphics.UI.Gtk hiding (Action)
19 import Graphics.UI.Gtk.Board.BoardLink hiding (attachGameRules)
20 import Graphics.UI.Gtk.Board.TiledBoard hiding
22 , boardOnPieceDragDrop
23 , boardOnPieceDragOver
24 , boardOnPieceDragStart
26 import qualified Graphics.UI.Gtk.Board.TiledBoard as BIO
29 data GUICell = GUICell { cellAction :: Action
34 data Player = Player deriving(Show)
36 -- Takes a GUI coordinate and give the corresponding coordinate on the
38 fromGUICoords :: (Int,Int) -> (Int,Int)
39 fromGUICoords (x,y) = (x,(x `mod` 2 - y) `quot` 2)
41 -- Takes coordinates from the point of view of the internal board and
42 -- translates them to GUI board coordinates.
43 toGUICoords :: (Int,Int) -> (Int,Int)
44 toGUICoords (x,y) = (x,2*(-y) + x `mod` 2)
47 defNa = NoteAttr { naArt = NoAccent
53 (xMax,yMax) = second (*2) $ neighbor N nec
55 (xMin,yMin) = second (*2) swc
57 ctrlPieces :: [(Int,Int,Player,GUICell)]
58 ctrlPieces = [(xMax+2,y,Player,GUICell { cellAction = action
62 | let actions = [ Absorb, Stop defNa
63 , ChDir False defNa N, ChDir True defNa N
65 -- /!\ It would be nice to find a general formula
66 -- for placing the control pieces.
67 , (y,action) <- zip [ yMin+4,yMin+8..] actions]
69 ctrlCoords :: [(Int,Int)]
70 ctrlCoords = map (\(x,y,_,_) -> (x,y)) ctrlPieces
72 boardToPiece :: [PlayHead] -> Board -> [(Int,Int,Player,GUICell)]
73 boardToPiece ph = (++ ctrlPieces) . map placePiece .
74 filter (onBoard . fst) . assocs
75 where placePiece :: (Pos,Cell) -> (Int,Int,Player,GUICell)
76 placePiece ((x,y),(a,n)) = let c = GUICell { cellAction = a
78 , asPh = (x,y) `elem` phPosS
80 (x',y') = toGUICoords (x,y)
84 validArea :: [(Int,Int)]
85 validArea = filter (onBoard . fromGUICoords) $
86 map (\(x,y,_,_) -> (x,y)) $ boardToPiece [] $ makeBoard []
88 -- Because of the geometry of the board, a tile might be covered by a
89 -- piece without actually carrying any. This function retrieves the
90 -- index of the tile carrying the piece that covers the tile.
91 actualTile :: (Int,Int) -> (Int,Int)
93 | y <= yMin || p `elem` piecesCoords = p
95 where piecesCoords = validArea ++ ctrlCoords
97 boardOnPieceDragStart :: BIO.Board Int tile piece
98 -> ((Int, Int) -> IO Bool) -> IO()
99 boardOnPieceDragStart board f = boardOnPress board $ \ix -> do
100 (x,y) <- eventCoordinates
101 returning False $ liftIO $ do
102 drag <- readIORef (dragEnabled board)
105 let from = if canDragThis
106 then Just $ actualTile ix
108 orig = if canDragThis
109 then Just (relativePos board (actualTile ix) (round x, round y))
111 writeIORef (draggingFrom board) from
112 writeIORef (draggingMouseOrig board) orig
113 boardInvalidate board
115 boardOnPieceDragOver :: Ix index =>
116 BIO.Board index tile piece
117 -> ((index, index) -> (index, index) -> IO Bool) -> IO()
118 boardOnPieceDragOver board f = boardOnMotion board $ \ix -> do
119 (x,y) <- eventCoordinates
120 returning False $ liftIO $ do
121 drag <- readIORef (dragEnabled board)
122 origM <- readIORef (draggingFrom board)
123 when (drag && isJust origM) $ do
124 canDropHere <- f (fromJust origM) ix
125 let newDest = if canDropHere then Just ix else Nothing
126 writeIORef (draggingTo board) newDest
127 writeIORef (draggingMousePos board) (Just (round x, round y))
128 boardInvalidate board
130 boardOnPieceDragDrop :: Ix index =>
131 BIO.Board index tile piece
132 -> ((index, index) -> (index, index) -> IO ()) -> IO()
133 boardOnPieceDragDrop board f = void $ do
134 widgetAddEvents (boardDrawingArea board) [ButtonPressMask, ButtonReleaseMask]
135 boardDrawingArea board `on` buttonReleaseEvent $ returning False $ liftIO $ do
136 drag <- readIORef (dragEnabled board)
137 origM <- readIORef (draggingFrom board)
138 destM <- readIORef (draggingTo board)
139 let notSame = origM /= destM
140 when (drag && isJust origM) $ do
142 -- No longer dragging
143 writeIORef (draggingFrom board) Nothing
144 writeIORef (draggingTo board) Nothing
145 writeIORef (draggingMouseOrig board) Nothing
146 writeIORef (draggingMousePos board) Nothing
148 -- When possible, call the handler
149 when (isJust destM && notSame) $ f (fromJust origM) (fromJust destM)
151 -- In any case, the board must be repainted
152 boardInvalidate board
154 -- This is a function shamelessy stolen and rewritten from gtk-helpers
155 -- to allow for hexagonal boards.
156 attachGameRules :: (PlayableGame a Int tile player piece) =>
157 Game a Int tile player piece
158 -> IO (BIO.Board Int tile (player, piece))
159 attachGameRules game = do
160 board <- boardNew (allPos $ gameS game) (tileF $ visual game)
161 (pieceF $ visual game)
163 let (r,g,b) = bgColor (visual game)
164 (r', g', b') = (fromIntegral r, fromIntegral g, fromIntegral b)
165 mapM_ (\s -> widgetModifyBg board s (Color r' g' b'))
166 [StateNormal, StateActive, StatePrelight, StateSelected]
167 when (isJust (bg $ visual game)) $
168 boardSetBackground board (bg $ visual game)
170 vgRef <- newIORef game
172 -- Set the initial board state
173 mapM_ (\(x,y) -> boardSetPiece x y board)
174 [((x,y),(pl,pc)) | (x,y,pl,pc) <- allPieces (gameS game)]
176 board `boardOnPieceDragStart` \pos' -> do
177 let pos = actualTile pos'
178 visualGame <- readIORef vgRef
179 let game' = gameS visualGame
180 return (moveEnabled game' && canMove game' (curPlayer game') pos)
182 board `boardOnPieceDragOver` \posF' posT' -> do
183 let posF = actualTile posF'
184 posT = actualTile posT'
185 visualGame <- readIORef vgRef
186 let game' = gameS visualGame
187 return (moveEnabled game' && canMoveTo game' (curPlayer game') posF posT)
189 board `boardOnPieceDragDrop` \posF' posT' -> do
190 let posF = actualTile posF'
191 posT = actualTile posT'
192 visualGame <- readIORef vgRef
193 let game' = gameS visualGame
194 moves = move game' (curPlayer game') posF posT
195 game'' = foldl applyChange game' moves
196 writeIORef vgRef (visualGame { gameS = game'' })
197 forM_ moves (applyBoardChange board)
199 when (moveEnabled (gameS game)) $ boardEnableDrag board