[GHC] #12639: Inconsistent treatment of FlexibleInstances and MPTCs with standard vs. flexible deriving

GHC ghc-devs at haskell.org
Wed Sep 28 22:33:31 UTC 2016


#12639: Inconsistent treatment of FlexibleInstances and MPTCs with standard vs.
flexible deriving
-------------------------------------+-------------------------------------
           Reporter:  dfeuer         |             Owner:
               Type:  feature        |            Status:  new
  request                            |
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Given `{-# LANGUAGE GeneralizedNewtypeDeriving #-}`, I can write

 {{{#!hs
 import Control.Monad.State.Strict

 newtype Foo s m a = Foo (StateT s m a)
   deriving (Functor, Applicative, Monad, MonadState s)
 }}}

 However, if I want to use `StandaloneDeriving` to make the `MonadState`
 instance more explicit,

 {{{#!hs
 deriving instance Monad m => MonadState s (Foo s m)
 }}}

 I suddenly need to add `FlexibleInstances` and `MultiParamTypeClasses`.

 In my personal opinion, the most sensible way to handle this is to change
 two things in two different directions:

 1. Allow MPTC instance declarations (but not class declarations) without
 `MultiParamTypeClasses`.

 2. Require `FlexibleInstances` for standard deriving clauses when they
 would be required for standalone deriving declarations.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12639>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list