[Haskell-cafe] lawless instances of Functor

Brent Yorgey byorgey at seas.upenn.edu
Mon Jan 4 18:22:48 EST 2010


On Mon, Jan 04, 2010 at 11:49:33PM +0100, Steffen Schuldenzucker wrote:
> 
> data Foo a = Foo a
> 
> instance Functor Foo where
>     fmap f (Foo x) = Foo . f . f $ x
> 
> Then:
> 
> fmap id (Foo x) == Foo . id . id $ x == Foo x
> 
> fmap (f . g) (Foo x)      == Foo . f . g . f . g $ x
> fmap f . fmap g $ (Foo x) == Foo . f . f . g . g $ x
> 
> Now consider Foo Int and
> 
> fmap ((+1) . (*3)) (Foo x)      == Foo $ (x * 3 + 1) * 3 + 1
>     == Foo $ x * 9 + 4
> fmap (+1) . fmap (*3) $ (Foo x) == Foo $ x * 3 * 3 + 1 + 1
>     == Foo $ x * 9 + 2

As others have pointed out, this doesn't typecheck; but what it DOES
show is that if we had a type class

  class Endofunctor a where
    efmap :: (a -> a) -> f a -> f a

then it would be possible to write an instance for which efmap id = id
but efmap (f . g) /= efmap f . efmap g.  The difference is that with
the normal Functor class, once you have applied your function f :: a
-> b to get a b, you can't do anything else with it, since you don't
know what b is.  With the Endofunctor class, once you have applied f
:: a -> a, you CAN do something with the result: namely, apply f
again.  

-Brent


More information about the Haskell-Cafe mailing list