compilation fixes
[intricacy.git] / GameStateTypes.hs
blob95cce483d8c417a4f3bd88726ff5ff2d125456d5
1 -- This file is part of Intricacy
2 -- Copyright (C) 2013 Martin Bays <mbays@sdf.org>
3 --
4 -- This program is free software: you can redistribute it and/or modify
5 -- it under the terms of version 3 of the GNU General Public License as
6 -- published by the Free Software Foundation, or any later version.
7 --
8 -- You should have received a copy of the GNU General Public License
9 -- along with this program. If not, see http://www.gnu.org/licenses/.
11 module GameStateTypes where
13 import Data.Map (Map)
14 import Data.Vector (Vector)
15 import Hex
17 data GameState = GameState { placedPieces :: Vector PlacedPiece,
18 connections :: [Connection] }
19 deriving (Eq, Ord, Show, Read)
21 data PlacedPiece = PlacedPiece { placedPos :: HexPos, placedPiece :: Piece }
22 deriving (Eq, Ord, Show, Read)
24 type PieceIdx = Int
26 data Piece = Block { blockPattern :: [HexVec] }
27 | Pivot { pivotArms :: [HexDir] }
28 | Hook { hookArm :: HexDir, hookForce :: HookForce}
29 | Wrench { wrenchMomentum :: HexDir }
30 | Ball
31 deriving (Eq, Ord, Show, Read)
33 data HookForce = NullHF | PushHF HexDir | TorqueHF Int
34 deriving (Eq, Ord, Show, Read)
36 isBlock, isPivot, isHook, isWrench, isTool, isBall :: Piece -> Bool
37 isBlock p = case p of Block _ -> True; _ -> False
38 isPivot p = case p of Pivot _ -> True; _ -> False
39 isHook p = case p of Hook _ _ -> True; _ -> False
40 isWrench p = case p of Wrench _ -> True; _ -> False
41 isTool p = isWrench p || isHook p
42 isBall p = case p of Ball -> True; _ -> False
44 data Connection = Connection { connectionRoot :: Locus
45 , connectionEnd :: Locus, connectionLink :: Link }
46 deriving (Eq, Ord, Show, Read)
48 type Locus = (PieceIdx, HexVec)
50 data Link = Free { freePos :: HexVec }
51 | Spring { springDir :: HexDir, springNatLength :: Int }
52 deriving (Eq, Ord, Show, Read)
54 data SpringExtension = Relaxed | Compressed | Stretched
55 deriving (Eq, Ord, Show, Read)
57 data Tile = BlockTile [HexDir] | PivotTile HexDir | ArmTile HexDir Bool | HookTile | WrenchTile HexDir
58 | BallTile | SpringTile SpringExtension HexDir
59 deriving (Eq, Ord, Show, Read)
61 tileType :: Tile -> Tile
62 tileType (BlockTile _) = BlockTile []
63 tileType (PivotTile _) = PivotTile zero
64 tileType (ArmTile _ _) = ArmTile zero False
65 tileType (WrenchTile _) = WrenchTile zero
66 tileType BallTile = BallTile
67 tileType (SpringTile _ _) = SpringTile Relaxed zero
68 tileType t = t
70 type OwnedTile = (PieceIdx, Tile)
71 type GameBoard = Map HexPos OwnedTile
73 -- |TorqueDir: Int of absolute value <= 1
74 type TorqueDir = Int
76 -- |'force' encompasses both usual directional forces and torques; we use
77 -- 'push' for the former.
78 data Force = Push PieceIdx HexDir | Torque PieceIdx TorqueDir
79 deriving (Eq, Ord, Show)
81 -- |Alert: for passing information about physics processing to the UI
82 data Alert = AlertCollision HexPos | AlertBlockingForce Force
83 | AlertResistedForce Force | AlertBlockedForce Force
84 | AlertAppliedForce Force | AlertDivertedWrench PieceIdx
85 | AlertUnlocked
86 | AlertIntermediateState GameState
87 deriving (Eq, Ord, Show)