[GHC] #15398: GADT deriving Ord generates inaccessible code in a pattern with constructor.

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. --------------------------------------+--------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Keywords: | Operating System: MacOS X Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- I added a second type parameter `k` to a GADT `Zone` and found that when deriving Ord with standalone deriving, the generated code has errors in ghc-8.2.2. There's a reproduction repo for this; https://github.com/BlockScope/zone-inaccessible-code-deriving-ord. I found I needed at least three constructors in `Zone` to get this error. #8128 seemed relevant for being about standalone deriving of a GADT. That being fixed, I tried with ghc-head that I built from source. With this version I found that the same code faults exist in the generated code but are treated as warnings by ghc-8.7.2 {{{
inplace/bin/ghc-stage2 --version The Glorious Glasgow Haskell Compilation System, version 8.7.20180715 }}}
{{{#!hs {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE StandaloneDeriving #-} module Flight.Zone where newtype Radius a = Radius a deriving (Eq, Ord) data CourseLine data OpenDistance data EndOfSpeedSection -- TODO: Remove standalone deriving Eq & Ord for empty data after GHC 8.4.1 -- SEE: https://ghc.haskell.org/trac/ghc/ticket/7401 deriving instance Eq CourseLine deriving instance Eq OpenDistance deriving instance Eq EndOfSpeedSection deriving instance Ord CourseLine deriving instance Ord OpenDistance deriving instance Ord EndOfSpeedSection data Zone k a where Point :: (Eq a, Ord a) => Zone CourseLine a Vector :: (Eq a, Ord a) => Zone OpenDistance a Conical :: (Eq a, Ord a) => Radius a -> Zone EndOfSpeedSection a deriving instance Eq a => Eq (Zone k a) deriving instance (Eq a, Ord a) => Ord (Zone k a) }}} The error; {{{ /.../Zone.hs:25:1: error: • Couldn't match type ‘OpenDistance’ with ‘CourseLine’ Inaccessible code in a pattern with constructor: Point :: forall a. (Eq a, Ord a) => Zone CourseLine a, in a case alternative • In the pattern: Point {} In a case alternative: Point {} -> GT In the expression: case b of Point {} -> GT Vector -> EQ _ -> LT When typechecking the code for ‘compare’ in a derived instance for ‘Ord (Zone k a)’: To see the code I am typechecking, use -ddump-deriv | 25 | deriving instance (Eq a, Ord a) => Ord (Zone k a) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ /.../Zone.hs:25:1: error: • Couldn't match type ‘OpenDistance’ with ‘CourseLine’ Inaccessible code in a pattern with constructor: Point :: forall a. (Eq a, Ord a) => Zone CourseLine a, in a case alternative • In the pattern: Point {} In a case alternative: Point {} -> False In the expression: case b of Point {} -> False Vector -> False _ -> True When typechecking the code for ‘<’ in a derived instance for ‘Ord (Zone k a)’: To see the code I am typechecking, use -ddump-deriv | 25 | deriving instance (Eq a, Ord a) => Ord (Zone k a) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} The generated code with these replacements; {{{ :%s/GHC\.Classes\.// :%s/GHC\.Types\.// :%s/Flight\.Zone\.// }}} {{{#!hs instance (Eq a, Ord a) => Ord (Zone k a) where compare a_a2hw b_a2hx = case a_a2hw of Point -> case b_a2hx of Point -> EQ _ -> LT Vector -> case b_a2hx of Point {} -> GT Vector -> EQ _ -> LT Conical a1_a2hy -> case b_a2hx of Conical b1_a2hz -> (a1_a2hy `compare` b1_a2hz) _ -> GT (<) a_a2hA b_a2hB = case a_a2hA of Point -> case b_a2hB of Point -> False _ -> True Vector -> case b_a2hB of Point {} -> False Vector -> False _ -> True Conical a1_a2hC -> case b_a2hB of Conical b1_a2hD -> (a1_a2hC < b1_a2hD) _ -> False (<=) a_a2hE b_a2hF = not ((<) b_a2hF a_a2hE) (>) a_a2hG b_a2hH = (<) b_a2hH a_a2hG (>=) a_a2hI b_a2hJ = not ((<) a_a2hI b_a2hJ) instance Eq a => Eq (Zone k a) where (==) (Point) (Point) = True (==) (Vector) (Vector) = True (==) (Conical a1_a2hK) (Conical b1_a2hL) = ((a1_a2hK == b1_a2hL)) (==) _ _ = False (/=) a_a2hM b_a2hN = not ((==) a_a2hM b_a2hN) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. ---------------------------------+-------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by RyanGlScott): I'm not sure what exactly the bug is here. The generated code genuinely has inaccessible cases, and since GHC 8.6+, this is a warning instead of an error, so you can now actually use this code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. ---------------------------------+-------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by philderbeast): Do those warnings serve an intended purpose and is there no way for GHC to do the derivation without the generated code having warnings and still be correct? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. ---------------------------------+-------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by RyanGlScott): Replying to [comment:2 philderbeast]:
Is there no way for GHC to do the derivation without the generated code having warnings?
In theory this would be possible, but it would significantly complicate the algorithm that `deriving Ord` uses to generate code. Currently, the algorithm is implemented as a pure function over the abstract syntax tree, but changing it to not generate inaccessible cases would require it to propagate typing information in a non-trivial way. I'm skeptical that such a large change would pay its weight, especially since the workaround (just use `-Wno-inaccesible-code`) is so simple. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. ---------------------------------+-------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by simonpj): Maybe the `deriving` mechanism should somehow add that flag itself. It already switches off a number of warnings -- why not this one too? (With a Note, along the lines of comment:3, to explain.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. ---------------------------------+-------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by RyanGlScott): I have no objection to the proposal in comment:4. That being said, it's far from clear to me how to implement it. Unlike other flags that `deriving` toggles, which primarily live in the renamer, `-Winaccessible- code` warnings are emitted during error reporting, which happens after typechecking. What's more, when `-Winaccessible-code` warnings are created, GHC only has access to an `Implication`, which gives no indication about whether it was created from derived code or not... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. ---------------------------------+-------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by simonpj):
it's far from clear to me how to implement it
I think the right thing to do is probably to capture the `DynFlags` in an `Implication`. We already capture the `TcLclEnv` in `ic_env`; capturing the `DynFlags` too would be easy. Then the `DynFlags` would be conveniently to hand when generating the innaccessible-code warning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => deriving, PatternMatchWarnings -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I don't understand what `DynFlags` has to do with anything. `-Wno- inaccesible-code` already disables these warnings. I thought you were requesting that we //never// emit inaccessible code warnings for derived code (regardless of whether `-Winaccessible-code` is enabled or not). That's what I don't know how to do. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
I thought you were requesting that we never emit inaccessible code warnings for derived code (regardless of whether -Winaccessible-code is enabled or not).
Correct. So if we switch off `-Winaccessible-code` when typechecking derived code, that would do job. And we try to; see {{{ -- Now GHC-generated derived bindings, generics, and selectors -- Do not generate warnings from compiler-generated code; -- hence the use of discardWarnings tc_envs@(tcg_env, tcl_env) <- discardWarnings (tcTopBinds deriv_binds deriv_sigs) ; }}} in `TcRnDriver`. Unfortunately the `dicardWarnings` only discards warnings generated while doing `tcTopBinds`. But `tcTopBinds` also creates a bunch of constraints that don't "see" that `discardWarnings`. If instead switched off the warning `DynFlags`, and captured the `DynFlags` in an implication, the warning suppression would still work on the constraints. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Ah, I suppose that would work. There's one annoying hiccup, though: what should we name this new field in `Implication` of type `DynFlags`? Unfortunately, `ic_dflags` is already taken by `InteractiveContext`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
Ah, I suppose that would work.
Yes.. I like the principle that we are preserving, in the constraint tree, the environment in force when the implication was built, so that delaying solving the constraint (rather than somehow solving it immediately) doesn't change the behaviour.
Unfortunately, ic_dflags is already taken by InteractiveContext.
Ha ha! I suppose the alternatives are * Use the same name, on the grounds that you'll seldom, if ever, want both in scope at the same time. Downside: grep won't find the right set of uses -- I used grep quite a lot * Use `implic_dflags` or something, with a short explanation about why it's different. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:11 simonpj]:
* Use the same name, on the grounds that you'll seldom, if ever, want both in scope at the same time.
Ah, if only. I actually did try adding a field named `ic_dflags` to `Implication`, and it resulted in compilation errors due to conflicting with `InteractiveContext`'s `ic_dflags` in certain modules, so this is a problem in practice.
* Use `implic_dflags` or something, with a short explanation about why it's different.
I'll go with that idea. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8128 #8740 | Differential Rev(s): Phab:D4993 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4993 * related: => #8128 #8740 Comment: A WIP patch for this is at Phab:D4993. I haven't added any documentation yet, since I'm not sure that this design is the one that Simon intended. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8128 #8740 | Differential Rev(s): Phab:D4993 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): If we really want to capture the environment in an implication, we could just store the `Env TcGblEnv TcLclEnv`, as retrieved by `getEnv`. We might want to do this in `CtLoc`, too, for similar reasons. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with
constructor.
-------------------------------------+-------------------------------------
Reporter: philderbeast | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.2.2
Resolution: | Keywords: deriving,
| PatternMatchWarnings
Operating System: MacOS X | Architecture: x86_64
| (amd64)
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #8128 #8740 | Differential Rev(s): Phab:D4993
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Krzysztof Gogolewski

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8128 #8740 | Differential Rev(s): Phab:D4993 Wiki Page: | -------------------------------------+------------------------------------- Changes (by monoidal): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15398: GADT deriving Ord generates inaccessible code in a pattern with constructor. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: deriving, | PatternMatchWarnings Operating System: MacOS X | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8128 #8740 | Differential Rev(s): Phab:D4993 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 8bed140099f8ab78e3e728fd2e50dd73d7210e84. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15398#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC