|
GHC.Exts | Portability | non-portable (GHC Extensions) | Stability | internal | Maintainer | cvs-ghc@haskell.org |
|
|
|
|
|
Description |
GHC Extensions: this is the Approved Way to get at GHC-specific extensions.
|
|
Synopsis |
|
|
|
|
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 | | Instances | |
|
|
data Word |
A Word is an unsigned integral type, with the same size as Int.
| Constructors | | 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 | | 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 | | Instances | |
|
|
data Integer |
Arbitrary-precision integers.
| Constructors | | Instances | |
|
|
data Char |
The character type Char is an enumeration whose values represent
Unicode (or equivalently ISO/IEC 10646) characters
(see http://www.unicode.org/ for details).
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 | | 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 | | 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
- the argument types are marshallable foreign types,
i.e. Char, Int, Double, Float,
Bool, Int8, Int16, Int32,
Int64, Word8, Word16,
Word32, Word64, Ptr a, FunPtr a,
StablePtr a or a renaming of any of these
using newtype.
- the return type is either a marshallable foreign type or has the form
IO t where t is a marshallable foreign type or ().
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 | | Instances | |
|
|
Primitive operations
|
|
module GHC.Prim |
|
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 |
|
|
Debugging
|
|
breakpoint :: a -> a |
|
Ids with special behaviour
|
|
lazy :: a -> a |
The lazy function restrains strictness analysis a little. The call
(lazy e) means the same as e, but lazy has a magical
property so far as strictness analysis is concerned: it is lazy in its first
argument, even though its semantics is strict. After strictness analysis has
run, calls to lazy are inlined to be the identity function.
This behaviour is occasionally useful when controlling evaluation order.
Notably, lazy is used in the library definition of Control.Parallel.par:
par :: a -> b -> b par x y = case (par# x) of _ -> lazy y If lazy were not lazy, par would look strict in y which
would defeat the whole purpose of par.
Like seq, the argument of lazy can have an unboxed type.
|
|
inline :: a -> a |
The call (inline f) arranges that f is inlined, regardless of its size.
More precisely, the call (inline f) rewrites to the right-hand side of
f's definition. This allows the programmer to control inlining from a
particular call site rather than the definition site of the function (c.f.
INLINE pragmas in User's Guide, Section 7.10.3, "INLINE and NOINLINE
pragmas").
This inlining occurs regardless of the argument to the call or the size of
f's definition; it is unconditional. The main caveat is that f's
definition must be visible to the compiler. That is, f must be
let-bound in the current scope. If no inlining takes place, the
inline function expands to the identity function in Phase zero; so its
use imposes no overhead.
If the function is defined in another module, GHC only exposes its inlining
in the interface file if the function is sufficiently small that it might be
inlined by the automatic mechanism. There is currently no way to tell GHC to
expose arbitrarily-large functions in the interface file. (This shortcoming
is something that could be fixed, with some kind of pragma.)
|
|
Produced by Haddock version 0.8 |