Haskell Hierarchical Libraries (base package)ContentsIndex
GHC.Exts
Portabilitynon-portable (GHC Extensions)
Stabilityinternal
Maintainercvs-ghc@haskell.org
Contents
Representations of some basic types
Primitive operations
Fusion
Linear implicit parameter support
Description
GHC Extensions: this is the Approved Way to get at GHC-specific extensions.
Synopsis
data Int = I# Int#
data Word = W# Word#
data Float = F# Float#
data Double = D# Double#
data Integer
= S# Int#
| J# Int# ByteArray#
data Char = C# Char#
data Ptr a = Ptr Addr#
data FunPtr a = FunPtr Addr#
shiftL# :: Word# -> Int# -> Word#
shiftRL# :: Word# -> Int# -> Word#
iShiftL# :: Int# -> Int# -> Int#
iShiftRA# :: Int# -> Int# -> Int#
iShiftRL# :: Int# -> Int# -> Int#
build :: forall a . (forall b . (a -> b -> b) -> b -> b) -> [a]
augment :: forall a . (forall b . (a -> b -> b) -> b -> b) -> [a] -> [a]
class Splittable t where
split :: t -> (t, t)
Representations of some basic types
data Int
A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.
Constructors
I# Int#
show/hide Instances
data Word
A Word is an unsigned integral type, with the same size as Int.
Constructors
W# Word#
show/hide Instances
data Float
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Constructors
F# Float#
show/hide Instances
data Double
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Constructors
D# Double#
show/hide Instances
data Integer
Arbitrary-precision integers.
Constructors
S# Int#
J# Int# ByteArray#
show/hide Instances
data Char

The character type Char is an enumeration whose values represent Unicode (or equivalently ISO 10646) characters. This set extends the ISO 8859-1 (Latin-1) character set (the first 256 charachers), which is itself an extension of the ASCII character set (the first 128 characters). A character literal in Haskell has type Char.

To convert a Char to or from the corresponding Int value defined by Unicode, use toEnum and fromEnum from the Enum class respectively (or equivalently ord and chr).

Constructors
C# Char#
show/hide Instances
data Ptr a

A value of type Ptr a represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of type a.

The type a will often be an instance of class Storable which provides the marshalling operations. However this is not essential, and you can provide your own operations to access the pointer. For example you might write small foreign functions to get or set the fields of a C struct.

Constructors
Ptr Addr#
show/hide Instances
data FunPtr a

A value of type FunPtr a is a pointer to a function callable from foreign code. The type a will normally be a foreign type, a function type with zero or more arguments where

A value of type FunPtr a may be a pointer to a foreign function, either returned by another foreign function or imported with a a static address import like

 foreign import ccall "stdlib.h &free"
   p_free :: FunPtr (Ptr a -> IO ())

or a pointer to a Haskell function created using a wrapper stub declared to produce a FunPtr of the correct type. For example:

 type Compare = Int -> Int -> Bool
 foreign import ccall "wrapper"
   mkCompare :: Compare -> IO (FunPtr Compare)

Calls to wrapper stubs like mkCompare allocate storage, which should be released with freeHaskellFunPtr when no longer required.

To convert FunPtr values to corresponding Haskell functions, one can define a dynamic stub for the specific foreign type, e.g.

 type IntFunction = CInt -> IO ()
 foreign import ccall "dynamic" 
   mkFun :: FunPtr IntFunction -> IntFunction
Constructors
FunPtr Addr#
show/hide Instances
Primitive operations
shiftL# :: Word# -> Int# -> Word#
Shift the argument left by the specified number of bits (which must be non-negative).
shiftRL# :: Word# -> Int# -> Word#
Shift the argument right by the specified number of bits (which must be non-negative).
iShiftL# :: Int# -> Int# -> Int#
Shift the argument left by the specified number of bits (which must be non-negative).
iShiftRA# :: Int# -> Int# -> Int#
Shift the argument right (signed) by the specified number of bits (which must be non-negative).
iShiftRL# :: Int# -> Int# -> Int#
Shift the argument right (unsigned) by the specified number of bits (which must be non-negative).
Fusion
build :: forall a . (forall b . (a -> b -> b) -> b -> b) -> [a]

A list producer that can be fused with foldr. This function is merely

	build g = g (:) []

but GHC's simplifier will transform an expression of the form foldr k z (build g), which may arise after inlining, to g k z, which avoids producing an intermediate list.

augment :: forall a . (forall b . (a -> b -> b) -> b -> b) -> [a] -> [a]

A list producer that can be fused with foldr. This function is merely

	augment g xs = g (:) xs

but GHC's simplifier will transform an expression of the form foldr k z (augment g xs), which may arise after inlining, to g k (foldr k z xs), which avoids producing an intermediate list.

Linear implicit parameter support
class Splittable t where
Methods
split :: t -> (t, t)
Produced by Haddock version 0.7