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

oleg at okmij.org oleg at okmij.org
Tue Jul 27 04:17:57 EDT 2010


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




More information about the Haskell-Cafe mailing list