[GHC] #13916: Optimizations create run time seg faults
GHC
ghc-devs at haskell.org
Fri Jul 14 19:36:31 UTC 2017
#13916: Optimizations create run time seg faults
-------------------------------------+-------------------------------------
Reporter: newthin | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.2.2
Component: Compiler | Version: 8.0.2
(CodeGen) |
Resolution: | Keywords: optimization
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by bgamari):
Here is a sketch of the structure of `takeEnv` along with strictness
signatures,
{{{
takeEnv =
\ (@ env_a3hT)
(x_X3Lx [Dmd=<B,1*U(U,U,U)>] :: Vector (TMVar env_a3hT))
(eta_B1 [Dmd=<B,U>] :: GHC.Prim.State# GHC.Prim.RealWorld) ->
case x_X3Lx of
{ Data.Vector.Vector ipv_s4Q7 [Dmd=<B,U>] ipv_s4Q8 [Dmd=<B,U>]
ipv_s4Q9 [Dmd=<B,U>] ->
joinrec {
foldlM_loop_a45q [Occ=LoopBreaker]
:: GHC.Types.SPEC
-> STM env_a3hT
-> Int
-> (# GHC.Prim.State# GHC.Prim.RealWorld, env_a3hT #)
foldlM_loop_a45q (ds4_a45s [Dmd=<S,1*U>] :: GHC.Types.SPEC)
(z1_a45t [Dmd=<C(S),1*C1(U(U,U))>] :: STM
env_a3hT)
(s1_a45u [Dmd=<S(S),1*U(U)>] :: Int) = ...
}
in jump foldlM_loop_a45q
GHC.Types.SPEC
(((src<Bracket.hs:119:32-36> GHC.Prim.retry#) @ env_a3hT)
`cast` (Sym (GHC.Conc.Sync.N:STM[0] <env_a3hT>_R)
:: ((GHC.Prim.State# GHC.Prim.RealWorld
-> (# GHC.Prim.State# GHC.Prim.RealWorld,
env_a3hT #)) :: *)
~R#
(STM env_a3hT :: *)))
(GHC.Types.I# 0#)
}
}}}
Note how the analyzer somehow concludes hyperstrict demands for all of the
binders bound by the case analysis of the `Vector` despite the fact that
the whole thing consists of nothing more than a call to `foldlM_loop_a45q`
which does not itself diverge.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13916#comment:17>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list