[GHC] #12694: GHC HEAD no longer reports inaccessible code

#12694: GHC HEAD no longer reports inaccessible code -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | 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: -------------------------------------+------------------------------------- Given this A.hs: {{{ {-# LANGUAGE GADTs #-} module A where f :: Bool ~ Int => a -> b f x = x }}} I get: {{{ ezyang@sabre:~$ ghc-head --version The Glorious Glasgow Haskell Compilation System, version 8.1.20161010 ezyang@sabre:~$ ghc-head --make A.hs [1 of 1] Compiling A ( A.hs, A.o ) A.hs:4:1: warning: [-Woverlapping-patterns] Pattern match is redundant In an equation for ‘f’: f x = ... }}} In contrast: {{{ ezyang@sabre:~$ ghc-8.0 --make A.hs [1 of 1] Compiling A ( A.hs, A.o ) A.hs:3:6: error: • Couldn't match type ‘Bool’ with ‘Int’ Inaccessible code in the type signature for: f :: Bool ~ Int => a -> b • In the ambiguity check for ‘f’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature: f :: Bool ~ Int => a -> b }}} Is this expected? I'd expect at least a warning! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12694 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12694: GHC HEAD no longer reports inaccessible code -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | 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 simonpj): See #12466 for an extended discussion. I wish I had a better solution. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12694#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12694: GHC HEAD no longer reports inaccessible code -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | 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 ezyang): I would suggest putting it under a `-W` option but you've mentioned it in the ticket; in any case, I doubt it will help anyone who doesn't already know what's going on. I ran into this because I was debugging something that was marked insoluble that wasn't (very confusing! At least the "warning" is printed in `ddump-tc-trace`.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12694#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12694: GHC HEAD no longer reports inaccessible code -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | 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 simonpj): I'd missed this. Actually it turns out that it's already fixed in 8.0. What happens is this: * `(t1 ~ t2)` is actually a class constraint (homogeneous equality), with superclass `(t1 ~~ t2)` (heterogeneous equality). * `(t1 ~~ t2)` is actuall a class constraint with superclass `(t1 ~# t2)` (true nominal type equality). * The `oclose` function in `FunDeps` already takes account of true nominal equality. Iavor appears to have put this in as part of fe61599ffebb27924c4beef47b6237542644f3f4. To the code above I added {{{ data IndexOf a b data ElementByIdx a b class Measurable a data GraphBuilderT g (m :: * -> *) a data Ptr a b }}} And then your example compiles fine. More precisely, in addition to incorrectly reporting the coverate error, GHC 7.10 correctly says {{{ T10778.hs:18:10: Couldn't match type ‘a’ with ‘ElementByIdx (IndexOf a cont) cont’ ‘a’ is a rigid type variable bound by an instance declaration: (PtrFrom idx i, Appendable cont idx a, HasContainer g cont, Monad m) => RefBuilder3 a (GraphBuilderT g m) (Ptr i) at T10778.hs:18:10 Inaccessible code in an instance declaration: (PtrFrom idx i, Appendable cont idx a, HasContainer g cont, Monad m) => RefBuilder3 a (GraphBuilderT g m) (Ptr i) In the ambiguity check for an instance declaration: forall a g (m :: * -> *) i idx cont. (PtrFrom idx i, Appendable cont idx a, HasContainer g cont, Monad m) => RefBuilder3 a (GraphBuilderT g m) (Ptr i) }}} But because of #12694, #12466, it now says (much more confusingly) {{{ T10778.hs:20:5: warning: [-Woverlapping-patterns] Pattern match is redundant In an equation for ‘mkRef3’: mkRef3 = ... }}} The pattern match checker sees that the entire instance is inaccessible, and so reports that the (only) equation for `mkRef3` is redundant. See #12694 for a simpler case. Do you agree that the instance is in fact inaccessible? Want to change the example to something more sensible to add as a regression test? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12694#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12694: GHC HEAD no longer reports inaccessible code -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12466, #11066, | Differential Rev(s): #13766 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => PatternMatchWarnings * related: => #12466, #11066, #13766 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12694#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12694: GHC HEAD no longer reports inaccessible code -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12466, #11066, | Differential Rev(s): #13766 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): It seems that GHC 8.2 and later report this as inaccessible code again: {{{ $ /opt/ghc/8.4.3/bin/ghc Bug.hs [1 of 1] Compiling A ( Bug.hs, Bug.o ) Bug.hs:4:7: error: • Could not deduce: a ~ b from the context: Bool ~ Int bound by the type signature for: f :: forall a b. (Bool ~ Int) => a -> b at Bug.hs:3:1-25 ‘a’ is a rigid type variable bound by the type signature for: f :: forall a b. (Bool ~ Int) => a -> b at Bug.hs:3:1-25 ‘b’ is a rigid type variable bound by the type signature for: f :: forall a b. (Bool ~ Int) => a -> b at Bug.hs:3:1-25 • In the expression: x In an equation for ‘f’: f x = x • Relevant bindings include x :: a (bound at Bug.hs:4:3) f :: a -> b (bound at Bug.hs:4:1) | 4 | f x = x | ^ }}} Perhaps this can be closed, then? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12694#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC