[GHC] #14916: Missing checks when deriving special classes

#14916: Missing checks when deriving special classes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- For the following program {{{ {-# LANGUAGE DeriveAnyClass #-} module T where import Data.Coerce import Data.Typeable data A = MkA deriving ((~) A) data B = MkB deriving (Coercible B) }}} the deriving clause for `A` is accepted without complaints, and the deriving clause for `B` fails with the following error: {{{ T.hs:8:24: error: Top-level bindings for unlifted types aren't allowed: | 8 | data B = MkB deriving (Coercible B) | ^^^^^^^^^^^ }}} Corresponding standalone deriving instances trigger errors saying "Manual instances of this class are not permitted". Probably similar error messages should be triggered here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14916 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14916: Missing checks when deriving special classes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14916#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14916: Missing checks when deriving special classes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4501 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4501 Comment: Luckily, fixing this is quite straightforward by using `checkValidInstHead`, which is what Phab:D4501 accomplishes. One thing that's interesting about `checkValidInstHead` is that is also does validity checks for `FlexibleInstances` and `MultiParamTypeClasses`. This means that using `checkValidInstHead`, unaltered, would result in this program, which is currently accepted by GHC: {{{#!hs {-# LANGUAGE GeneralizedNewtypeDeriving #-} module T where import Control.Monad.Reader newtype MyReader a = MyReader (Int -> a) deriving ( Functor, Applicative, Monad , MonadReader Int ) }}} Being rejected due to not enabling `FlexibleInstances` or `MultiParamTypeClasses`, since it generates `instance MonadReader Int MyReader`. I decided to err on the side of avoiding unnecessary breakage and tweaked `checkValidInstHead` so as to disable these checks for `deriving` clauses (just as we do for `SPECIALISE instance` pragmas today). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14916#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14916: Missing checks when deriving special classes
-------------------------------------+-------------------------------------
Reporter: kosmikus | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.2.2
checker) |
Resolution: | Keywords: Deriving
Operating System: Unknown/Multiple | Architecture:
Type of failure: Poor/confusing | Unknown/Multiple
error message | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4501
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14916: Missing checks when deriving special classes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: Deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4501 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.4.2 Old description:
For the following program {{{ {-# LANGUAGE DeriveAnyClass #-} module T where
import Data.Coerce import Data.Typeable
data A = MkA deriving ((~) A) data B = MkB deriving (Coercible B) }}} the deriving clause for `A` is accepted without complaints, and the deriving clause for `B` fails with the following error: {{{ T.hs:8:24: error: Top-level bindings for unlifted types aren't allowed: | 8 | data B = MkB deriving (Coercible B) | ^^^^^^^^^^^ }}}
Corresponding standalone deriving instances trigger errors saying "Manual instances of this class are not permitted". Probably similar error messages should be triggered here.
New description: For the following program {{{#!hs {-# LANGUAGE DeriveAnyClass #-} module T where import Data.Coerce import Data.Typeable data A = MkA deriving ((~) A) data B = MkB deriving (Coercible B) }}} the deriving clause for `A` is accepted without complaints, and the deriving clause for `B` fails with the following error: {{{ T.hs:8:24: error: Top-level bindings for unlifted types aren't allowed: | 8 | data B = MkB deriving (Coercible B) | ^^^^^^^^^^^ }}} Corresponding standalone deriving instances trigger errors saying "Manual instances of this class are not permitted". Probably similar error messages should be triggered here. -- Comment: Merged to `ghc-8.4`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14916#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC