
#11562: WARNING: file compiler/stgSyn/CoreToStg.hs, line 250: $fCategoryConstraint:- True False -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Tried to debug unrelated build failure of constraints-0.4.1.3 and found this in today's ghc-HEAD: {{{ $ inplace/bin/ghc-stage2 -fforce-recomp -c C.hs -O0 WARNING: file compiler/stgSyn/CoreToStg.hs, line 250 $fCategoryConstraint:- True False }}} {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE GADTs #-} module C () where import Control.Category import GHC.Types (Constraint) data Dict :: Constraint -> * where Dict :: a => Dict a infixr 9 :- newtype a :- b = Sub (a => Dict b) instance Category (:-) where id = refl (.) = trans infixl 1 \\ (\\) :: a => (b => r) -> (a :- b) -> r r \\ Sub Dict = r trans :: (b :- c) -> (a :- b) -> a :- c trans f g = Sub (Dict \\ f \\ g) refl :: a :- a refl = Sub Dict {- $ inplace/bin/ghc-stage2 -fforce-recomp -c C.hs -O0 WARNING: file compiler/stgSyn/CoreToStg.hs, line 250 $fCategoryConstraint:- True False -} }}} Original file it was factored out is: https://github.com/ekmett/constraints/blob/c550b7653e88d58882873d11f05538d78... Might be a result of Phab:D1889 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11562 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler