License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- bool# :: Int# -> Bool
- data PinnedStatus
- toPinnedStatus# :: Pinned# -> PinnedStatus
- compatMkWeak# :: o -> b -> IO () -> State# RealWorld -> (# State# RealWorld, Weak# b #)
- compatIsByteArrayPinned# :: ByteArray# -> Pinned#
- compatIsMutableByteArrayPinned# :: MutableByteArray# s -> Pinned#
- unsafeCoerce# :: forall (k0 :: RuntimeRep) (k1 :: RuntimeRep) (a :: TYPE k0) (b :: TYPE k1). a -> b
- data Word = W# Word#
- type Word8# = Word#
- type Word16# = Word#
- type Word32# = Word#
- type Int8# = Int#
- type Int16# = Int#
- type Int32# = Int#
- word8ToWord16# :: Word8# -> Word16#
- word8ToWord32# :: Word8# -> Word32#
- word8ToWord# :: Word8# -> Word#
- word16ToWord8# :: Word16# -> Word8#
- word16ToWord32# :: Word16# -> Word32#
- word16ToWord# :: Word16# -> Word#
- word32ToWord# :: Word32# -> Word#
- word32ToWord8# :: Word32# -> Word8#
- word32ToWord16# :: Word32# -> Word16#
- wordToWord32# :: Word# -> Word32#
- wordToWord16# :: Word# -> Word16#
- wordToWord8# :: Word# -> Word8#
- int8ToInt16# :: Int8# -> Int16#
- int8ToInt32# :: Int8# -> Int32#
- int8ToInt# :: Int8# -> Int#
- int16ToInt32# :: Int16# -> Int32#
- int16ToInt# :: Int16# -> Int#
- int32ToInt# :: Int32# -> Int#
- intToInt8# :: Int# -> Int8#
- intToInt16# :: Int# -> Int16#
- intToInt32# :: Int# -> Int32#
- word8ToInt# :: Word8# -> Int#
- word8ToInt16# :: Word8# -> Int16#
- word8ToInt32# :: Word8# -> Int32#
- charToWord32# :: Char# -> Word32#
- word8ToChar# :: Word8# -> Char#
- word16ToChar# :: Word16# -> Char#
- word32ToChar# :: Word32# -> Char#
- wordToChar# :: Word# -> Char#
- plusWord8# :: Word8# -> Word8# -> Word8#
- uncheckedShiftRLWord16# :: Word# -> Int# -> Word#
- plusWord16# :: Word16# -> Word16# -> Word16#
- uncheckedShiftRLWord32# :: Word# -> Int# -> Word#
- plusWord32# :: Word32# -> Word32# -> Word32#
- plusInt8# :: Int8# -> Int8# -> Int8#
- plusInt16# :: Int16# -> Int16# -> Int16#
- plusInt32# :: Int32# -> Int32# -> Int32#
Documentation
data PinnedStatus Source #
Flag record whether a specific byte array is pinned or not
Instances
Eq PinnedStatus Source # | |
Defined in Basement.Compat.Primitive (==) :: PinnedStatus -> PinnedStatus -> Bool # (/=) :: PinnedStatus -> PinnedStatus -> Bool # |
unsafeCoerce# :: forall (k0 :: RuntimeRep) (k1 :: RuntimeRep) (a :: TYPE k0) (b :: TYPE k1). a -> b #
The function unsafeCoerce#
allows you to side-step the typechecker entirely. That
is, it allows you to coerce any type into any other type. If you use this function,
you had better get it right, otherwise segmentation faults await. It is generally
used when you want to write a program that you know is well-typed, but where Haskell's
type system is not expressive enough to prove that it is well typed.
The following uses of unsafeCoerce#
are supposed to work (i.e. not lead to
spurious compile-time or run-time crashes):
- Casting any lifted type to
Any
- Casting
Any
back to the real type - Casting an unboxed type to another unboxed type of the same size.
(Casting between floating-point and integral types does not work.
See the
GHC.Float
module for functions to do work.) - Casting between two types that have the same runtime representation. One case is when
the two types differ only in "phantom" type parameters, for example
Ptr Int
toPtr Float
, or[Int]
to[Float]
when the list is known to be empty. Also, anewtype
of a typeT
has the same representation at runtime asT
.
Other uses of unsafeCoerce#
are undefined. In particular, you should not use
unsafeCoerce#
to cast a T to an algebraic data type D, unless T is also
an algebraic data type. For example, do not cast Int->Int
to Bool
, even if
you later cast that Bool
back to Int->Int
before applying it. The reasons
have to do with GHC's internal representation details (for the cognoscenti, data values
can be entered but function closures cannot). If you want a safe type to cast things
to, use Any
, which is not an algebraic data type.
Warning: this can fail with an unchecked exception.
Instances
word8ToWord16# :: Word8# -> Word16# Source #
word8ToWord32# :: Word8# -> Word32# Source #
word8ToWord# :: Word8# -> Word# Source #
word16ToWord8# :: Word16# -> Word8# Source #
word16ToWord32# :: Word16# -> Word32# Source #
word16ToWord# :: Word16# -> Word# Source #
word32ToWord# :: Word32# -> Word# Source #
word32ToWord8# :: Word32# -> Word8# Source #
word32ToWord16# :: Word32# -> Word16# Source #
wordToWord32# :: Word# -> Word32# Source #
wordToWord16# :: Word# -> Word16# Source #
wordToWord8# :: Word# -> Word8# Source #
int8ToInt16# :: Int8# -> Int16# Source #
int8ToInt32# :: Int8# -> Int32# Source #
int8ToInt# :: Int8# -> Int# Source #
int16ToInt32# :: Int16# -> Int32# Source #
int16ToInt# :: Int16# -> Int# Source #
int32ToInt# :: Int32# -> Int# Source #
intToInt8# :: Int# -> Int8# Source #
intToInt16# :: Int# -> Int16# Source #
intToInt32# :: Int# -> Int32# Source #
word8ToInt# :: Word8# -> Int# Source #
word8ToInt16# :: Word8# -> Int16# Source #
word8ToInt32# :: Word8# -> Int32# Source #
charToWord32# :: Char# -> Word32# Source #
word8ToChar# :: Word8# -> Char# Source #
word16ToChar# :: Word16# -> Char# Source #
word32ToChar# :: Word32# -> Char# Source #
wordToChar# :: Word# -> Char# Source #