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

Robert Vollmert rvollmert-lists at gmx.net
Mon Apr 28 19:32:42 UTC 2014


On Apr 28, 2014, at 21:17 , Rob Stewart <robstewart57 at gmail.com> wrote:
> 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?

You’re defining ‘CUDA’ to be replaced by the empty string, so after running through CPP, you’ll have

module CPP where
import qualified Data.Array.Accelerate. as 

(Haven’t actually tested this, but it’s what cpp should do, and explains the error message nicely.)

Try using ‘-DWITHCUDA’ or something similar?

Cheers
Rob
 


More information about the Haskell-Cafe mailing list