ConstraintKinds and default associated empty constraints
Gábor Lehel
illissius at gmail.com
Thu Dec 22 14:53:34 CET 2011
On Thu, Dec 22, 2011 at 12:45 AM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> 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
This is the same solution I ended up with, while of course that
doesn't prove there's no better one.
More information about the Glasgow-haskell-users
mailing list