
On Wed, Dec 21, 2011 at 6:45 PM, Bas van Dijk
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 wound up with in https://github.com/ekmett/constraints Adding an argument to the family would work but is somewhat unsatisfying as it mucks with polymorphic recursive use of the dictionary, and with placing constraints on constraints, so I prefer to keep as few arguments as possible. You can go farther with Functor by using polymorphic kinds and indexing the source and destination Category as well as the class of objects in the category. I should probably write up what I've done with this, but doing so lets you have real product and coproduct Category instances, which were previously not possible (a fact which in part drove me to write all the semigroupoid code i have on hackage. -Edward