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@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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe