[GHC] #10326: ImpredicativeTypes: Unable to use in Functor etc..

#10326: ImpredicativeTypes: Unable to use in Functor etc.. -------------------------------------+------------------------------------- Reporter: | Owner: j80JjBjVNRMajmA | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- I want to use values of RankNTypes within Functors/Monads/... just like normal values. The following code shows, that I cannot lift a function `ReturnNull -> ReturnNull` into a functor the way I would like to (e.g. `liftId2`). However, using another version that seems equivalent and that is allowed by GHC, `liftId3`, does not allow me to pipe the result to `override`. How can I do this? {{{#!hs {-# LANGUAGE ImpredicativeTypes #-} type ReturnNull = forall m. Monad m => m () id2 :: ReturnNull -> ReturnNull id2 = id testId2 :: ReturnNull testId2 = id2 $ return () liftId :: Functor f => f ReturnNull -> f ReturnNull liftId = fmap id -- rejected liftId2 :: Functor f => f ReturnNull -> f ReturnNull liftId2 = fmap id2 liftId3 :: (Monad m,Functor f) => f ReturnNull -> f (m ()) liftId3 = fmap id2 override :: Functor f => f ReturnNull -> f () override = fmap $ const () testLift :: Functor f => f ReturnNull -> f () testLift = override . liftId --rejected testLift3 :: Functor f => f ReturnNull -> f () testLift3 = override . liftId3 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10326 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10326: ImpredicativeTypes: Unable to use in Functor etc.. -------------------------------------+------------------------------------- Reporter: j80JjBjVNRMajmA | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => wontfix Comment: `ImpredicativeTypes` is thoroughly broken and is unsupported. In the past, this extension was more properly implemented, but caused more grief than help even then. If you want this kind of thing, use a `newtype` instead of a `type`. It's surely more annoying, but it's better to have an annoying option instead of a totally-broken one. There are a number of Very Clever People working on integrating impredicativity with GHC-style type inference. (I'm not one of them, however.) In GHC's view, there has not yet been the right solution. We all look forward to when the right solution is found! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10326#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC