2009/4/2 Louis Wasserman <wasserman.louis@gmail.com>
The following module does not compile, and I can't figure out why:{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE KindSignatures #-}module Foo where
import Control.Monadimport Data.Maybeclass Key k wheretype Map k :: * -> *empty :: Map k v
look :: k -> Map k v -> Maybe vupdate :: k -> (Maybe v -> Maybe v) -> Map k v -> Map k vinstance (Key k1, Key k2) => Key (k1, k2) wheretype Map (k1, k2) v = Map k1 (Map k2 v)
empty = empty
update (k1, k2) f = update k1 (update k2 f . fromMaybe empty)look (k1, k2) = look k1 >=> look k2The compile fails withFoo.hs:16:1:Number of parameters must match family declaration; expected 1In the type synonym instance declaration for `Map'In the instance declaration for `Key (k1, k2)'Is this a bug with type synonym families? Is there something silly I'm missing?Louis Wasserman
wasserman.louis@gmail.com
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe