[GHC] #11444: 8.0 rc1 panics in applyTypeToArgs
GHC
ghc-devs at haskell.org
Thu Jan 12 00:43:20 UTC 2017
#11444: 8.0 rc1 panics in applyTypeToArgs
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc1
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 RyanGlScott):
To be precise, here's the portion of `atomic-primops` that fails with a
Core Lint error:
{{{#!hs
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
module AtomicPrimops where
import GHC.Exts
{-# NOINLINE ptrEq #-}
ptrEq :: a -> a -> Bool
ptrEq !x !y = I# (reallyUnsafePtrEquality# x y) == 1
}}}
{{{
$ ~/Software/ghc3/inplace/bin/ghc-stage2 -fforce-recomp -dcore-lint -O2
Bug.hs[1 of 1] Compiling AtomicPrimops ( Bug.hs, Bug.o )
*** Core Lint errors : in result of Float out(FOS {Lam = Just 0,
Consts = True,
OverSatApps = False})
***
<no location info>: warning:
In the expression: I# (reallyUnsafePtrEquality# @ a x_a2OY y_a2OZ)
This argument does not satisfy the let/app invariant:
reallyUnsafePtrEquality# @ a x_a2OY y_a2OZ
*** Offending Program ***
lvl_s3TE :: Int
[LclId]
lvl_s3TE = I# 1#
ptrEq [InlPrag=NOINLINE] :: forall a. a -> a -> Bool
[LclIdX, Arity=2]
ptrEq =
\ (@ a_a3I6) (x_a2OY :: a) (y_a2OZ :: a) ->
case x_a2OY of x_X2P2 { __DEFAULT ->
case y_a2OZ of y_X2P4 { __DEFAULT ->
eqInt (I# (reallyUnsafePtrEquality# @ a x_a2OY y_a2OZ)) lvl_s3TE
}
}
$trModule_s3TA :: TrName
[LclId]
$trModule_s3TA = TrNameS "main"#
$trModule_s3TB :: TrName
[LclId]
$trModule_s3TB = TrNameS "AtomicPrimops"#
$trModule :: Module
[LclIdX]
$trModule = Module $trModule_s3TA $trModule_s3TB
*** End of Offense ***
<no location info>: error:
Compilation had errors
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11444#comment:9>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list