Copyright | (C) 2011-2015 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Synopsis
- class a ~R# b => Coercible (a :: k0) (b :: k0)
- unsafeCoerceConstraint :: a :- b
- unsafeDerive :: Coercible n o => (o -> n) -> t o :- t n
- unsafeUnderive :: Coercible n o => (o -> n) -> t n :- t o
- unsafeApplicative :: forall m a. Monad m => (Applicative m => m a) -> m a
- unsafeAlternative :: forall m a. MonadPlus m => (Alternative m => m a) -> m a
Documentation
class a ~R# b => Coercible (a :: k0) (b :: k0) #
Coercible
is a two-parameter class that has instances for types a
and b
if
the compiler can infer that they have the same representation. This class
does not have regular instances; instead they are created on-the-fly during
type-checking. Trying to manually declare an instance of Coercible
is an error.
Nevertheless one can pretend that the following three kinds of instances exist. First, as a trivial base-case:
instance Coercible a a
Furthermore, for every type constructor there is
an instance that allows to coerce under the type constructor. For
example, let D
be a prototypical type constructor (data
or
newtype
) with three type arguments, which have roles nominal
,
representational
resp. phantom
. Then there is an instance of
the form
instance Coercible b b' => Coercible (D a b c) (D a b' c')
Note that the nominal
type arguments are equal, the
representational
type arguments can differ, but need to have a
Coercible
instance themself, and the phantom
type arguments can be
changed arbitrarily.
The third kind of instance exists for every newtype NT = MkNT T
and
comes in two variants, namely
instance Coercible a T => Coercible a NT
instance Coercible T b => Coercible NT b
This instance is only usable if the constructor MkNT
is in scope.
If, as a library author of a type constructor like Set a
, you
want to prevent a user of your module to write
coerce :: Set T -> Set NT
,
you need to set the role of Set
's type parameter to nominal
,
by writing
type role Set nominal
For more details about this feature, please refer to Safe Coercions by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich.
Since: ghc-prim-4.7.0.0
unsafeCoerceConstraint :: a :- b Source #
Coerce a dictionary unsafely from one type to another
unsafeDerive :: Coercible n o => (o -> n) -> t o :- t n Source #
Coerce a dictionary unsafely from one type to a newtype of that type
unsafeUnderive :: Coercible n o => (o -> n) -> t n :- t o Source #
Coerce a dictionary unsafely from a newtype of a type to the base type
Sugar
unsafeApplicative :: forall m a. Monad m => (Applicative m => m a) -> m a Source #
Construct an Applicative instance from a Monad
unsafeAlternative :: forall m a. MonadPlus m => (Alternative m => m a) -> m a Source #
Construct an Alternative instance from a MonadPlus