
On 12/01/09 15:12, Daniel Fischer wrote:
Am Dienstag 01 Dezember 2009 23:34:46 schrieb Jeremy Fitzhardinge:
I'm playing around with some types to represent a game board (like Go, Chess, Scrabble, etc).
I'm using a type class to represent the basic Board interface, so I can change the implementation freely:
class Board b pos piece where -- Update board with piece played at pos play :: b pos piece -> pos -> piece -> b pos piece
So the parameter b of the class is a type constructor taking two types and constructing a type from those.
Yep.
IOW, it's a type constructor of kind (* -> * -> *), like (->) or Either. (* is the kind of types [Int, Char, Either Bool (), Double -> Rational -> Int, ...]
[...]
but ghci complains: board.hs:34:15: Kind mis-match Expected kind `* -> * -> *', but `pos -> Maybe piece' has kind `*' In the instance declaration for `Board (pos -> Maybe piece) pos piece'
Yes, as said above. (pos -> Maybe piece) is a *type*, but the type class expects a type constructor of kind (* -> * ->*) here.
I thought "(pos -> Maybe piece) pos piece" would provide the 3 type arguments to Board. Oh, I see my mistake. I was seeing "b pos piece" as type parameters for Board, but actually Board is just taking a single parameter of kind * -> * -> *.
Method 2: Multiparameter type class with functional dependencies and suitable kinds
class Board b pos piece | b -> pos, b -> piece where play :: b -> pos -> piece -> b at :: b -> pos -> Maybe piece empty :: b
instance (Eq pos) => Board (pos -> Maybe piece) pos piece where play b pos piece = \p -> if p == pos then Just piece else b p at = id empty = const Nothing
requires {-# LANGUAGE FlexibleInstances #-}
Not necessarily ideal either.
OK, but that's pretty much precisely what I was aiming for. I'm not sure I understand what the difference between play :: b pos piece -> pos -> piece -> b pos piece and play :: b -> pos -> piece -> b is. Does adding type params to b here change its kind?
Method 3: Associated type families
{-# LANGUAGE TypeFamilies, FlexibleInstances #-} module Board where
class Board b where type Pos b :: * type Piece b :: * play :: b -> Pos b -> Piece b -> b at :: b -> Pos b -> Maybe (Piece b) empty :: b
instance (Eq pos) => Board (pos -> Maybe piece) where type Pos (pos -> Maybe piece) = pos type Piece (pos -> Maybe piece) = piece play b pos piece = \p -> if p == pos then Just piece else b p at b p = b p empty _ = Nothing
I would try that first.
OK, there's some new stuff there I'm going to have to digest... Thanks very much, J