Re: [GHC] #14070: Allow ‘unsafe’ deriving strategy, deriving code with ‘unsafeCoerce’
GHC
ghc-devs at haskell.org
Sat Feb 24 23:57:38 UTC 2018
#14070: Allow ‘unsafe’ deriving strategy, deriving code with ‘unsafeCoerce’
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: feature request | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: duplicate | Keywords:
| QuantifiedConstraints, deriving
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #2893 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Sure. Here's a test adapted from the original post:
{{{#!hs
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImpredicativeTypes #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
import Data.Coerce
import Data.Kind
class Monad m => MonadJoin m where
join_ :: m (m a) -> m a
newtype T m a = T (m a)
deriving (Functor, Applicative, Monad)
type Representational1 f = (forall a b. Coercible a b => Coercible (f a)
(f b) :: Constraint)
instance (MonadJoin m, Representational1 m) => MonadJoin (T m) where
join_ = coerce @(forall a. m ( m a) -> m a)
@(forall a. T m (T m a) -> T m a)
join_
}}}
As this is essentially the code that this proposed deriving strategy would
have generated (except with `unsafeCoerce` replaced with `coerce`).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14070#comment:23>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list