[GHC] #8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving?

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? ------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- Nathan Howell posts this code: {{{ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} -- Uncomment to compile on GHC 7.8 -- {-# LANGUAGE ImpredicativeTypes #-} module Repro where import Control.Monad.Trans.Cont import Control.Monad.Trans.State.Lazy newtype AnyContT m a = AnyContT { unAnyContT :: forall r . ContT r m a } class MonadAnyCont b m where anyContToM :: (forall r . (a -> b r) -> b r) -> m a instance MonadAnyCont b (AnyContT m) where anyContToM _ = error "foo" data DecodeState = DecodeState newtype DecodeAST a = DecodeAST { unDecodeAST :: AnyContT (StateT DecodeState IO) a } deriving (MonadAnyCont IO) }}} Compiling on HEAD produces {{{ [1 of 1] Compiling Repro ( repro.hs, interpreted ) repro.hs:24:13: Cannot instantiate unification variable ‛b0’ with a type involving foralls: (forall r. (a1 -> IO r) -> IO r) -> DecodeAST a1 Perhaps you want ImpredicativeTypes In the expression: GHC.Prim.coerce (anyContToM :: (forall (r :: *). (a -> IO r) -> IO r) -> AnyContT (StateT DecodeState IO) a) :: forall (a :: *). (forall (r :: *). (a -> IO r) -> IO r) -> DecodeAST a In an equation for ‛anyContToM’: anyContToM = GHC.Prim.coerce (anyContToM :: (forall (r :: *). (a -> IO r) -> IO r) -> AnyContT (StateT DecodeState IO) a) :: forall (a :: *). (forall (r :: *). (a -> IO r) -> IO r) -> DecodeAST a Failed, modules loaded: none. }}} Two questions: 1. Should we require users to specify !ImpredicativeTypes here? Or, should the !GeneralizedNewtypeDeriving mechanism (which sometimes is impredicative) just assume the extension? 2. Can we improve the error message? I'd like to note that the original example really ''does'' require impredicativity -- the question is whether and how to bother the user with this technicality. Small program note: I've done a lot of stuff with !GeneralizedNewtypeDeriving lately but am on holiday until Jan. 6, so don't expect responses! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by nomeata): * cc: mail@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by simonpj): * cc: sweirich@… (added) Comment: We really want explicit type application here (#4466, #5296). The point is that we want to say "instantiate `coerce` at these particular types", which happen in this case to be polymorphic. (There is a good reason to be suspicious about filling in unification variables with polytypes, but explicit type application would mean that didn't happen.) Stephanie has a student working on this, I believe. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): Yes, absolutely, explicit type application would make all of this much easier. But, I believe we can still fix this bug without it, once we have some design decisions about the questions I posed originally. As for question 1: I think it's safe to turn on !ImpredicativeTypes over the code produced by GND. This would make using GND easier, and I don't want to bother users with this technicality. As for question 2: In general, I'm a little worried about error messages that mention `coerce` yet refer to code that patently does ''not'' mention `coerce`. If we can't get rid of the `coerce`, could we add some extra context describing the use of GND and perhaps suggesting `-ddump-deriv`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): I thought I had got rid of `coerce` in error messages when doing GND (#8567)... I’ll have to look. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): It should have been [95ba5d81/ghc]: We check at deriving time that the `Coercible` instances are solvable, and report an appropriate error message; any time that there is an error message mentioning `coercible` (or deriv-generated code in general), that is a bug. So unless turning on `ImpredicativeTypes` for deriv’ed code solve the problem, we need to check for this already at deriving phase, and report an error. What would that error say? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): `-XImpredicativeTypes` it not a very well-defined flag. It might make this program compile, and I think it'd be safe to enable it for GND- produced code. But it has had no love for many years. Do give it a try; which would make Q2 moot. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by nomeata): Looking into Q1. There is some code temporarily enabling certain extension (`EmptyCase`, `ScopedTypeVariables` and `KindSignatures`) in `renameDeriv`, but these just affect the renamer; the error message we see occurs later, and I don’t see how we can enable `ImpredicativeTypes` in a scoped way, i.e. only applying to the code generated by GND. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): Bah. I was thinking of exactly that code when I suggested enabling `ImpredicativeTypes`, but I didn't look closely before making the suggestion. I'll see if I can take a look later this week and come up with an implementation plan. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): I have an implementation plan: * Augment `InstBindings` with a new field `ib_extensions`, which will be a list of `ExtensionFlag`. * In `tcInstanceMethods`, apply these flags using `setXOptM`. * In the `is_newtype` branch of `genInst`, set `ib_extensions` to `[Opt_ImpredicativeTypes]`. * Elsewhere, set `ib_extensions` to `[]`. Seems quite straightforward once I've examined all the plumbing. Expect a patch in the next few hours. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving?
-------------------------------------+------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Richard Eisenberg

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by goldfire): * status: new => merge Comment: Please merge this into 7.8 -- this bug would annoy users if it stays around. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by carter): I think i was hit by this when I was trying out LLVM-General on 7.8 RC, https://github.com/bscarlet/llvm-general/issues/83#issuecomment-34557918 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving?
-------------------------------------+------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: merge
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Richard Eisenberg

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------------------+------------------------- Reporter: goldfire | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: deriving/should_compile/T8631 | Unknown Blocking: | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by goldfire): * testcase: => deriving/should_compile/T8631 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------------------+------------------------- Reporter: goldfire | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: Resolution: | 7.8.1-rc1 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple deriving/should_compile/T8631 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by goldfire): * version: 7.7 => 7.8.1-rc1 * milestone: => 7.8.1 Comment: Putting this on Austin's radar for 7.8.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------------------+------------------------- Reporter: goldfire | Owner: Type: bug | Status: Priority: normal | closed Component: Compiler | Milestone: 7.8.1 Resolution: fixed | Version: Operating System: Unknown/Multiple | 7.8.1-rc1 Type of failure: None/Unknown | Keywords: Test Case: | Architecture: deriving/should_compile/T8631 | Unknown/Multiple Blocking: | Difficulty: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8631: Need ImpredicativeTypes for GeneralizedNewtypeDeriving? -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc1 Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_compile/T8631 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8631#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC