[GHC] #15772: Strange constraint error that disappears when adding another top-level declaration

#15772: Strange constraint error that disappears when adding another top-level declaration -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this program: {{{#!hs {-# LANGUAGE DataKinds, TypeFamilies, TypeOperators, UndecidableInstances #-} module CURepro where import Data.Kind data NP (f :: Type -> Type) (xs :: [Type]) type family Curry (f :: Type -> Type) (xs :: [Type]) (r :: Type) (a :: Type) :: Constraint where Curry f xs r (f x -> a) = (xs ~ (x : Tail xs), Curry f (Tail xs) r a) Curry f xs r a = (xs ~ '[], r ~ a) type family Tail (a :: [Type]) :: [Type] where Tail (_ : xs) = xs uncurry_NP :: (Curry f xs r a) => (NP f xs -> r) -> a uncurry_NP = undefined fun_NP :: NP Id xs -> () fun_NP = undefined newtype Id a = MkId a -- test1 :: () -- test1 = uncurry_NP fun_NP (MkId 5) test2 :: () test2 = uncurry_NP fun_NP (MkId True) (MkId 5) (MkId True) }}} With GHC 8.6.1 (and also 8.4.3), this produces the following error message: {{{ CURepro.hs:27:9: error: • Couldn't match type ‘Tail t0’ with ‘Bool : Tail (Tail t0)’ arising from a use of ‘uncurry_NP’ The type variable ‘t0’ is ambiguous • In the expression: uncurry_NP fun_NP (MkId True) (MkId 5) (MkId True) In an equation for ‘test2’: test2 = uncurry_NP fun_NP (MkId True) (MkId 5) (MkId True) | 27 | test2 = uncurry_NP fun_NP (MkId True) (MkId 5) (MkId True) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} However, uncommenting the definition of `test1` makes the whole program check without error! I think both versions of the program should be accepted. I've tried to extract this from a much larger failing example, but did not manage to make it any smaller than this. In particular, the fact that `NP` is parameterised over a type constructor `f` seems to be somehow essential to trigger this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15772 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15772: Strange constraint error that disappears when adding another top-level declaration -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15772#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15772: Strange constraint error that disappears when adding another top-level declaration -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * cc: adamgundry (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15772#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15772: Strange constraint error that disappears when adding another top-level declaration -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This appears to be a regression, since this program typechecks in GHC 8.0, but not in 8.2 and later. (It also typechecks in 7.8 and 7.10, provided you make some tweaks to support older GHCs). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15772#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15772: Strange constraint error that disappears when adding another top-level declaration -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): This looks subtle. I think that `Note [FunEq occurs-check principle]` may be implicated, and I'm worried that there's something subtle about solve order. FWIW, `-fdefer-type-errors` forces implications to be built more aggressively, and that too makes it work. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15772#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15772: Strange constraint error that disappears when adding another top-level declaration -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I think your hunch about `Note [FunEq occurs-check principle]` is right on the mark, since commit 1eec1f21268af907f59b5d5c071a9a25de7369c7 (`Another major constraint-solver refactoring`), which introduced that Note, is the first commit to demonstrate this bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15772#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15772: Strange constraint error that disappears when adding another top-level declaration -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kosmikus): Thanks Ryan. I can confirm that my original test case works as expected with GHC 8.0. In addition, it also seems to typecheck ''much'' faster. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15772#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC