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

#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

#12639: Inconsistent treatment of FlexibleInstances and MPTCs with standard vs. flexible deriving -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I have some opinions on both of these suggestions, but I'll refrain from posting them here. Before that, if you really want to see these changes make it into GHC, you should propose them as a post to the [https://mail.haskell.org/mailman/listinfo/ghc-devs GHC devs mailing list]. In particular, your second proposed item would cause a //lot// of code in the wild to break, so we need to discuss it more thoroughly to ensure it's a breakage we want to endorse. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12639#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12639: Inconsistent treatment of FlexibleInstances and MPTCs with standard vs. flexible deriving -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12639#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC