
#16246: GHC HEAD-only Core Lint error with unboxed equality (Non-CoVar has coercion type) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #15648 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Simpler example: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Bug where import Foo (ueqT) f :: $ueqT a b -> $ueqT a b f x = x }}} {{{ $ ~/Software/ghc5/inplace/bin/ghc-stage2 --interactive Bug.hs -dcore-lint GHCi, version 8.7.20190115: https://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 2] Compiling Foo ( Foo.hs, interpreted ) [2 of 2] Compiling Bug ( Bug.hs, interpreted ) *** Core Lint errors : in result of Desugar (before optimization) *** Bug.hs:7:3: warning: [in body of lambda with binder x_a4vD :: a_a4vV ~# b_a4vW] Non-CoVar has coercion type x_a4vD :: a_a4vV ~# b_a4vW *** Offending Program *** Rec { $trModule :: Module [LclIdX] $trModule = Module (TrNameS "main"#) (TrNameS "Bug"#) f :: forall a b. (a ~# b) -> a ~# b [LclIdX] f = \ (@ a_a4vV) (@ b_a4vW) (x_a4vD :: a_a4vV ~# b_a4vW) -> break<0>() x_a4vD end Rec } *** End of Offense *** }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16246#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler