GHC supports several pragmas, or instructions to the compiler placed in the source code. Pragmas don't normally affect the meaning of the program, but they might affect the efficiency of the generated code.
Pragmas all take the form
{-#
where word
... #-}word
indicates the type of
pragma, and is followed optionally by information specific to that
type of pragma. Case is ignored in
word
. The various values for
word
that GHC understands are described
in the following sections; any pragma encountered with an
unrecognised word
is (silently)
ignored.
The DEPRECATED pragma lets you specify that a particular function, class, or type, is deprecated. There are two forms.
You can deprecate an entire module thus:
module Wibble {-# DEPRECATED "Use Wobble instead" #-} where ...
When you compile any module that import
Wibble
, GHC will print the specified
message.
You can deprecate a function, class, type, or data constructor, with the following top-level declaration:
{-# DEPRECATED f, C, T "Don't use these" #-}
When you compile any module that imports and uses any of the specified entities, GHC will print the specified message.
You can only depecate entities declared at top level in the module
being compiled, and you can only use unqualified names in the list of
entities being deprecated. A capitalised name, such as T
refers to either the type constructor T
or the data constructor T
, or both if
both are in scope. If both are in scope, there is currently no way to deprecate
one without the other (c.f. fixities Section 7.4.1.2, “Infix type constructors, classes, and type variables”).
Any use of the deprecated item, or of anything from a deprecated module, will be flagged with an appropriate message. However, deprecations are not reported for (a) uses of a deprecated function within its defining module, and (b) uses of a deprecated function in an export list. The latter reduces spurious complaints within a library in which one module gathers together and re-exports the exports of several others.
You can suppress the warnings with the flag
-fno-warn-deprecations
.
The INCLUDE
pragma is for specifying the names
of C header files that should be #include
'd into
the C source code generated by the compiler for the current module (if
compiling via C). For example:
{-# INCLUDE "foo.h" #-} {-# INCLUDE <stdio.h> #-}
The INCLUDE
pragma(s) must appear at the top of
your source file with any OPTIONS_GHC
pragma(s).
An INCLUDE
pragma is the preferred alternative
to the -#include
option (Section 4.10.5, “Options affecting the C compiler (if applicable)”), because the
INCLUDE
pragma is understood by other
compilers. Yet another alternative is to add the include file to each
foreign import
declaration in your code, but we
don't recommend using this approach with GHC.
These pragmas control the inlining of function definitions.
GHC (with -O
, as always) tries to
inline (or “unfold”) functions/values that are
“small enough,” thus avoiding the call overhead
and possibly exposing other more-wonderful optimisations.
Normally, if GHC decides a function is “too
expensive” to inline, it will not do so, nor will it
export that unfolding for other modules to use.
The sledgehammer you can bring to bear is the
INLINE
pragma, used thusly:
key_function :: Int -> String -> (Bool, Double) #ifdef __GLASGOW_HASKELL__ {-# INLINE key_function #-} #endif
(You don't need to do the C pre-processor carry-on
unless you're going to stick the code through HBC—it
doesn't like INLINE
pragmas.)
The major effect of an INLINE
pragma
is to declare a function's “cost” to be very low.
The normal unfolding machinery will then be very keen to
inline it.
Syntactically, an INLINE
pragma for a
function can be put anywhere its type signature could be
put.
INLINE
pragmas are a particularly
good idea for the
then
/return
(or
bind
/unit
) functions in
a monad. For example, in GHC's own
UniqueSupply
monad code, we have:
#ifdef __GLASGOW_HASKELL__ {-# INLINE thenUs #-} {-# INLINE returnUs #-} #endif
See also the NOINLINE
pragma (Section 7.10.3.2, “NOINLINE pragma”).
The NOINLINE
pragma does exactly what
you'd expect: it stops the named function from being inlined
by the compiler. You shouldn't ever need to do this, unless
you're very cautious about code size.
NOTINLINE
is a synonym for
NOINLINE
(NOINLINE
is
specified by Haskell 98 as the standard way to disable
inlining, so it should be used if you want your code to be
portable).
Sometimes you want to control exactly when in GHC's
pipeline the INLINE pragma is switched on. Inlining happens
only during runs of the simplifier. Each
run of the simplifier has a different phase
number; the phase number decreases towards zero.
If you use -dverbose-core2core
you'll see the
sequence of phase numbers for successive runs of the
simplifier. In an INLINE pragma you can optionally specify a
phase number, thus:
"INLINE[k] f
" means: do not inline
f
until phase k
, but from phase
k
onwards be very keen to inline it.
"INLINE[~k] f
" means: be very keen to inline
f
until phase k
, but from phase
k
onwards do not inline it.
"NOINLINE[k] f
" means: do not inline
f
until phase k
, but from phase
k
onwards be willing to inline it (as if
there was no pragma).
"INLINE[~k] f
" means: be willing to inline
f
until phase k
, but from phase
k
onwards do not inline it.
The same information is summarised here:
-- Before phase 2 Phase 2 and later {-# INLINE [2] f #-} -- No Yes {-# INLINE [~2] f #-} -- Yes No {-# NOINLINE [2] f #-} -- No Maybe {-# NOINLINE [~2] f #-} -- Maybe No {-# INLINE f #-} -- Yes Yes {-# NOINLINE f #-} -- No No
By "Maybe" we mean that the usual heuristic inlining rules apply (if the function body is small, or it is applied to interesting-looking arguments etc). Another way to understand the semantics is this:
For both INLINE and NOINLINE, the phase number says when inlining is allowed at all.
The INLINE pragma has the additional effect of making the function body look small, so that when inlining is allowed it is very likely to happen.
The same phase-numbering control is available for RULES (Section 7.11, “Rewrite rules ”).
This allows language extensions to be enabled in a portable way.
It is the intention that all Haskell compilers support the
LANGUAGE
pragma with the same syntax, although not
all extensions are supported by all compilers, of
course. The LANGUAGE
pragma should be used instead
of OPTIONS_GHC
, if possible.
For example, to enable the FFI and preprocessing with CPP:
{-# LANGUAGE ForeignFunctionInterface, CPP #-}
Any extension from the Extension
type defined in
Language.Haskell.Extension
may be used. GHC will report an error if any of the requested extensions are not supported.
This pragma is similar to C's #line
pragma, and is mainly for use in automatically generated Haskell
code. It lets you specify the line number and filename of the
original code; for example
{-# LINE 42 "Foo.vhs" #-}
if you'd generated the current file from something called
Foo.vhs
and this line corresponds to line
42 in the original. GHC will adjust its error messages to refer
to the line/file named in the LINE
pragma.
The OPTIONS_GHC
pragma is used to specify
additional options that are given to the compiler when compiling
this source file. See Section 4.1.2, “command line options in source files” for
details.
Previous versions of GHC accepted OPTIONS
rather
than OPTIONS_GHC
, but that is now deprecated.
The RULES pragma lets you specify rewrite rules. It is described in Section 7.11, “Rewrite rules ”.
(UK spelling also accepted.) For key overloaded functions, you can create extra versions (NB: more code space) specialised to particular types. Thus, if you have an overloaded function:
hammeredLookup :: Ord key => [(key, value)] -> key -> value
If it is heavily used on lists with
Widget
keys, you could specialise it as
follows:
{-# SPECIALIZE hammeredLookup :: [(Widget, value)] -> Widget -> value #-}
A SPECIALIZE
pragma for a function can
be put anywhere its type signature could be put.
A SPECIALIZE
has the effect of generating
(a) a specialised version of the function and (b) a rewrite rule
(see Section 7.11, “Rewrite rules
”) that rewrites a call to the
un-specialised function into a call to the specialised one.
The type in a SPECIALIZE pragma can be any type that is less
polymorphic than the type of the original function. In concrete terms,
if the original function is f
then the pragma
{-# SPECIALIZE f :: <type> #-}
is valid if and only if the defintion
f_spec :: <type> f_spec = f
is valid. Here are some examples (where we only give the type signature for the original function, not its code):
f :: Eq a => a -> b -> b {-# SPECIALISE f :: Int -> b -> b #-} g :: (Eq a, Ix b) => a -> b -> b {-# SPECIALISE g :: (Eq a) => a -> Int -> Int #-} h :: Eq a => a -> a -> a {-# SPECIALISE h :: (Eq a) => [a] -> [a] -> [a] #-}
The last of these examples will generate a RULE with a somewhat-complex left-hand side (try it yourself), so it might not fire very well. If you use this kind of specialisation, let us know how well it works.
A SPECIALIZE
pragma can optionally be followed with a
INLINE
or NOINLINE
pragma, optionally
followed by a phase, as described in Section 7.10.3, “INLINE and NOINLINE pragmas”.
The INLINE
pragma affects the specialised verison of the
function (only), and applies even if the function is recursive. The motivating
example is this:
-- A GADT for arrays with type-indexed representation data Arr e where ArrInt :: !Int -> ByteArray# -> Arr Int ArrPair :: !Int -> Arr e1 -> Arr e2 -> Arr (e1, e2) (!:) :: Arr e -> Int -> e {-# SPECIALISE INLINE (!:) :: Arr Int -> Int -> Int #-} {-# SPECIALISE INLINE (!:) :: Arr (a, b) -> Int -> (a, b) #-} (ArrInt _ ba) !: (I# i) = I# (indexIntArray# ba i) (ArrPair _ a1 a2) !: i = (a1 !: i, a2 !: i)
Here, (!:)
is a recursive function that indexes arrays
of type Arr e
. Consider a call to (!:)
at type (Int,Int)
. The second specialisation will fire, and
the specialised function will be inlined. It has two calls to
(!:)
,
both at type Int
. Both these calls fire the first
specialisation, whose body is also inlined. The result is a type-based
unrolling of the indexing function.
Warning: you can make GHC diverge by using SPECIALISE INLINE
on an ordinarily-recursive function.
Note: In earlier versions of GHC, it was possible to provide your own specialised function for a given type:
{-# SPECIALIZE hammeredLookup :: [(Int, value)] -> Int -> value = intLookup #-}
This feature has been removed, as it is now subsumed by the
RULES
pragma (see Section 7.11.4, “Specialisation
”).
Same idea, except for instance declarations. For example:
instance (Eq a) => Eq (Foo a) where { {-# SPECIALIZE instance Eq (Foo [(Int, Bar)]) #-} ... usual stuff ... }
The pragma must occur inside the where
part
of the instance declaration.
Compatible with HBC, by the way, except perhaps in the placement of the pragma.
The UNPACK
indicates to the compiler
that it should unpack the contents of a constructor field into
the constructor itself, removing a level of indirection. For
example:
data T = T {-# UNPACK #-} !Float {-# UNPACK #-} !Float
will create a constructor T
containing
two unboxed floats. This may not always be an optimisation: if
the T
constructor is scrutinised and the
floats passed to a non-strict function for example, they will
have to be reboxed (this is done automatically by the
compiler).
Unpacking constructor fields should only be used in
conjunction with -O
, in order to expose
unfoldings to the compiler so the reboxing can be removed as
often as possible. For example:
f :: T -> Float f (T f1 f2) = f1 + f2
The compiler will avoid reboxing f1
and f2
by inlining +
on floats, but only when -O
is on.
Any single-constructor data is eligible for unpacking; for example
data T = T {-# UNPACK #-} !(Int,Int)
will store the two Int
s directly in the
T
constructor, by flattening the pair.
Multi-level unpacking is also supported:
data T = T {-# UNPACK #-} !S data S = S {-# UNPACK #-} !Int {-# UNPACK #-} !Int
will store two unboxed Int#
s
directly in the T
constructor. The
unpacker can see through newtypes, too.
If a field cannot be unpacked, you will not get a warning,
so it might be an idea to check the generated code with
-ddump-simpl
.
See also the -funbox-strict-fields
flag,
which essentially has the effect of adding
{-# UNPACK #-}
to every strict
constructor field.