[Haskell-cafe] Re: Instances for Set of Functor, Traversable?

Lennart Augustsson lennart at augustsson.net
Tue Jul 27 05:11:16 EDT 2010


But that's not really a solution, since it doesn't make a Functor
instance for Set; it makes a Functor' instance for Set.
If you are willing to not be upwards compatible then, yes, there are solutions.

I think the best bet for an upwards compatible solutions is the
associated constraints,
www.cs.kuleuven.be/~toms/Research/papers/constraint_families.pdf

On Tue, Jul 27, 2010 at 10:17 AM,  <oleg at okmij.org> wrote:
>
> Lennart Augustsson wrote:
>> Try to make Set an instance of Functor and you'll see why it isn't.
>> It's very annoying.
>
> And yet the very simple, and old solution works.
>
>        http://okmij.org/ftp/Haskell/types.html#restricted-datatypes
>
> We just properly generalize Functor, so that all old functors are new
> functors. In addition, many more functors become possible, including
> Set. In general, we can have functors
>        fmap' :: (C1 a, C2 b) => (a -> b) -> f a -> f b
> Incidentally, even an Integer may be considered a functor:
> we can define the fmap' operation fitting the above signature, where
> the constraint C1 a is a ~ Integer.
>
> Although the use of OverlappingInstances is not required, the
> extension leads to the nicest code; all old functors just work.
>
>
> {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
> {-# LANGUAGE OverlappingInstances #-}
>
> module FunctorEx where
>
> import Control.Monad
> import Data.Set as S
>
> class Functor' f a b where
>    fmap' :: (a -> b) -> f a -> f b
>
> -- The default instance:
> -- All ordinary Functors are also extended functors
>
> instance Functor f => Functor' f a b where
>    fmap' = fmap
>
> -- Now define a functor for a set
> instance (Ord a, Ord b) => Functor' S.Set a b where
>    fmap' = S.map
>
>
> -- Define a degenerate functor, for an integer
> newtype I a = I Integer deriving Show
>
> instance Functor'  I Integer Integer where
>    fmap' f (I x) = I $ f x
>
> -- tests
>
> -- Lists as functors
> test_l = fmap' (+10) [1,2,3,4]
> -- [11,12,13,14]
>
> -- Sets as functors
> test_s = fmap' (\x -> x `mod` 3) $ S.fromList [1,2,3,4]
> -- fromList [0,1,2]
>
> -- Integer as functor
> test_i = fmap' (* (6::Integer)) $ I 7
> -- I 42
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list