[Haskell-cafe] Trying to sort out multiparameter type classes and
their instances
Daniel Fischer
daniel.is.fischer at web.de
Tue Dec 1 18:12:44 EST 2009
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.
IOW, it's a type constructor of kind (* -> * -> *), like (->) or Either.
(* is the kind of types [Int, Char, Either Bool (), Double -> Rational -> Int, ...]
> -- Query pos to get piece (Nothing if off board)
> at :: b pos piece -> pos -> Maybe piece
> -- Empty board
> empty :: b pos piece
>
> and a Position on the board is represented thus:
>
> class Position p where
> up :: p -> p
> down :: p -> p
> left :: p -> p
> right :: p -> p
>
> With a concrete implementation using a tuple:
>
> instance (Enum c,Enum r) => Position (c,r) where
> up = second pred
> down = second succ
> left = first pred
> right = first succ
>
>
> My initial Board is a function: position -> Maybe piece, but I'm having
> a hard time writing the instance for it. My first attempt is:
>
> instance Board (pos -> Maybe piece) pos piece where
> empty = \_ -> Nothing
> at = ($)
> play b pos piece = move
> where move pos' | pos' == pos = Just piece
>
> | otherwise = b pos'
>
> 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.
>
> Playing around with parentheses on the instance line got various similar
> messages, but I couldn't get anything to work.
>
> What am I missing here?
>
> One thing that strikes me is that "Board (pos -> Maybe piece) pos piece"
> has a lot of redundancy, and I'm wondering if I'm defining the Board
> type class wrong in the first place.
>
> Given that the "b" type parameter necessarily defines the position and
> pieces, I tried using dependent types:
>
> class Board b | b -> pos, b -> piece where ...
Method 1: The class above, with a modified instance.
newtype Brd pos piec = Brd { mpiece :: pos -> Maybe piece }
instance (Eq pos) => Board Brd pos piece where
play b pos piece = Brd $ \p -> if p == pos then Just piece else mpiece b pos
...
Perhaps not truly satisfying.
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.
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.
Choose your pick.
More information about the Haskell-Cafe
mailing list