[GHC] #13077: Worker/wrapper can break the let-app invariant
GHC
ghc-devs at haskell.org
Fri Jan 6 17:38:23 UTC 2017
#13077: Worker/wrapper can break the let-app invariant
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider this
{{{
{-# LANGUAGE MagicHash #-}
module Bar where
import GHC.Exts
data X = A | B | C
data T = MkT !X Int# Int#
f (MkT x 0# _) = True
f (MkT x n _) = let v = case x of
A -> 1#
B -> 2#
C -> n
in f (MkT x v v)
}}}
Compile with -O and (with GHC 8) you'll get
{{{
*** Core Lint errors : in result of Simplifier ***
Bar.hs:10:23: Warning:
[RHS of v_s1IX :: Int#]
The type of this binder is primitive: v_s1IX
Binder's type: Int#
*** Offending Program ***
Rec {
f [InlPrag=INLINE[0]] :: T -> Bool
[LclIdX,
Arity=1,
Str=DmdType <S(SSL),1*U(U,1*U,A)>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
Tmpl= \ (w_s1Jq [Occ=Once!] :: T) ->
case w_s1Jq
of _ [Occ=Dead]
{ MkT ww_s1Jt [Occ=Once] ww_s1Ju [Occ=Once] _ [Occ=Dead]
->
$wf_s1Jx ww_s1Jt ww_s1Ju
}}]
f =
\ (w_s1Jq :: T) ->
case w_s1Jq of _ [Occ=Dead] { MkT ww_s1Jt ww_s1Ju ww_s1Jv ->
$wf_s1Jx ww_s1Jt ww_s1Ju
}
$wf_s1Jx [InlPrag=[0], Occ=LoopBreaker] :: X -> Int# -> Bool
[LclId,
Arity=2,
Str=DmdType <S,U><S,1*U>,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [40 30] 80 10}]
$wf_s1Jx =
\ (ww_s1Jt :: X) (ww_s1Ju :: Int#) ->
case ww_s1Ju of ds_X1IO [Dmd=<L,1*U>] {
__DEFAULT ->
let {
v_s1IX [Dmd=<S,U>] :: Int#
[LclId,
Str=DmdType,
Unf=Unf{Src=<vanilla>, TopLvl=False, Value=False,
ConLike=False,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30
0}]
v_s1IX =
case ww_s1Jt of _ [Occ=Dead, Dmd=<L,A>] {
A -> 1;
B -> 2;
C -> ds_X1IO
} } in
$wf_s1Jx ww_s1Jt v_s1IX;
0 -> True
}
end Rec }
}}}
Reason: in the worker, the lambda-bound arguments don't say they are
evaluated, so the previously ok-for-speculation RHS of the 'let' is no
longer so.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13077>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list