[GHC] #10577: Use empty cases where appropriate when deriving instances for empty types

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- In some sense the correct instance for {{{ data X deriving instance Eq X }}} is not (what GHC currently produces) {{{ instance Eq X where (==) = error "Void ==" }}} but rather {{{ instance Eq X where a == b = case a of {} -- using the EmptyCase extension }}} See comments starting at ticket:7401#comment:28 for justification. The list of classes that GHC can currently derive is * Eq, Ord, Enum, Bounded, Show, Read (Haskell 2010 Report) * Functor, Foldable, Traversable, Typeable, Generic, Data, "any class" (`-XDerive*`) Deriving Enum and Bounded is not currently allowed for empty data types. The `showList` method of Show and the whole Read instance are easy and already implemented correctly. All the remaining methods of Haskell 2010 derivable type classes take at least one argument of the instance head type `a`. I propose that all these methods be defined as an empty case on the first such argument. Similarly in Functor, Foldable and Traversable, each method has a single argument of the form `t _` where `t :: * -> *` is the instance head type, and the method should be defined as an empty case on that argument. In all these cases so far, the derived methods for a non-empty type would, at the outermost level, be a (non-empty) case on that first argument, or the equivalent (series of pattern matches, one for each constructor), so the use of an empty case is justified for an empty type. Typeable does not care about the values or even the kind of the type at all, so it's not relevant here. Generic and especially Data are above my pay grade, but generally I expect that methods which are normally defined by case analysis on an argument of the instance head type should be defined by an empty case, and methods that (sometimes) produce a value of the instance head type should do whatever they normally do when unable to produce such a value (like `readsPrec` returning an empty list, or `read` calling `error` (if `read` were actually a method of `Read`)). `DeriveAnyClass` doesn't generate any new code, so like Typeable it's not relevant. None of this behavior is specified by the Haskell 2010 Report, which disallows deriving any class for a type with no constructors; but see #7401. So, we are entitled to do what we think is best here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by osa1): * cc: omeragacan@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by osa1): One thing to note: We have two ways to derive instances, using `deriving (..)` syntax and StandaloneDeriving. If we want to make changes described here and also keep this two methods of instance deriving consistent with each other(currently they're not), it means breaking change. IMHO, StandaloneDeriving and `deriving (..)` should work the same, so we should either do this breaking change or merge https://phabricator.haskell.org/D978. Also, I'm not sure how relevant it is, but `Data.Void.Void`s methods are currently not forcing the arguments. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13117, #7401 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * related: => #13117, #7401 Comment: This is fixed for `Functor`, `Foldable`, `Traversable`, `Generic`, and `Generic1`. I believe some `Data` methods already do the right thing here, but I don't know if they all do. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13117, #7401 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13117, #7401 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13117, #7401 | Differential Rev(s): Phab:D4047 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4047 Comment: Phab:D4047 fixes this ticket in the sense that more classes now use `EmptyCase` in derived code for empty data types (namely, `Show`, `Lift`, and `Data`). Note that `Eq` and `Ord` are not among these classes—refer to the [https://github.com/ghc-proposals/ghc- proposals/blob/dbf516088d2839432c9568c3d1f7ae28d46aeb43/proposals/0006 -deriving-empty.rst proposal] which Phab:D4047 implements. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13117, #7401 | Differential Rev(s): Phab:D4047 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I still think there should be a "few examples where folks tied knots with fixed points to get inhabitants of Void" seeing as that is the primary motivation for this implementation. They are good for tests and notes even though I accept I will find them dubious. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13117, #7401 | Differential Rev(s): Phab:D4047 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm not sure if you're asking me to add something here or in the Diff. If the latter, are you asking for a test case to see if something like this evaluates to `True`? {{{#!hs {-# LANGUAGE EmptyDataDeriving #-} module Main where import Data.Function data Foo deriving Eq foo1 :: Foo foo1 = fix id foo2 :: Foo foo2 = let x = y y = x in y main :: IO () main = print (foo1 == foo2) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10577: Use empty cases where appropriate when deriving instances for empty types
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords: deriving
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #13117, #7401 | Differential Rev(s): Phab:D4047
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13117, #7401 | Differential Rev(s): Phab:D4047 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10577#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC