Pragma not recognised when wrapped in #ifdef
Simon Marlow
marlowsd at gmail.com
Tue Feb 10 08:43:32 EST 2009
Simon Peyton-Jones wrote:
> I'm guessing a bit here, but it looks as if you intend this:
>
> * GHC should read Foo.hs, and see {-# LANGUAGE CPP #-}
> * Then it should run cpp
> * Then it should look *again* in the result of running cpp,
> to see the now-revealed {-# LANGUAGE DeriveDataTypeable #-}
>
> I'm pretty sure we don't do that; that is, we get the command-line flags once for all from the pre-cpp'd source code. Simon or Ian may be able to confirm.
Spot on.
> If so, then this amounts to
> a) a documentation bug: it should be clear what GHC does
Right, I checked the docs and it doesn't explicitly say this.
> b) a feature request, to somehow allow cpp to affect in-file flags
> I'm not sure what the spec would be
It needs a bit of thought - what should happen to pragmas that are there
pre-CPP but not post-CPP, for example?
Cheers,
Simon
>
> | -----Original Message-----
> | From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-
> | bounces at haskell.org] On Behalf Of Alistair Bayley
> | Sent: Tuesday, February 10, 2009 12:03 PM
> | To: GHC Users Mailing List
> | Subject: Re: Pragma not recognised when wrapped in #ifdef
> |
> | > {-# LANGUAGE CPP #-}
> | > #ifdef PRAGMA_DERIVE_TYPEABLE
> | > {-# LANGUAGE DeriveDataTypeable #-}
> | > #else
> | > {-# OPTIONS -fglasgow-exts #-}
> | > #endif
> | > -- This file is Test/Fail.hs.
> | > -- ghc --make -optP-DPRAGMA_DERIVE_TYPEABLE -XCPP Test.Fail
> | > module Test.Fail where
> | > import Data.Generics
> | > data Fail = Fail deriving Typeable
> | >
> | > If compile this wih the command
> | > ghc --make -optP-DPRAGMA_DERIVE_TYPEABLE -XCPP Test.Fail
> | > then I get this error from ghc-6.10.1:
> | >
> | > [1 of 1] Compiling Test.Fail ( Test\Fail.hs, Test\Fail.o )
> | >
> | > Test\Fail.hs:11:26:
> | > Can't make a derived instance of `Typeable Fail'
> | > (You need -XDeriveDataTypeable to derive an instance for this class)
> | > In the data type declaration for `Fail'
> |
> |
> | No response. I'd like to know if this is a bug (that's what it looks
> | like to me), or just a mistake I've made.
> |
> | Thanks,
> | Alistair
> | _______________________________________________
> | Glasgow-haskell-users mailing list
> | Glasgow-haskell-users at haskell.org
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>
>
> ------------------------------------------------------------------------
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list