[GHC] #13153: Several Traversable instances have an extra fmap

GHC ghc-devs at haskell.org
Sat Feb 24 00:17:53 UTC 2018


#13153: Several Traversable instances have an extra fmap
-------------------------------------+-------------------------------------
        Reporter:  dfeuer            |                Owner:  dfeuer
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Core Libraries    |              Version:  8.1
      Resolution:                    |             Keywords:
                                     |  QuantifiedConstraints
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Runtime           |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 Oh dear. I now realize that my heart was in the right place when I wrote
 comment:9, but I goofed up several key details. I had written this
 instance:

 {{{#!hs
 instance (forall f b. Applicative f => Coercible (f (inner b)) (f (Wrapped
 inner b)), Traversable inner) => Traversable (Wrapped inner) where
   traverse :: forall f a b. Applicative f => (a -> f b) -> Wrapped inner a
 -> f (Wrapped inner b)
   traverse = coerce (traverse :: (a -> f b) -> Wrapped inner a -> f
 (Wrapped inner b))
 }}}

 But this is not quite what I wanted. The `f` in the instance context is
 not the same `f` as the `f` in the type signature as `traverse`, which is
 crucial. Indeed, the quantified constraint shouldn't go in the instance
 context at all, but rather in the method type signature itself:

 {{{#!hs
 instance Traversable inner => Traversable (Wrapped inner) where
   traverse :: forall f a b.
               (Applicative f, forall p q. Coercible p q => Coercible (f p)
 (f q))
            => (a -> f b) -> Wrapped inner a -> f (Wrapped inner b)
   traverse = coerce (traverse :: (a -> f b) -> Wrapped inner a -> f
 (Wrapped inner b))
 }}}

 Of course, this isn't going to work either, because that's not actually
 the type signature for `traverse`. If only that were the case!

 But wait, there's something interesting going on here. `f` is an instance
 of `Applicative` and in turn an instance of `Functor`. What exactly //is//
 `Functor`, anyway? Here's the definition we all know and love:

 {{{#!hs
 class Functor f where
   fmap :: (a -> b) -> f a -> f b
 }}}

 If you squint really hard and look at the type signature for `fmap`, it
 says "if you give me a coercion from `a` to `b`, then I can produce a
 coercion from `f a` to `f b`. That's awfully close to `forall a b.
 Coercible a b => Coercible (f a) (f b)`! I'm going to be bold add suggest
 adding just that as a superclass of `Functor`:

 {{{#!hs
 class (forall a b. Coercible a b => Coercible (f a) (f b))
     => Functor f
 }}}

 (This is adapted from a similar suggestion
 [https://ghc.haskell.org/trac/ghc/ticket/9123#comment:3 here], which
 predates `QuantifiedConstraints`.)

 If we did this, we'd be able to newtype-derive `Traversable` instances
 with no further changes, which is awesome! The downside, of course, is
 that we'd have to add a quantified constraint as a superclass of a Haskell
 Report class, at which many people would (understandably) turn up their
 noses.

 If that option is too unpalatable, an alternative would be to add an
 additional class method to `Traversable` with the right context:

 {{{#!hs
 class (Functor t, Foldable t) => Traversable t where
   traverse  :: Applicative f => (a -> f b) -> t a -> f (t b)
   traverse' :: (Applicative f, forall p q. Coercible p q => Coercible (f
 p) (f q))
             => (a -> f b) -> t a -> f (t b)
   traverse' = traverse
 }}}

 Then, folks who really care about performance could implement `traverse' =
 coerce (traverse' :: ...)` themselves and use that. However, you still
 wouldn't be able to newtype-derive `Traversable` with this approach, and
 it's rather unsatisfying in that performance-minded programmers would have
 to switch over all of their `traverse`s to `traverse'`s. (And arguably,
 //every// programmer should be performance-minded anyway!)

 In any case, this situation is clearly more complicated than I originally
 imagined, and I imagine that any solution we could pick will have its
 share of drawbacks.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13153#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list