28

I run into this situation often enough for it to be annoying.

Let's say I have a sum type which can hold an instance of x or a bunch of other things unrelated to x -

data Foo x = X x | Y Int | Z String | ...(other constructors not involving x)

To declare a Functor instance I have to do this -

instance Functor Foo where
    fmap f (X x) = X (f x)
    fmap _ (Y y) = Y y
    fmap _ (Z z) = Z z
    ... And so on

Whereas what I would like to do is this -

instance Functor Foo where
    fmap f (X x) = X (f x)
    fmap _ a = a

i.e. I only care about the X constructor, all other constructors are simply "passed through". But of course this wouldn't compile because a on the left hand side is a different type from the a on the right hand side of the equation.

Is there a way I can avoid writing this boilerplate for the other constructors?

Anupam Jain
  • 7,851
  • 2
  • 39
  • 74
  • Can you write the error? – AJF Jun 16 '15 at 06:17
  • This is just an example, and the actual code is much more complicated, so I don't have an exact error message handy. But it's easy to see the error - The type of fmap must be `(a -> b) -> Foo a -> Foo b` But the last equation has `fmap f a = a`, where `f::(a->b)` and `a::Foo a`, implying that the type of fmap is `(a->b) -> Foo a -> Foo a`. So the error message says that `a` and `b` cannot be unified. – Anupam Jain Jun 16 '15 at 06:40
  • @AJFarmar the rhs has a different type than the lhs. GHC knows that the types check out only if we write out the constructors. – András Kovács Jun 16 '15 at 06:52
  • 4
    Another option would be to derive Functor using that GHC extension? – AJF Jun 16 '15 at 06:55
  • @AJFarmar Good suggestion! However deriving a functor will work for this specific example, but not when you want to do something more complicated in the functor instance. – Anupam Jain Jun 16 '15 at 07:05
  • 1
    Deriving functor should cover a vast amount of cases. IIRC, given a type there can only be one functor instance (satisfying the functor laws), so you can't really do anything different in an hand crafted instance (can't find the proof for this at the moment). One can always also write a Template Haskell library, if all else fails. – chi Jun 16 '15 at 08:08
  • @chi, a hand-written instance for a recursive type may manually apply the static argument transformation to allow the mapped function to inline. Derived instances don't currently do this. Maybe they should. Also, instances can't be derived for GADTs and such. There are also some cases involving existential quantification where there can be multiple valid instances in a boring and unobservable way. And there can also be invalid instances that people want to hide under the module covers. – dfeuer Sep 16 '17 at 18:49
  • @dfeuer Do you have an example for "a hand-written instance for a recursive type may manually apply the static argument transformation to allow the mapped function to inline"? – Anupam Jain Sep 17 '17 at 10:58
  • @AnupamJain, `fmap f = go where go [] = []; go (x:xs) = f x : go xs`, as opposed to the derived `fmap f [] = []; fmap f (x:xs) = f x : fmap f xs`. Usually it doesn't matter, but for passed functions that are somewhat trivial it can matter a good bit. – dfeuer Sep 17 '17 at 15:36
  • @dfeuer ah I see what you mean now! Thanks! – Anupam Jain Sep 17 '17 at 18:41
  • Trivial, in this case, means that they either ignore their argument altogether, or do nothing but apply zero or more lazy constructors. In such cases, inlining prevents the construction of useless thunks, and in the constant case can even prevent memory leaks. – dfeuer Sep 17 '17 at 20:41

4 Answers4

12

There are two main simple solutions to this.

First, for simple types, just deriving (Functor) it using the necessary extension.

The other solution is to define another data type:

data Bar = S String | B Bool | I Int  -- "Inner" type
data Foo a = X a | Q Bar              -- "Outer" type

instance Functor Foo where
    fmap f (X a) = X (f a)
    fmap _ (Q b) = Q b -- `b' requires no type change. 

So you can write one more line to remove many.

It's not exactly ideal for pattern matching, but it does at least solve this problem.

AJF
  • 11,767
  • 2
  • 37
  • 64
10

I assume that we'd like to have a solution for the general case where the changing type parameter is not necessarily in the right position for DeriveFunctor.

We can distinguish two cases.

In the simple case out data type is not recursive. Here, prisms are a fitting solution:

{-# LANGUAGE TemplateHaskell #-}

import Control.Lens

data Foo x y = X x | Y y | Z String

makePrisms ''Foo

mapOverX :: (x -> x') -> Foo x y -> Foo x' y
mapOverX = over _X

If our data is recursive, then things get more complicated. Now makePrisms doesn't create type-changing prisms. We can get rid of the recursion in the definition by factoring it out to an explicit fixpoint. This way our prisms remain type-changing:

import Control.Lens

newtype Fix f = Fix {out :: f (Fix f)}

-- k marks the recursive positions
-- so the original type would be "data Foo x y = ... | Two (Foo x y) (Foo x y)"
data FooF x y k = X x | Y y | Z String | Two k k deriving (Functor)

type Foo x y = Fix (FooF x y)

makePrisms ''FooF

mapOverX :: (x -> x') -> Foo x y -> Foo x' y
mapOverX f = 
   Fix .               -- rewrap 
   over _X f .         -- map f over X if possible
   fmap (mapOverX f) . -- map over recursively
   out                 -- unwrap

Or we can factor out the bottom-up transformation:

cata :: (Functor f) => (f a -> a) -> Fix f -> a
cata f = go where go = f . fmap go . out

mapOverX :: (x -> x') -> Foo x y -> Foo x' y
mapOverX f = cata (Fix . over _X f)

There's a sizeable literature on using fixpoints of functors for generic programming, and also a number of libraries, for example this or this. You might want to search for "recursion schemes" for further references.

András Kovács
  • 29,931
  • 3
  • 53
  • 99
8

Looks like a job for prisms.

Disclaimer: I'm a lens/prism newbie.

{-# LANGUAGE TemplateHaskell   #-}

import Control.Lens
import Control.Lens.Prism

data Foo x = X x | Y Int | Z String deriving Show

makePrisms ''Foo

instance Functor Foo where
   -- super simple impl, by András Kovács
   fmap = over _X
   -- My overly complicated idea
   --    fmap f = id & outside _X .~ (X . f)
   -- Original still more complicated implementation below
   --     fmap f (X x) = X (f x)
   --     fmap _ a = id & outside _X .~ undefined $ a

Usage:

*Main> fmap (++ "foo") (Y 3)
Y 3
*Main> fmap (++ "foo") (X "abc")
X "abcfoo"
n. m. could be an AI
  • 112,515
  • 14
  • 128
  • 243
3

Mostly for completeness, here is yet a way to do it:

import Unsafe.Coerce

instance Functor Foo where
    fmap f (X x) = X (f x)
    fmap _ a = unsafeCoerce a

in the situation described by you, this would actually be a safe use of unsafeCoere. But there are good reasons to avoid this:

  • The safety depends on how GHC compiles the data structures and the code; knowledge that the normal programer should not need to have.
  • It is also not robust: if the datatype is extended with a new constructor X' x, no warning will be generated because the catch-all makes this definition exhaustive and then anything will go. (thx @gallais for that comment)

Therefore, this solution is definitely not advisable.

Joachim Breitner
  • 25,395
  • 6
  • 78
  • 139
  • 2
    It's also not robust: if the datatype is extended with a new constructor `X' x`, no warning will be generated because the catch-all makes this definition exhaustive and then anything will go. – gallais Jun 16 '15 at 11:24
  • Thanks for mentioning it. It's educational, even though it's a bad idea! I did try `coerce`, but that doesn't work across types. I assumed unsafeCoerce would also not work because GHC would represent the two types differently, but I guess I was wrong. – Anupam Jain Jun 16 '15 at 14:08