1 {-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses,
2 ScopedTypeVariables, TypeSynonymInstances #-}
4 module RMCA.GUI.Board ( GUICell (..)
19 import Data.Array.MArray
20 import qualified Data.Bifunctor as BF
21 import Data.Board.GameBoardIO
24 import Data.ReactiveValue
25 import Game.Board.BasicTurnGame
26 import Graphics.UI.Gtk hiding (Action)
27 import Graphics.UI.Gtk.Board.BoardLink hiding (attachGameRules)
28 import Graphics.UI.Gtk.Board.TiledBoard hiding
30 , boardOnPieceDragDrop
31 , boardOnPieceDragOver
32 , boardOnPieceDragStart
34 import qualified Graphics.UI.Gtk.Board.TiledBoard as BIO
36 import RMCA.Global.Clock
37 import RMCA.GUI.HelpersRewrite
40 newtype GUIBoard = GUIBoard { toGS :: GameState Int Tile Player GUICell }
42 type IOBoard = BIO.Board Int Tile (Player,GUICell)
44 -- There are two types of tiles that can be distinguished by setting
45 -- two different colors for debugging purposes. A future release might
46 -- want to remove that.
47 data Tile = TileW | TileB
50 rotateGUICell :: GUICell -> GUICell
51 rotateGUICell g = g { cellAction = rotateAction $ cellAction g }
52 where rotateAction (ChDir b na d) = ChDir b na (nextDir d)
61 d = sqrt 3 * fromIntegral tileW / 3
66 d = 4 * fromIntegral tileW / 3
71 d = sqrt 3 * fromIntegral hexW / 2
73 boardToTile :: [(Int,Int,Tile)]
74 boardToTile = [(x,y,selTile) | (x,y) <- range ( (xMin-1,yMin)
76 , let selTile = if even x && even y
84 outGUIBoard :: (Int,Int) -> Bool
85 outGUIBoard (xf,yf) = xf < xMin || xf > xMax || yf < yMin || yf > yMax
88 inertCell = GUICell { cellAction = Inert
93 initGUIBoard :: GUIBoard
94 initGUIBoard = GUIBoard GameState
96 , boardPos = boardToTile
97 , boardPieces' = boardToPiece [] $ makeBoard []
100 instance PlayableGame GUIBoard Int Tile Player GUICell where
102 allPos (GUIBoard game) = boardPos game
103 allPieces (GUIBoard game) = boardPieces' game
106 canMove (GUIBoard game) _ (x,y)
107 | Just (_,p) <- getPieceAt game (x,y)
108 , GUICell { cellAction = Inert } <- p = False
109 | Nothing <- getPieceAt game (x,y) = False
111 canMoveTo _ _ _ fPos = fPos `elem` validArea || outGUIBoard fPos
113 move (GUIBoard game) _ iPos@(_,yi) fPos@(xf,yf)
114 | outGUIBoard iPos && outGUIBoard fPos = []
115 | outGUIBoard fPos = [ RemovePiece iPos
116 , AddPiece iPos Player nCell ]
117 | iPos `elem` ctrlCoords = [ RemovePiece fPos'
118 , AddPiece fPos' Player
119 (nCell { cellAction = ctrlAction }) ]
120 | otherwise = [ MovePiece iPos fPos'
121 , AddPiece iPos Player nCell ]
123 | (xf `mod` 2 == 0 && yf `mod` 2 == 0)
124 || (xf `mod` 2 /= 0 && yf `mod` 2 /= 0) = (xf,yf)
125 | otherwise = (xf,yf+signum' (yf-yi))
128 | otherwise = signum x
129 ctrlAction = cellAction $ snd $ fromJust $ getPieceAt game iPos
131 | Just (_,GUICell { asPh = ph, repeatCount = n }) <-
132 getPieceAt game iPos = inertCell { repeatCount = n
135 | otherwise = inertCell
137 applyChange (GUIBoard game) (AddPiece (x,y) Player piece) =
138 GUIBoard $ game { boardPieces' = bp' }
139 where bp' = (x,y,Player,piece):boardPieces' game
141 applyChange (GUIBoard game) (RemovePiece (x,y)) = GUIBoard $
142 game { boardPieces' = bp' }
143 where bp' = [p | p@(x',y',_,_) <- boardPieces' game
144 , x /= x' || y /= y']
146 applyChange guiBoard@(GUIBoard game) (MovePiece iPos fPos)
147 | Just (_,p) <- getPieceAt game iPos
148 = applyChanges guiBoard [ RemovePiece iPos
150 , AddPiece fPos Player p]
151 | otherwise = guiBoard
153 initGame :: IO (Game GUIBoard Int Tile Player GUICell)
155 pixbufs <- fileToPixbuf
156 tilePixbufB <- pixbufNew ColorspaceRgb False 8 tileW tileH
157 tilePixbufW <- pixbufNew ColorspaceRgb False 8 tileW tileH
158 pixbufFill tilePixbufB 50 50 50 0
159 pixbufFill tilePixbufW 50 50 50 0
160 let pixPiece :: (Player,GUICell) -> Pixbuf
161 pixPiece (_,a) = fromJust $ lookup (actionToFile a) pixbufs
162 pixTile :: Tile -> Pixbuf
163 pixTile TileW = tilePixbufW
164 pixTile TileB = tilePixbufB
165 visualA = VisualGameAspects { tileF = pixTile
167 , bgColor = (1000,1000,1000)
171 return $ Game visualA initGUIBoard
173 -- Initializes a readable RV for the board and an readable-writable RV
174 -- for the playheads. Also installs some handlers for pieces modification.
175 initBoardRV :: TickableClock
176 -> BIO.Board Int Tile (Player,GUICell)
177 -> IO ( ReactiveFieldRead IO Board
178 , Array Pos (ReactiveFieldWrite IO GUICell)
179 , ReactiveFieldWrite IO [PlayHead])
180 initBoardRV tc board@BIO.Board { boardPieces = (GameBoard gArray) } = do
182 phMVar <- newCBMVar []
183 let getterB :: IO Board
185 (boardArray :: [((Int,Int),Maybe (Player,GUICell))]) <- getAssocs gArray
186 let board = makeBoard $
187 map (BF.first fromGUICoords .
188 BF.second ((\(_,c) -> (cellAction c,repeatCount c)) .
190 filter (isJust . snd) boardArray
193 notifierB :: IO () -> IO ()
194 notifierB = reactiveValueOnCanRead tc
196 getterP :: IO [PlayHead]
197 getterP = readCBMVar phMVar
199 setterP :: [PlayHead] -> IO ()
201 oph <- readCBMVar phMVar
202 let offPh :: PlayHead -> IO ()
204 let pos = toGUICoords $ phPos ph
205 piece <- boardGetPiece pos board
206 when (isJust piece) $ do
207 let (_,c) = fromJust piece
208 boardSetPiece pos (Player, c { asPh = False }) board
209 onPh :: PlayHead -> IO ()
211 let pos = toGUICoords $ phPos ph
212 piece <- boardGetPiece pos board
213 when (isJust piece) $ do
214 let (_,c) = fromJust piece
215 boardSetPiece pos (Player, c { asPh = True }) board
216 postGUIAsync $ mapM_ offPh oph
217 postGUIAsync $ mapM_ onPh lph
218 writeCBMVar phMVar lph
220 notifierP :: IO () -> IO ()
221 notifierP = installCallbackCBMVar phMVar
223 b = ReactiveFieldRead getterB notifierB
224 ph = ReactiveFieldReadWrite setterP getterP notifierP
226 setterW :: (Int,Int) -> GUICell -> IO ()
227 setterW i g = postGUIAsync $ boardSetPiece i (Player,g) board
230 arrW :: Array Pos (ReactiveFieldWrite IO GUICell)
231 arrW = array (minimum validArea, maximum validArea)
232 [(i, ReactiveFieldWrite (setterW i))
233 | i <- validArea :: [(Int,Int)]]
235 return (b,arrW,writeOnly ph)
237 fileToPixbuf :: IO [(FilePath,Pixbuf)]
238 fileToPixbuf = mapM (\f -> let f' = ("img/" ++ f) in
241 , getDataFileName f' >>=
242 (pixbufNewFromFile >=>
243 \p -> pixbufScaleSimple p hexW hexW InterpBilinear)))
244 (["hexOn.png","hexOff.png","stop.svg","split.svg","absorb.svg"] ++
245 concat [["start" ++ show d ++ ".svg","ric" ++ show d ++ ".svg"]
248 actionToFile :: GUICell -> FilePath
249 actionToFile GUICell { cellAction = a
253 Inert -> "img/hexO" ++ (if ph then "n" else "ff") ++ ".png"
254 Absorb -> "img/absorb.svg"
255 Stop _ -> "img/stop.svg"
256 ChDir True _ d -> "img/start" ++ show d ++ ".svg"
257 ChDir False _ d -> "img/ric" ++ show d ++ ".svg"
258 Split _ -> "img/split.svg"