#7542: GHC doesn't optimize (strict) composition with id
---------------------------------+------------------------------------------
Reporter: shachaf | Owner:
Type: bug | Status: infoneeded
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.1
Keywords: | Os: Unknown/Multiple
Architecture: Unknown/Multiple | Failure: Runtime performance bug
Difficulty: Unknown | Testcase:
Blockedby: | Blocking:
Related: |
---------------------------------+------------------------------------------
Changes (by simonpj):
* status: new => infoneeded
* difficulty: => Unknown
Comment:
Can you give a concrete example? With this module
{{{
module T7542 where
newtype Id a = MkId a
f1 = map reverse
f2 = map (MkId . reverse)
}}}
compiled with `ghc-7.6 -O -ddump-stg` I get
{{{
==================== STG syntax: ====================
T7542.f1 :: forall a_afy. [[a_afy]] -> [[a_afy]]
[GblId, Arity=1, Str=DmdType, Unf=OtherCon []] =
\r [eta_B1] GHC.Base.map GHC.List.reverse eta_B1;
SRT(T7542.f1): []
T7542.f2 :: forall a_afr. [[a_afr]] -> [T7542.Id [a_afr]]
[GblId, Arity=1, Str=DmdType, Unf=OtherCon []] =
\r [eta_B1] GHC.Base.map GHC.List.reverse eta_B1;
SRT(T7542.f2): []
}}}
which looks fine to me.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7542#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs