
On 29 February 2012 19:54, Daniel Gorín
I was always under the impression that the fact that Data.Set.Set can not be made an instance of Functor was a sort of unavoidable limitation.
I guess the way forward is to start using ConstraintKinds and TypeFamilies: {-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleInstances #-} import Prelude hiding (Functor, fmap) import Data.Set (Set) import qualified Data.Set as Set (map) import GHC.Exts (Constraint) class Functor f where type FunctorConstraint f :: * -> Constraint type FunctorConstraint f = Empty fmap :: (FunctorConstraint f b) => (a -> b) -> f a -> f b class Empty a instance Empty a instance Functor Set where type FunctorConstraint Set = Ord fmap = Set.map -- Note that the unnecessary 'Ord a' constraint needs to be dropped from: -- Set.map :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b Regards, Bas