[GHC] #11562: WARNING: file compiler/stgSyn/CoreToStg.hs, line 250: $fCategoryConstraint:- True False

#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

#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):
Might be a result of Phab:D1889 Same warning exists in current ghc-8.0 as well thus something else is happening here.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11562#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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 Simon Peyton Jones

#11562: WARNING: file compiler/stgSyn/CoreToStg.hs, line 250: $fCategoryConstraint:- True False -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T11562 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => simplCore/should_compile/T11562 * resolution: => fixed Comment: Thanks for a nice small example. The failure was benign (so barely worth merging to 8.0) but the fix is easy. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11562#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC