
#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 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 slyfox): Even less extensions, less external haskell module dependencies: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} module C () where import qualified GHC.Types as C (Constraint) class Category (cat :: k -> k -> *) where id :: cat a a (.) :: cat b c -> cat a b -> cat a c data Dict :: C.Constraint -> * where Dict :: a => Dict a newtype C2D a b = Sub (a => Dict b) instance Category C2D where id = Sub Dict f . g = Sub (sub (sub Dict f) g) sub :: a => (b => r) -> (C2D a b) -> r sub r (Sub Dict) = r {- $ inplace/bin/ghc-stage2 -fforce-recomp -c C.hs -O0 WARNING: file compiler/stgSyn/CoreToStg.hs, line 250 $fCategoryConstraint:- True False -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11562#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler