Copyright | (c) The University of Glasgow 2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | cvs-ghc@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
- Representations of some basic types
- The maximum tuple size
- Primitive operations
- Fusion
- Overloaded string literals
- Debugging
- Ids with special behaviour
- Safe coercions
- Equality
- Representation polymorphism
- Transform comprehensions
- Event logging
- SpecConstr annotations
- The call stack
- The Constraint kind
- Overloaded lists
GHC Extensions: this is the Approved Way to get at GHC-specific extensions.
Note: no other base module should import this module.
- 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# :: Word# -> Int# -> Word#
- uncheckedShiftRL64# :: Word# -> Int# -> Word#
- uncheckedIShiftL64# :: Int# -> Int# -> Int#
- uncheckedIShiftRA64# :: Int# -> Int# -> Int#
- isTrue# :: Int# -> Bool
- 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
- breakpoint :: a -> a
- breakpointCond :: Bool -> a -> a
- lazy :: a -> a
- inline :: a -> a
- coerce :: Coercible * a b => a -> b
- class (~R#) k k a b => Coercible k a b
- class (~#) j k a b => (j ~~ k) a b
- data TYPE a :: RuntimeRep -> *
- data RuntimeRep :: *
- data VecCount :: *
- data VecElem :: *
- 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 :: *
- class IsList l where
- type Item l
Representations of some basic types
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.
Bounded Int # | |
Enum Int # | |
Eq Int | |
Integral Int # | |
Data Int # | |
Num Int # | |
Ord Int | |
Read Int # | |
Real Int # | |
Show Int # | |
Ix Int # | |
FiniteBits Int # | |
Bits Int # | |
Storable Int # | |
PrintfArg Int # | |
Functor (URec Int) # | |
Foldable (URec Int) # | |
Traversable (URec Int) # | |
Generic1 (URec Int) # | |
Eq (URec Int p) # | |
Ord (URec Int p) # | |
Show (URec Int p) # | |
Generic (URec Int p) # | |
data URec Int # | Used for marking occurrences of |
type Rep1 (URec Int) # | |
type Rep (URec Int p) # | |
Bounded Word # | |
Enum Word # | |
Eq Word | |
Integral Word # | |
Data Word # | |
Num Word # | |
Ord Word | |
Read Word # | |
Real Word # | |
Show Word # | |
Ix Word # | |
FiniteBits Word # | |
Bits Word # | |
Storable Word # | |
PrintfArg Word # | |
Functor (URec Word) # | |
Foldable (URec Word) # | |
Traversable (URec Word) # | |
Generic1 (URec Word) # | |
Eq (URec Word p) # | |
Ord (URec Word p) # | |
Show (URec Word p) # | |
Generic (URec Word p) # | |
data URec Word # | Used for marking occurrences of |
type Rep1 (URec Word) # | |
type Rep (URec Word p) # | |
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.
Eq Float | |
Floating Float # | |
Data Float # | |
Ord Float | |
Read Float # | |
RealFloat Float # | |
Storable Float # | |
PrintfArg Float # | |
Functor (URec Float) # | |
Foldable (URec Float) # | |
Traversable (URec Float) # | |
Generic1 (URec Float) # | |
Eq (URec Float p) # | |
Ord (URec Float p) # | |
Show (URec Float p) # | |
Generic (URec Float p) # | |
data URec Float # | Used for marking occurrences of |
type Rep1 (URec Float) # | |
type Rep (URec Float p) # | |
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.
Eq Double | |
Floating Double # | |
Data Double # | |
Ord Double | |
Read Double # | |
RealFloat Double # | |
Storable Double # | |
PrintfArg Double # | |
Functor (URec Double) # | |
Foldable (URec Double) # | |
Traversable (URec Double) # | |
Generic1 (URec Double) # | |
Eq (URec Double p) # | |
Ord (URec Double p) # | |
Show (URec Double p) # | |
Generic (URec Double p) # | |
data URec Double # | Used for marking occurrences of |
type Rep1 (URec Double) # | |
type Rep (URec Double p) # | |
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
).
Bounded Char # | |
Enum Char # | |
Eq Char | |
Data Char # | |
Ord Char | |
Read Char # | |
Show Char # | |
Ix Char # | |
Storable Char # | |
IsChar Char # | |
PrintfArg Char # | |
Functor (URec Char) # | |
Foldable (URec Char) # | |
Traversable (URec Char) # | |
Generic1 (URec Char) # | |
Eq (URec Char p) # | |
Ord (URec Char p) # | |
Show (URec Char p) # | |
Generic (URec Char p) # | |
data URec Char # | Used for marking occurrences of |
type Rep1 (URec Char) # | |
type Rep (URec Char p) # | |
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
.
Eq (Ptr a) # | |
Data a => Data (Ptr a) # | |
Functor (URec (Ptr ())) # | |
Ord (Ptr a) # | |
Show (Ptr a) # | |
Foldable (URec (Ptr ())) # | |
Traversable (URec (Ptr ())) # | |
Generic1 (URec (Ptr ())) # | |
Storable (Ptr a) # | |
Eq (URec (Ptr ()) p) # | |
Ord (URec (Ptr ()) p) # | |
Generic (URec (Ptr ()) p) # | |
type Rep1 (URec (Ptr ())) # | |
data URec (Ptr ()) # | Used for marking occurrences of |
type Rep (URec (Ptr ()) p) # | |
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 likeFunPtr
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
maxTupleSize :: Int Source #
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). The RL means "right, logical" (as opposed to RA for arithmetic) (although an arithmetic right shift wouldn't make sense for Word#)
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). The RA means "right, arithmetic" (as opposed to RL for logical)
iShiftRL# :: Int# -> Int# -> Int# Source #
Shift the argument right (unsigned) by the specified number of bits (which must be non-negative). The RL means "right, logical" (as opposed to RA for arithmetic)
isTrue# :: Int# -> Bool Source #
Alias for tagToEnum#
. Returns True if its parameter is 1# and False
if it is 0#.
Fusion
Overloaded string literals
class IsString a where Source #
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
fromString :: String -> a Source #
Debugging
breakpoint :: a -> a Source #
breakpointCond :: Bool -> a -> a Source #
Ids with special behaviour
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
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
.
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).
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; it is
therefore recommended to mark the function with an INLINABLE
pragma at its definition so that GHC guarantees to record its
unfolding regardless of size.
If no inlining takes place, the inline
function expands to the
identity function in Phase zero, so its use imposes no overhead.
Safe coercions
These are available from the Trustworthy module Data.Coerce as well
Since: 4.7.0.0
coerce :: Coercible * a b => a -> b Source #
The function coerce
allows you to safely convert between values of
types that have the same representation with no run-time overhead. In the
simplest case you can use it instead of a newtype constructor, to go from
the newtype's concrete type to the abstract type. But it also works in
more complicated settings, e.g. converting a list of newtypes to a list of
concrete types.
class (~R#) k k a b => Coercible k a b Source #
Coercible
is a two-parameter class that has instances for types a
and b
if
the compiler can infer that they have the same representation. This class
does not have regular instances; instead they are created on-the-fly during
type-checking. Trying to manually declare an instance of Coercible
is an error.
Nevertheless one can pretend that the following three kinds of instances exist. First, as a trivial base-case:
instance a a
Furthermore, for every type constructor there is
an instance that allows to coerce under the type constructor. For
example, let D
be a prototypical type constructor (data
or
newtype
) with three type arguments, which have roles nominal
,
representational
resp. phantom
. Then there is an instance of
the form
instance Coercible b b' => Coercible (D a b c) (D a b' c')
Note that the nominal
type arguments are equal, the
representational
type arguments can differ, but need to have a
Coercible
instance themself, and the phantom
type arguments can be
changed arbitrarily.
The third kind of instance exists for every newtype NT = MkNT T
and
comes in two variants, namely
instance Coercible a T => Coercible a NT
instance Coercible T b => Coercible NT b
This instance is only usable if the constructor MkNT
is in scope.
If, as a library author of a type constructor like Set a
, you
want to prevent a user of your module to write
coerce :: Set T -> Set NT
,
you need to set the role of Set
's type parameter to nominal
,
by writing
type role Set nominal
For more details about this feature, please refer to Safe Coercions by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich.
Since: 4.7.0.0
Equality
class (~#) j k a b => (j ~~ k) a b Source #
Lifted, heterogeneous equality. By lifted, we mean that it
can be bogus (deferred type error). By heterogeneous, the two
types a
and b
might have different kinds. Because ~~
can
appear unexpectedly in error messages to users who do not care
about the difference between heterogeneous equality ~~
and
homogeneous equality ~
, this is printed as ~
unless
-fprint-equality-relations
is set.
Representation polymorphism
data TYPE a :: RuntimeRep -> * Source #
data RuntimeRep :: * Source #
GHC maintains a property that the kind of all inhabited types
(as distinct from type constructors or type-level data) tells us
the runtime representation of values of that type. This datatype
encodes the choice of runtime value.
Note that TYPE
is parameterised by RuntimeRep
; this is precisely
what we mean by the fact that a type's kind encodes the runtime
representation.
For boxed values (that is, values that are represented by a pointer), a further distinction is made, between lifted types (that contain ⊥), and unlifted ones (that don't).
VecRep VecCount VecElem | a SIMD vector type |
PtrRepLifted | lifted; represented by a pointer |
PtrRepUnlifted | unlifted; represented by a pointer |
VoidRep | erased entirely |
IntRep | signed, word-sized value |
WordRep | unsigned, word-sized value |
Int64Rep | signed, 64-bit value (on 32-bit only) |
Word64Rep | unsigned, 64-bit value (on 32-bit only) |
AddrRep | A pointer, but not to a Haskell value |
FloatRep | a 32-bit floating point number |
DoubleRep | a 64-bit floating point number |
UnboxedTupleRep | An unboxed tuple; this doesn't specify a concrete rep |
Element of a SIMD vector type
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
Provides Show
and Read
instances (since: 4.7.0.0).
Since: 4.6.0.0
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 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 :: Eq a => [a] -> a Source #
the
ensures that all the elements of the list are identical
and then returns that unique element
Event logging
traceEvent :: String -> IO () Source #
Deprecated: Use traceEvent
or traceEventIO
SpecConstr annotations
data SpecConstrAnnotation Source #
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.
Since: 4.5.0.0
The Constraint kind
data Constraint :: * Source #
The kind of constraints, like Show a
Overloaded lists
The IsList
class and its methods are intended to be used in
conjunction with the OverloadedLists extension.
Since: 4.7.0.0
fromList :: [Item l] -> l Source #
The fromList
function constructs the structure l
from the given
list of Item l
fromListN :: Int -> [Item l] -> l Source #
The fromListN
function takes the input list's length as a hint. Its
behaviour should be equivalent to fromList
. The hint can be used to
construct the structure l
more efficiently compared to fromList
. If
the given hint does not equal to the input list's length the behaviour of
fromListN
is not specified.
toList :: l -> [Item l] Source #
The toList
function extracts a list of Item l
from the structure l
.
It should satisfy fromList . toList = id.