
#13014: Seemingly unnecessary marking of a SpecConstr specialization as a loopbreaker -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: SpecConstr 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 nfrisby): Thank you for your attention, Simon. I've confirmed your example: these modules `A` and `B` give the same behavior: the specialization in `A` is a loopbreaker and the rule only fires once in `B`. {{{#!hs {-# Language MagicHash #-} {-# OPTIONS_GHC -fspec-constr #-} module A where import GHC.Prim import GHC.Types f :: [a] -> Int# f [] = 0# f (x:xs) = f xs f' a b = f (a:b) -- a call pattern to specialize }}} {{{#!hs {-# Language MagicHash #-} module B where import GHC.Types import A boo = I# (f [1,2,3,4,5,6,6]) }}} And your explanation makes total sense: unexpected supercompilation could have terrible consequences. Also, that's something I'm usually aware of, when I'm not wearing my blinders :). ---- The `SPECIALIZE INLINE` alternative I mentioned in comment:4 is interesting. It's possible as a "workaround" for `lengthVL` precisely because the type constructors (of the spine) are 1-to-1 with the data constructors; thus `SPECIALIZE` can be used to emulate `-fspec-constr`. ---- I opened #13016 regarding the `SPECIALIZE INLINE` specialization being a loopbreaker -- that seems like a bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13014#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler