[GHC] #14916: Missing checks when deriving special classes
GHC
ghc-devs at haskell.org
Tue Mar 13 19:30:20 UTC 2018
#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
More information about the ghc-tickets
mailing list