The Haskell 98 Report
top | back | next | contents | function index

11  Compiler Pragmas

Some compiler implementations support compiler pragmas, which are used to give additional instructions or hints to the compiler, but which do not form part of the Haskell language proper and do not change a program's semantics. This chapter summarizes this existing practice. An implementation is not required to respect any pragma, but the pragma should be ignored if an implementation is not prepared to handle it. Lexically, pragmas appear as comments, except that the enclosing syntax is {-# #-}.

11.1  Inlining

decl -> {-# INLINE qvars #-}
decl -> {-# NOINLINE qvars #-}

The INLINE pragma instructs the compiler to inline the specified variables at their use sites. Compilers will often automatically inline simple expressions. This may be prevented by the NOINLINE pragma.

11.2  Specialization

decl -> {-# SPECIALIZE spec1 , ... , speck #-} (k>=1)
spec -> vars :: type
Specialization is used to avoid inefficiencies involved in dispatching overloaded functions. For example, in

factorial :: Num a => a -> a
factorial 0 = 0
factorial n = n * factorial (n-1)
{-# SPECIALIZE factorial :: Int -> Int,
               factorial :: Integer -> Integer #-}

calls to factorial in which the compiler can detect that the parameter is either Int or Integer will use specialized versions of factorial which do not involve overloaded numeric operations.


The Haskell 98 Report
top | back | next | contents | function index
December 2002