
#13027: Core lint errors compiling containers HEAD with GHC HEAD -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: dfeuer (added) Comment: I'm not entirely sure if this is a GHC bug. For one thing, you don't need GHC HEAD to reproduce this - you could just as well use GHC 8.0.1. Here is a minimized test case (taken from the source code of `containers` HEAD): {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE MagicHash #-} module Containers (insert) where import GHC.Exts (isTrue#, reallyUnsafePtrEquality#) data Set a = Bin {-# UNPACK #-} !Size !a !(Set a) !(Set a) | Tip type Size = Int insert :: Ord a => a -> Set a -> Set a insert = go where go :: Ord a => a -> Set a -> Set a go !x Tip = Bin 1 x Tip Tip go !x t@(Bin sz y l r) = case compare x y of LT | l' `ptrEq` l -> t | otherwise -> undefined -- balanceL y l' r where !l' = go x l GT | r' `ptrEq` r -> t | otherwise -> undefined -- balanceR y l r' where !r' = go x r EQ | x `ptrEq` y -> t | otherwise -> Bin sz x l r {-# INLINABLE insert #-} ptrEq :: a -> a -> Bool ptrEq x y = isTrue# (reallyUnsafePtrEquality# x y) {-# INLINE ptrEq #-} }}} If you compile this with `/opt/ghc/8.0.1/bin/ghc Containers.hs -dcore-lint -O2`, you'll get a very similar Core Lint error. The culprit seems to be the suspicious use of `reallyUnsafePtrEquality#` in `ptrEq`. Any thoughts on this, David? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13027#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler