Portability | non-portable (GHC Extensions) |
---|---|
Stability | internal |
Maintainer | cvs-ghc@haskell.org |
Safe Haskell | Unsafe |
GHC Extensions: this is the Approved Way to get at GHC-specific extensions.
- data Int = I# Int#
- data Word = W# Word#
- data Float = F# Float#
- data Double = D# Double#
- data Char = C# Char#
- data Ptr a = Ptr Addr#
- data FunPtr a = FunPtr Addr#
- maxTupleSize :: Int
- module GHC.Prim
- shiftL# :: Word# -> Int# -> Word#
- shiftRL# :: Word# -> Int# -> Word#
- iShiftL# :: Int# -> Int# -> Int#
- iShiftRA# :: Int# -> Int# -> Int#
- iShiftRL# :: Int# -> Int# -> Int#
- uncheckedShiftL64# :: Word64# -> Int# -> Word64#
- uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
- uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
- build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
- augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a]
- class IsString a where
- fromString :: String -> a
- breakpoint :: a -> a
- breakpointCond :: Bool -> a -> a
- lazy :: a -> a
- inline :: a -> a
- newtype Down a = Down a
- groupWith :: Ord b => (a -> b) -> [a] -> [[a]]
- sortWith :: Ord b => (a -> b) -> [a] -> [a]
- the :: Eq a => [a] -> a
- traceEvent :: String -> IO ()
- data SpecConstrAnnotation
- currentCallStack :: IO [String]
- data Constraint
Representations of some basic types
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.
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.
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 characters), 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
).
A value of type
represents a pointer to an object, or an
array of objects, which may be marshalled to or from Haskell values
of type Ptr
aa
.
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
.
A value of type
is a pointer to a function callable
from foreign code. The type FunPtr
aa
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
or a renaming of any of these usingStablePtr
anewtype
. - the return type is either a marshallable foreign type or has the form
whereIO
tt
is a marshallable foreign type or()
.
A value of type
may be a pointer to a foreign function,
either returned by another foreign function or imported with a
a static address import like
FunPtr
a
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
The maximum tuple size
Primitive operations
module GHC.Prim
shiftL# :: Word# -> Int# -> Word#Source
Shift the argument left by the specified number of bits (which must be non-negative).
shiftRL# :: Word# -> Int# -> Word#Source
Shift the argument right by the specified number of bits (which must be non-negative).
iShiftL# :: Int# -> Int# -> Int#Source
Shift the argument left by the specified number of bits (which must be non-negative).
iShiftRA# :: Int# -> Int# -> Int#Source
Shift the argument right (signed) by the specified number of bits (which must be non-negative).
iShiftRL# :: Int# -> Int# -> Int#Source
Shift the argument right (unsigned) by the specified number of bits (which must be non-negative).
uncheckedShiftL64# :: Word64# -> Int# -> Word64#Source
uncheckedShiftRL64# :: Word64# -> Int# -> Word64#Source
uncheckedIShiftL64# :: Int64# -> Int# -> Int64#Source
uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#Source
Fusion
Overloaded string literals
Class for string-like datastructures; used by the overloaded string extension (-foverloaded-strings in GHC).
fromString :: String -> aSource
Debugging
breakpoint :: a -> aSource
breakpointCond :: Bool -> a -> aSource
Ids with special behaviour
The call '(lazy e)' means the same as e
, but lazy
has a
magical strictness property: it is lazy in its first argument,
even though its semantics is strict.
The call '(inline f)' reduces to f
, but inline
has a BuiltInRule
that tries to inline f
(if it has an unfolding) unconditionally
The NOINLINE
pragma arranges that inline only gets inlined (and
hence eliminated) late in compilation, after the rule has had
a good chance to fire.
Transform comprehensions
The Down
type allows you to reverse sort order conveniently. A value of type
contains a value of type Down
aa
(represented as
).
If Down
aa
has an
instance associated with it then comparing two
values thus wrapped will give you the opposite of their normal sort order.
This is particularly useful when sorting in generalised list comprehensions,
as in: Ord
then sortWith by
Down
x
Down a |
groupWith :: Ord b => (a -> b) -> [a] -> [[a]]Source
The groupWith
function uses the user supplied function which
projects an element out of every list element in order to to first sort the
input list and then to form groups by equality on these projected elements
sortWith :: Ord b => (a -> b) -> [a] -> [a]Source
The sortWith
function sorts a list of elements using the
user supplied function to project something out of each element
the
ensures that all the elements of the list are identical
and then returns that unique element
Event logging
traceEvent :: String -> IO ()Source
SpecConstr annotations
The call stack
currentCallStack :: IO [String]Source
returns a '[String]' representing the current call stack. This can be useful for debugging.
The implementation uses the call-stack simulation maintined by the
profiler, so it only works if the program was compiled with -prof
and contains suitable SCC annotations (e.g. by using -fprof-auto
).
Otherwise, the list returned is likely to be empty or
uninformative.
The Constraint kind
data Constraint Source