[GHC] #14855: Implementation of liftA2 for Const has high arity

GHC ghc-devs at haskell.org
Mon Feb 26 23:06:52 UTC 2018


#14855: Implementation of liftA2 for Const has high arity
-------------------------------------+-------------------------------------
        Reporter:  lyxia             |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  libraries/base    |              Version:  8.2.2
      Resolution:                    |             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:                    |
-------------------------------------+-------------------------------------

Comment (by lyxia):

 The Core looks different when the `Monoid` remains abstract, but the same
 if it is specialized. So there is some optimization that makes it fine in
 the end.

 Example with abstract `Monoid`:

 {{{
 {-# LANGUAGE ScopedTypeVariables #-}

 module W where

 import Data.Coerce
 import Data.Functor.Const

 xyz, abc :: forall x a b c. Monoid x => (a -> b -> c) -> Const x a ->
 Const x b -> Const x c
 xyz _ (Const a) (Const b) = Const (mappend a b)
 abc _ = coerce (mappend :: x -> x -> x)
 }}}

 Core:

 {{{
 -- RHS size: {terms: 12, types: 24, coercions: 10, joins: 0/0}
 xyz1
 xyz1
   = \ @ x_a10q
       @ a_a10r
       @ b_a10s
       @ c_a10t
       $dMonoid_a10v
       _
       ds1_d11x
       ds2_d11y ->
       mappend
         $dMonoid_a10v (ds1_d11x `cast` <Co:5>) (ds2_d11y `cast` <Co:5>)

 -- RHS size: {terms: 1, types: 0, coercions: 37, joins: 0/0}
 xyz
 xyz = xyz1 `cast` <Co:37>

 -- RHS size: {terms: 8, types: 14, coercions: 0, joins: 0/0}
 abc1
 abc1
   = \ @ x_a105 @ a_a106 @ b_a107 @ c_a108 $dMonoid_a10a _ ->
       mappend $dMonoid_a10a

 -- RHS size: {terms: 1, types: 0, coercions: 39, joins: 0/0}
 abc
 abc = abc1 `cast` <Co:39>
 }}}

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


More information about the ghc-tickets mailing list