[Haskell-cafe] Parse error when #ifdef pragma enabled

Sylvain Henry hsyl20 at gmail.com
Mon Apr 28 19:30:14 UTC 2014


CUDA is substituted in
> import qualified Data.Array.Acceletare.*CUDA* as *CUDA*
with nothing.

-Sylvain


2014-04-28 21:17 GMT+02:00 Rob Stewart <robstewart57 at gmail.com>:

> Hi,
>
> I'm missing something obvious. I'd like to compile the following code.
>
> --8<---------------cut here---------------start------------->8---
> {-# LANGUAGE CPP #-}
>
> module CPP where
>
> #ifdef CUDA
> import qualified Data.Array.Accelerate.CUDA as CUDA
> #endif
>
> f = "lolcats"
> --8<---------------cut here---------------end--------------->8---
>
> Without the CUDA pragma, it's all good:
>
> $ ghc --make CPP.hs
> [1 of 1] Compiling CPP              ( CPP.hs, CPP.o )
>
> With the pragma thought, I get a compilation error:
>
> $ ghc --make CPP.hs -DCUDA
> [1 of 1] Compiling CPP              ( CPP.hs, CPP.o )
> CPP.hs:6:39: parse error on input `.'
>
> Where's my mistake?
>
> Thanks!
>
> --
> Rob
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140428/1ea8456d/attachment.html>


More information about the Haskell-Cafe mailing list