basement-0.0.15: Foundation scrap box of array & string
License BSD-style
Maintainer Vincent Hanquez <vincent@snarc.org>
Stability experimental
Portability portable
Safe Haskell None
Language Haskell2010

Basement.Compat.Primitive

Description

Synopsis

Documentation

bool# :: Int# -> Bool Source #

turn an Int# into a Bool

data PinnedStatus Source #

Flag record whether a specific byte array is pinned or not

Constructors

Pinned
Unpinned

compatMkWeak# :: o -> b -> IO () -> State# RealWorld -> (# State# RealWorld , Weak# b #) Source #

A mkWeak# version that keep working on 8.0

signature change in ghc-prim: * 0.4: mkWeak# :: o -> b -> c -> State# RealWorld -> ( RealWorld, Weak# b#) * 0.5 :mkWeak# :: o -> b -> (State# RealWorld -> ( RealWorld, c#)) -> State# RealWorld -> ( RealWorld, Weak# b#)

unsafeCoerce# :: forall (k0 :: RuntimeRep ) (k1 :: RuntimeRep ) (a :: TYPE k0) (b :: TYPE k1). a -> b Source #

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 to Ptr Float , or [Int] to [Float] when the list is known to be empty. Also, a newtype of a type T has the same representation at runtime as T .

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.

data Word Source #

A Word is an unsigned integral type, with the same size as Int .

Constructors

W# Word#

Instances

Instances details
Bounded Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Word
Instance details

Defined in GHC.Classes

Integral Word

Since: base-2.1

Instance details

Defined in GHC.Real

Data Word

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Word -> c Word Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Word Source #

toConstr :: Word -> Constr Source #

dataTypeOf :: Word -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Word ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Word ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Word -> Word Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Word -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Word -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Word -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Word -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Word -> m Word Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word -> m Word Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word -> m Word Source #

Num Word

Since: base-2.1

Instance details

Defined in GHC.Num

Ord Word
Instance details

Defined in GHC.Classes

Read Word

Since: base-4.5.0.0

Instance details

Defined in GHC.Read

Real Word

Since: base-2.1

Instance details

Defined in GHC.Real

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Ix Word

Since: base-4.6.0.0

Instance details

Defined in GHC.Ix

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word

Since: base-2.1

Instance details

Defined in Data.Bits

FiniteBits Word

Since: base-4.6.0.0

Instance details

Defined in Data.Bits

HasNegation Word Source #
Instance details

Defined in Basement.Compat.NumLiteral

Integral Word Source #
Instance details

Defined in Basement.Compat.NumLiteral

IsNatural Word Source #
Instance details

Defined in Basement.Numerical.Number

IsIntegral Word Source #
Instance details

Defined in Basement.Numerical.Number

Subtractive Word Source #
Instance details

Defined in Basement.Numerical.Subtractive

Additive Word Source #
Instance details

Defined in Basement.Numerical.Additive

IDivisible Word Source #
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word Source #
Instance details

Defined in Basement.Numerical.Multiplicative

PrimMemoryComparable Word Source #
Instance details

Defined in Basement.PrimType

PrimType Word Source #
Instance details

Defined in Basement.PrimType

NormalForm Word Source #
Instance details

Defined in Basement.NormalForm

BitOps Word Source #
Instance details

Defined in Basement.Bits

FiniteBitsOps Word Source #
Instance details

Defined in Basement.Bits

IntegralUpsize Word Word64 Source #
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Word Source #
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word16 Word Source #
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word32 Word Source #
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word Word8 Source #
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word Word16 Source #
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word Word32 Source #
Instance details

Defined in Basement.IntegralConv

Cast Int Word Source #
Instance details

Defined in Basement.Cast

Cast Int64 Word Source #
Instance details

Defined in Basement.Cast

Cast Word Int Source #
Instance details

Defined in Basement.Cast

Cast Word Int64 Source #
Instance details

Defined in Basement.Cast

Cast Word Word64 Source #
Instance details

Defined in Basement.Cast

Cast Word64 Word Source #
Instance details

Defined in Basement.Cast

From Word Word64 Source #
Instance details

Defined in Basement.From

From Word8 Word Source #
Instance details

Defined in Basement.From

From Word16 Word Source #
Instance details

Defined in Basement.From

From Word32 Word Source #
Instance details

Defined in Basement.From

From Word ( CountOf ty) Source #
Instance details

Defined in Basement.From

From Word ( Offset ty) Source #
Instance details

Defined in Basement.From

Generic1 ( URec Word :: k -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ( URec Word ) :: k -> Type Source #

Foldable ( UWord :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Traversable ( UWord :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

From ( CountOf ty) Word Source #
Instance details

Defined in Basement.From

Functor ( URec Word :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ( URec Word p) :: Type -> Type Source #

type NatNumMaxBound Word Source #
Instance details

Defined in Basement.Nat

type Difference Word Source #
Instance details

Defined in Basement.Numerical.Subtractive

type PrimSize Word Source #
Instance details

Defined in Basement.PrimType

data URec Word (p :: k)

Used for marking occurrences of Word#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 ( URec Word :: k -> Type )
Instance details

Defined in GHC.Generics

type Rep ( URec Word p)
Instance details

Defined in GHC.Generics