[GHC] #14916: Missing checks when deriving special classes
GHC
ghc-devs at haskell.org
Wed Mar 14 00:15:03 UTC 2018
#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
More information about the ghc-tickets
mailing list