
#14070: Allow ‘unsafe’ deriving strategy, deriving code with ‘unsafeCoerce’ -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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):
Do they cover legitimate uses of '`UnsafeDeriving`' or are there cases where it would still be useful?
My hunch is that just about every use case for this proposed `unsafe newtype` deriving strategy would be subsumed by the ability to have quantified contexts involving `Coercible`. To use your earlier example: {{{#!hs class MonadJoin m where join_ :: m (m a) -> m a newtype M m a = M (m a) deriving newtype MonadJoin }}} In a brave new quantified world, this would generate code to the effect of: {{{#!hs instance (forall a. Coercible (m (M m a)) (m (m a)), MonadJoin m) => MonadJoin (M m) where join_ = coerce @(forall a. m (m a) -> m a) @(forall a. M m (M m a) -> M m a) join_ }}} Where the `forall a. Coercible (m (M m a)) (m (m a))` bit is needed to convince the typechecker that one can `coerce` underneath `m` in the right spot. Another possible design for this would be to use an implication constraint instead: {{{#!hs instance (forall a b. Coercible a b => Coercible (m a) (m b), MonadJoin m) => MonadJoin (M m) where join_ = coerce @(forall a. m (m a) -> m a) @(forall a. M m (M m a) -> M m a) join_ }}} Would this always be the right thing to do? My gut feeling is "yes", since if you can coerce between `m (M m a)` and `m (m a)` (for any `a`), it feels like you should be able to coerce between `m a` and `m b` for _any_ pair of inter-`Coercible` types `a` and `b`. But I haven't worked out the full details yet, so this is purely speculation on my end for the time being.
Incidentally is it possible to coerce `Lens s a = forall f. Functor f => (a -> f a) -> (s -> f s)` types?
Sure! The example you gave only doesn't typecheck because you didn't expand the `Lens` type synonym: {{{#!hs {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} import Unsafe.Coerce type Lens s a = forall f. Functor f => (a -> f a) -> (s -> f s) class X f where x :: Lens (f a) a newtype WrappedX f a = WrapX (f a) instance X t => X (WrappedX t) where x :: forall a f. Functor f => (a -> f a) -> WrappedX t a -> f (WrappedX t a) x = unsafeCoerce x' where x' :: (a -> f a) -> t a -> f (t a) x' = x @t @a }}} This is important, since the `f` needs to scope over both `x` and `x'`. In your example, the `f` tucked underneath the two occurrences of the `Lens` type synonyms were distinct. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14070#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler