[GHC] #13218: <$ is bad in derived functor instances

GHC ghc-devs at haskell.org
Wed Feb 1 18:59:17 UTC 2017


#13218: <$ is bad in derived functor instances
-------------------------------------+-------------------------------------
           Reporter:  dfeuer         |             Owner:  dfeuer
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.4.1
          Component:  Compiler       |           Version:  8.1
           Keywords:                 |  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:
-------------------------------------+-------------------------------------
 `Functor` deriving derives the definition of `fmap`, leaving the
 definition of `<$` to the default. This is quite bad for recursive types:

 {{{#!hs
 data Tree a = Bin !(Tree a) a !(Tree a) | Tip deriving Functor
 }}}

 produces

 {{{
 Replace.$fFunctorTree_$c<$ =
   \ (@ a_aGl) (@ b_aGm) (eta_aGn :: a_aGl) (eta1_B1 :: Tree b_aGm) ->
     Replace.$fFunctorTree_$cfmap
       @ b_aGm @ a_aGl (\ _ [Occ=Dead] -> eta_aGn) eta1_B1
 }}}

 Why is this bad? It fills the tree with thunks keeping the original values
 (which we never use again) alive. What we want to generate is

 {{{#!hs
 x <$ Bin l _ r = Bin (x <$ l) x (x <$ r)
 }}}

 When there are other functor types in the constructor, like

 {{{#!hs
   | Whatever (Tree (Tree a))
 }}}

 we will need to insert `fmap (x <$) t`. The overall shape should be
 basically the same as `fmap` deriving.

 Note: there are some types for which we will not realistically be able to
 derive optimal definitions. In particular, fixed-shape, undecorated types
 that appear in nested types allow special treatment:

 {{{#!hs
 data Pair a = Pair a a deriving Functor
 data Tree2 a = Z a | S (Tree2 (Pair a)) deriving Functor
 }}}

 The ideal definition for this type is

 {{{#!hs
   x <$ Z _ = Z x
   x <$ S t = S (Pair x x <$ t)
 }}}

 but that requires cleverness. We should probably settle for

 {{{#!hs
   x <$ Z _ = Z x
   x <$ S t = S (fmap (x <$) t)
 }}}

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


More information about the ghc-tickets mailing list