[GHC] #12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint interation
GHC
ghc-devs at haskell.org
Thu Jul 7 08:08:07 UTC 2016
#12368: Demand Analyzer: Cunnig plan not adhered to with aborting fixpoint
interation
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner:
Type: bug | Status: new
Priority: low | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by nomeata):
I could trigger an unsound result this way:
{{{#!hs
module DmdFixBug where
-- Needs to be a product type
data Stream = S Int Stream
bar s = foo s
where
foo :: Stream -> Int
foo (S n s) = n + foo s
}}}
that terminate only because of the 10-iteration-limit, and as you can see,
the result is wrong (there is an “absent” value that is not absent)
{{{
bar :: Stream -> Int
[LclIdX,
Arity=1,
Str=<B,1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),A)))))))))>b,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)
Tmpl= \ (s_axX [Occ=Once] :: Stream) -> foo_sK7 s_axX}]
bar =
\ (s_axX
[Dmd=<B,1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),1*U(1*U(U),A)))))))))>]
:: Stream) ->
foo_sK7 s_axX
}}}
(I need to wrap `foo` in `bar` because `foo` does not get a strictness
result attached, because the analysis fails.)
I’ll see if I can actually make the program crash, and turn this into a
proper test suite test case.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12368#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list