[GHC] #11152: GND accepts ill-roled coercion when manually defining it won't typecheck
GHC
ghc-devs at haskell.org
Tue Dec 1 19:39:38 UTC 2015
#11152: GND accepts ill-roled coercion when manually defining it won't typecheck
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.2
checker) |
Resolution: invalid | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #9123 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* status: new => closed
* resolution: => invalid
* related: => #9123
Comment:
Oops, I overlooked the `forall (a_axs :: *)` part. It turns out that (and
some language extensions) are needed to make the generated code compile
when typed out manually:
{{{#!hs
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
module CoerceJoin where
import qualified Control.Monad (join)
import Data.Coerce (coerce)
class MyMonad m where
join :: m (m a) -> m a
instance MyMonad Maybe where
join = Control.Monad.join
newtype MyMaybe a = MyMaybe (Maybe a)
instance MyMonad MyMaybe where
join = coerce (join :: Maybe (Maybe a) -> Maybe a) :: forall (a :: *).
MyMaybe (MyMaybe a) -> MyMaybe a
}}}
Also, I think the issue I was trying to reproduce is #9123, so I'll add
that to the related tickets as evidence that adding `join` to `Monad`
''would'' cause some trouble.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11152#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list