#2440: Bad code with type families
-----------------------------------------+----------------------------------
Reporter: rl | Owner:
Type: run-time performance bug | Status: new
Priority: normal | Milestone: 6.10 branch
Component: Compiler | Version: 6.9
Severity: normal | Resolution:
Keywords: | Difficulty: Unknown
Testcase: | Os: Unknown/Multiple
Architecture: Unknown/Multiple |
-----------------------------------------+----------------------------------
Comment (by batterseapower):
Interesting. I can't find $wfoo, but I did find this suspicious looking
function:
{{{
a_smw :: forall s_afW.
Foo.Vec s_afW
-> GHC.Types.Int
-> Foo.M (Foo.Vec s_afW) GHC.Types.Int
[Arity 2
Str: DmdType U(L)L]
a_smw =
\ (@ s_afW) (ds_Xmw :: Foo.Vec s_afW) (n_Xgx :: GHC.Types.Int) ->
case ds_Xmw of _ { Foo.Vec r_afZ [ALWAYS Just D(L)] ->
(\ (s_ane :: GHC.Prim.State# s_afW) ->
case r_afZ of _ { GHC.STRef.STRef var#_anJ [ALWAYS Just L] ->
case GHC.Prim.readMutVar# @ s_afW @ GHC.Types.Int var#_anJ s_ane
of _ { (# new_s_ank [ALWAYS Just L], r_anl [ALWAYS Just D(L)] #) ->
(# new_s_ank,
case r_anl of _ { GHC.Types.I# x_anS [ALWAYS Just L] ->
case n_Xgx of _ { GHC.Types.I# y_anW [ALWAYS Just L] ->
GHC.Types.I# (GHC.Prim.+# x_anS y_anW)
}
} #)
}
})
`cast` (trans
(sym (GHC.ST.NTCo:ST s_afW GHC.Types.Int))
(trans
(sym
(trans
(Foo.TFCo:R1:M s_afW)
(sym
(trans
(trans (GHC.ST.ST s_afW) (GHC.ST.ST s_afW))
(GHC.ST.ST s_afW)))))
(Foo.M (Foo.Vec s_afW))
GHC.Types.Int)
:: GHC.ST.STRep s_afW GHC.Types.Int
~
Foo.M (Foo.Vec s_afW) GHC.Types.Int)
}
}}}
We'd really like to give this an arity of 3, but GHC is currently not
smart enough to eta-expand through this type coercion (see the final case
of eta_expand in CoreUtils.lhs).
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2440#comment:4>
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