df1c109e0e4a0c9b16661561efd612c31d2b7ce3
1 {-# LANGUAGE Unsafe #-}
2 {-# LANGUAGE NoImplicitPrelude, MagicHash #-}
4 -----------------------------------------------------------------------------
6 -- Module : Unsafe.Coerce
7 -- Copyright : Malcolm Wallace 2006
8 -- License : BSD-style (see the LICENSE file in the distribution)
10 -- Maintainer : libraries@haskell.org
11 -- Stability : experimental
12 -- Portability : portable
14 -- The highly unsafe primitive 'unsafeCoerce' converts a value from any
15 -- type to any other type. Needless to say, if you use this function,
16 -- it is your responsibility to ensure that the old and new types have
17 -- identical internal representations, in order to prevent runtime corruption.
19 -- The types for which 'unsafeCoerce' is representation-safe may differ
20 -- from compiler to compiler (and version to version).
22 -- * Documentation for correct usage in GHC will be found under
23 -- 'unsafeCoerce#' in GHC.Base (around which 'unsafeCoerce' is just a
26 -- * In nhc98, the only representation-safe coercions are between Enum
27 -- types with the same range (e.g. Int, Int32, Char, Word32),
28 -- or between a newtype and the type that it wraps.
30 -----------------------------------------------------------------------------
32 module Unsafe
.Coerce
(unsafeCoerce
) where
34 import GHC
.Integer () -- for build ordering
35 import GHC
.Prim
(unsafeCoerce
#)
38 local_id x
= x
-- See Note [Mega-hack for coerce]
40 {- Note [Mega-hack for coerce]
43 unsafeCoerce x = unsafeCoerce# x
44 then the simple-optimiser that the desugarer runs will eta-reduce to
45 unsafeCoerce :: forall (a:*) (b:*). a -> b
46 unsafeCoerce = unsafeCoerce#
47 But we shouldn't be calling unsafeCoerce# in a higher
48 order way; it has a compulsory unfolding
49 unsafeCoerce# a b x = x |> UnsafeCo a b
50 and we really rely on it being inlined pronto. But the simple-optimiser doesn't.
51 The identity function local_id delays the eta reduction just long enough
52 for unsafeCoerce# to get inlined.
54 Sigh. This is horrible, but then so is unsafeCoerce.
57 unsafeCoerce
:: a
-> b
58 unsafeCoerce x
= local_id
(unsafeCoerce
# x
)
59 -- See Note [Unsafe coerce magic] in basicTypes/MkId
60 -- NB: Do not eta-reduce this definition (see above)