category feedCPPMiscellaneouseditdelete







With {-# LANGUAGE CPP #-} enabled, .hs files will be processed with C preprocessor before the code is compiled. It's often useful if:

  • you need backwards compatibility with an older version of GHC or some library, or you want to avoid compiler warnings
  • you are writing code that depends on OS or CPU architecture
  • you want to enable some parts of code depending on a flag
  • you don't want to bother with Template Haskell and need some easy way to generate code (e.g. repetitive instances)

However, see the Stop (ab)using CPP in Haskell sources post for a discussion of some drawbacks of CPP (and alternatives to it).

Running CPP

To dump CPP output, do ghc -E file.hs (it'll be saved into file.hspp). There might be a lot of empty lines in the file, so don't forget to scroll.

To just run CPP on a file without using GHC, do either of these:

  • gcc -E -traditional - < file.hs (on Linux)
  • clang -E -traditional - < file.hs (on macOS)
  • cpphs file.hs (for cpphs)

Since Clang is used instead of GCC on macOS, and Clang's preprocessor syntax is slightly different, you should use this command to see whether your code would compile under Clang:

$ ghc -pgmP "clang -E -undef -traditional" file.hs

CPP features

Defining macros

#define DOUBLE_QUOTE 34
#define POW(a,b) a ^ (b :: Int)

Once a constant/macro is defined, it'll be substituted everywhere in code (except when it's a part of a string or a word). For instance, POW(2,3) will be replaced with 2 ^ (3 :: Int).

Using constants as flags

#ifdef FOO             /* or #ifndef to check that a constant is *not* defined */
  ...
#endif

Code inside #ifdef ... #endif will be removed unless FOO is defined (which can be done via .cabal or with a #define earlier in the file).

Conditionals

#if __GLASGOW_HASKELL__ < 710
  ...
#endif

#ifdef FOO is actually a shortcut for #if defined(FOO); with #if you can branch on an arbitrary boolean expression (see the GCC manual for full syntax of conditionals). Also, you can have more than two branches with #elif. Note that #define and other CPP directives can be used inside of #if – it's useful when you're writing your own macros.

See the “Standard CPP macros” section in the GHC manual for a full list of macros defined by GHC.

Tricks

Commas

If you need to use a comma in a macro argument, just define a separate macro for the comma:

#define COMMA ,
GEN(a COMMA b COMMA c)

Concatenation

If CPP doesn't understand that a macro should be expanded in some particular place (e.g. if it's a part of a word, or has _ in front of it, etc), you can use /**/:

#define U(x) xbar
U(foo)                         <- expanded into “xbar”
#define U(x) x/**/bar
U(foo)                         <- expanded into “foobar” on GCC
                                  or “foo bar” on Clang

Note that if you don't want a space there, cpphs is your only bet.

Workarounds

There are three main reasons why code with CPP might not work as expected:

  1. You used #, ## or __VA_ARGS__. GHC runs CPP in traditional mode, which disables all advanced features.

  2. OS differences – Linux uses GCC and macOS uses Clang, which are slightly incompatible. Either read Differences between GCC and Clang, or consider using cpphs if you don't want to bother.

  3. You used something that CPP doesn't support well, like:

    • #-} on a separate line without space in front of it.

    • Single or double quotes – CPP tries to handle them smartly and fails.

    • Multiline strings (e.g. "foo\ and \bar" on two separate lines).

    • \ at the end of line (e.g. infix 5 \\) – to fix it, add a comment after \.

edit description
or press Ctrl+Enter to savemarkdown supported
#
Check version of a library
other
move item up move item down edit item info delete item
Summary edit summary

Cabal automatically generates macros (MIN_VERSION_<library>) for all libraries your project depends upon. E.g. you can do something if e.g. bytestring is 0.10.4 or newer:

#if MIN_VERSION_bytestring(0,10,4)
  ...
#endif

If a library has hyphens - in its name, replace them with underscores _:

#if MIN_VERSION_template_haskell(2,11,0)
  ...
#endif
Summary quit editing summary
#
Check GHC version
other
move item up move item down edit item info delete item
Summary edit summary

GHC versions currently in use: 7.8 = 708, 7.10 = 710, 8.0 = 800.

Do something if GHC is older than 7.10:

#if __GLASGOW_HASKELL__ < 710
  ...
#endif

Use different code for GHC 8.0 and older versions:

#if __GLASGOW_HASKELL__ >= 800
  ...
#else
  ...
#endif

If you need to check for patch level as well (e.g. detect GHC 8.0.1 but not 8.0.2), you can use a .cabal flag:

library
  ...
  if impl(ghc == 8.0.1)
    cpp-options: -DGHC_801

For more info on .cabal flags, see Define a .cabal flag.

Summary quit editing summary
#
Define a .cabal flag
other
move item up move item down edit item info delete item
Summary edit summary

Let's say you want to add asserts to your code. First, add a flag to your .cabal file:

Flag asserts
  Description:   Turn on asserts
  Default:       False

library
  exposed-modules: ...

  if flag(asserts)
    cpp-options: -DASSERTS

(It's also possible to define a constant by writing -DFOO=bar.)

Now, to enable a flag during compilation, do this (to disable, use -asserts instead of asserts):

  • Cabal: cabal configure -f asserts
  • Stack: stack build --flag pkgname:asserts

Then you can check for this flag in code:

#ifdef ASSERTS
  ...
#endif
Summary quit editing summary
#
Define a macro
other
move item up move item down edit item info delete item
Summary edit summary

Macros are useful when you need to write repetitive code but don't want to use Template Haskell (either because it's hard or because you want to avoid the compilation time penalty). For example, monad-control uses macros to generate instances, and GHC uses macros to define shorter function names.

The simplest example is defining a synonym for a function:

#define FI fromIntegral

Now FI can be used anywhere instead of fromIntegral. As mentioned in the introduction, it won't be expanded inside strings or words; still, it might be better to undefine it after use:

#undef FI

We can define a more complex macro with parameters. For instance, instead of generating lenses with makeLenses we could do it with macros (sometimes it's a necessary evil, like when you want to define lenses for data families):

#define MAKE_LENS(field, lens) lens f s = (\y -> s {field = y}) <$> f (field s)

-- | Lens for foo.
foo :: Lens' (SomeFamily Int) Foo
MAKE_LENS(foo, _foo)

(Note that we can't get rid of repetition – foo, _foo – without breaking compatibility with Clang. If you use cpphs or don't need your code to compile on macOS, you can use /**/ to add the underscore instead.)

Finally, you can use \ for longer macros:

#define BASE(M)                           \
instance MonadBaseControl (M) (M) where { \
    type StM (M) a = a;                   \
    liftBaseWith f = f id;                \
    restoreM = return;                    \
    {-# INLINABLE liftBaseWith #-};       \
{-# INLINABLE restoreM #-}}

This macro isn't actually multiline, though – it will be expanded into a single line (which is why curly braces were used and there's ; after every line).

Summary quit editing summary
#
Detect OS
other
move item up move item down edit item info delete item
Summary edit summary

The following variables are defined depending on OS:

  • mingw32_HOST_OS – Windows
  • darwin_HOST_OS – macOS
  • ghcjs_HOST_OS – Javascript (when compiling with GHCJS)
  • linux_HOST_OS – Linux (shouldn't be needed most of the time)
  • freebsd_HOST_OS – FreeBSD
  • netbsd_HOST_OS – NetBSD
  • openbsd_HOST_OS – OpenBSD
  • solaris_HOST_OS – Solaris

For instance, here's how you can detect macOS:

#ifdef darwin_HOST_OS
  ...
#endif

Note that despite lots of libraries using #if defined(mingw32_HOST_OS) || defined(__MINGW32__) for detecting Windows, you don't need to do it – just mingw32_HOST_OS will suffice. See this Trac ticket.

Summary quit editing summary
#
Detect architecture
other
move item up move item down edit item info delete item
Summary edit summary

There are variables for detecting architecture:

  • i386_HOST_ARCH – x86
  • x86_64_HOST_ARCH – x64
  • arm_HOST_ARCH – ARM (there's also arm_HOST_ARCH_PRE_ARMv7)
  • powerpc_HOST_ARCH
  • sparc_HOST_ARCH
#if defined(i386_HOST_ARCH)
  ...
#elif defined(x86_64_HOST_ARCH)
  ...
#else
# error Unsupported architecture
#endif

# error Unsupported architecture will emit an error at the CPP step (and stop compilation) if the architecture isn't one of the above.

Summary quit editing summary
#
Detect Hlint
other
move item up move item down edit item info delete item
Summary edit summary

Sometimes you want to hide some code from Hlint (for instance, if Hlint's parser doesn't support a particular language feature yet).

You can do it by defining HLINT (e.g. by writing a script like lens does, or just by passing --cpp-define=HLINT to Hlint) and then wrapping code into an #ifndef HLINT section:

#ifndef HLINT
  ...
#endif
Summary quit editing summary
#
Detect Int/Word size
other
move item up move item down edit item info delete item
Summary edit summary

You can use CPP to find out whether Int and Word have 32 bits, 64 bits, or (if you're unlucky) some other amount of bits. First you'll have to add #include "MachDeps.h" to the beginning of the file. This makes the WORD_SIZE_IN_BITS variable available:

#if (WORD_SIZE_IN_BITS == 64)
  ...
#else
  ...
#endif

There are other constants defined in MachDeps.h as well.

Summary quit editing summary
#
Use cpphs as the preprocessor
other
move item up move item down edit item info delete item
Summary edit summary

Sometimes it's easier to use cpphs than to fight with GCC's and Clang's differences, idiosyncrasies, etc:

[...] There have always been problems with, for instance, string gaps, and prime characters in identifiers. These problems are only going to get worse.

So, it seemed right to provide an alternative to cpp, both more compatible with Haskell, and itself written in Haskell so that it can be distributed with compilers.

Cpphs handles single quotes and /**/ correctly, doesn't mangle Haddock comments and knows about Haskell's multiline strings.

To use cpphs, you need to add these options to all sections of your .cabal file:

library
  ...
  build-tools: cpphs >= 1.19
  ghc-options: -pgmP cpphs -optP --cpp

A warning: Stack will install cpphs automatically, but cabal-install might not (and then you'd have to install it manually). Thus, depending on cpphs isn't recommended for libraries that would be published on Hackage.

If you can't use cpphs because of its modified LGPL license (e.g. in corporate environment where each license has to be vetted by a lawyer), you can use hpp instead.

Summary quit editing summary
#
base-feature-macros (Hackage)
other
move item up move item down edit item info delete item
Summary edit summary

The base-feature-macros package lets you write some macros more conveniently – e.g. instead of #if MIN_VERSION_base(4,8,0) you can write #if HAVE_FOLDABLE_TRAVERSABLE_IN_PRELUDE, which is much more understandable to a casual reader.

Summary quit editing summary
#
Differences between GCC and Clang
other
move item up move item down edit item info delete item
Summary edit summary

On Linux and Windows, GCC's CPP is used for preprocessing; on macOS – Clang's CPP. They have some differences, which you have to account for (unless you're using cpphs).

If you're on Linux, use ghc -pgmP "clang -E -undef -traditional" file.hs to check whether your code would compile with Clang. If you use CI (e.g. Travis-CI), you can add it to your .cabal file in the ghc-options section (hidden under a flag) and run your CI builds both with and without the flag.


Single quotes

Clang is more strict about single quotes than GCC. For instance, this piece of code using -XDataKinds won't be expanded correctly by Clang:

#define X(a) Foo '[a]
X(Int)                         <- expanded into “Foo '[a]”

A workaround is defining a separate macro for ':

#define QUOTE '
#define X(a) Foo QUOTE[a]
X(Int)                         <- expanded into “Foo '[Int]”

If you need to surround something with single quotes, this might help:

#define QUOTE() '
#define QLEFT(a) QUOTE()a
#define Q(a) QLEFT(a)'
Q(Int)                         <- expanded into “'Int'”

Concatenation

GCC expands the following macro as _foo, but Clang adds a space and produces _ foo:

#define U(x) _/**/x
U(foo)

There is no way to get rid of the space on Clang. Either rewrite your code to not need such tricks, or use cpphs.

Summary quit editing summary