What about class Functor f where type C f :: * -> Constraint type C f = ()
After all, just as (Ord a, Show a) is a contraint, so is (). Simon | -----Original Message----- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- | users-boun...@haskell.org] On Behalf Of Bas van Dijk | Sent: 21 December 2011 23:46 | To: glasgow-haskell-users@haskell.org | Subject: ConstraintKinds and default associated empty constraints | | I'm playing a bit with the new ConstraintKinds feature in GHC | 7.4.1-rc1. I'm trying to give the Functor class an associated | constraint so that we can make Set an instance of Functor. The | following code works but I wonder if the trick with: class Empty a; | instance Empty a, is the recommended way to do this: | | {-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleInstances #-} | | import GHC.Prim (Constraint) | | import Prelude hiding (Functor, fmap) | | import Data.Set (Set) | import qualified Data.Set as S (map, fromList) | | class Functor f where | type C f :: * -> Constraint | type C f = Empty | | fmap :: (C f a, C f b) => (a -> b) -> f a -> f b | | class Empty a; instance Empty a | | instance Functor Set where | type C Set = Ord | fmap = S.map | | instance Functor [] where | fmap = map | | testList = fmap (+1) [1,2,3] | testSet = fmap (+1) (S.fromList [1,2,3]) | | Cheers and thanks for a great new feature! | | Bas | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users