[GHC] #10942: CPP pragma ignored if top comments and Opt_KeepRawTokenStream
GHC
ghc-devs at haskell.org
Wed Oct 7 12:48:01 UTC 2015
#10942: CPP pragma ignored if top comments and Opt_KeepRawTokenStream
-------------------------------------+-------------------------------------
Reporter: alanz | Owner: alanz
Type: bug | Status: new
Priority: normal | Milestone: 8.0.1
Component: Compiler | Version: 7.10.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): |
-------------------------------------+-------------------------------------
HaRe sets `Opt_KeepRawTokenStream` to be able to round trip the source
code.
If we have a module starting
{{{#!hs
{-
A normal comment, to check if we can still pick up the CPP directive after
it.
-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE CPP #-}
-- Check that we can parse a file which requires CPP
module BCpp where
bob :: Int -> Int -> Int
#if __GLASGOW_HASKELL__ > 704
bob x y = x + y
#else
bob x y = x + y * 2
#endif
}}}
then the call to `loadTargets` via the GHC API fails with
`SourceError (lexical error at character 'i'` which is the normal error
when `#if` is hit and CPP is not enabled.
If `Opt_KeepRawTokenStream` is not set it loads without problems.
Also, files using CPP but not having a top comment load properly too.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10942>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list