#6144: Preprocessor line control suppressed by comments
------------------------------+---------------------------------------------
 Reporter:  holzensp          |          Owner:                   
     Type:  bug               |         Status:  new              
 Priority:  normal            |      Component:  Compiler (Parser)
  Version:  7.4.1             |       Keywords:                   
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple 
  Failure:  Other             |       Testcase:                   
Blockedby:                    |       Blocking:                   
  Related:                    |  
------------------------------+---------------------------------------------
 Using the preprocessor and "purely functional" parser from the GHC API,
 SrcSpan annotations in the AST turned out wrong. I have created a minimal
 example to reproduce. It comprises three files, PPBugDemo.hs, ppbug.hs and
 ppbug.h. PPBugDemo is the program calling the GHC API. It prints the
 contents of ppbug.hs and ppbug.h, to show clearly what goes wrong.

 Here is PPBugDemo:

 {{{
 module PPBugDemo where

 import GHC
 import GHC.Paths
 import DriverPipeline
 import DriverPhases
 import HscMain
 import DynFlags
 import ErrUtils
 import Outputable
 import System.Directory

 main :: IO ()
 main = do
         {- Initialising Ghc and getting dynflags + environment -}
         (df,env) <- defaultErrorHandler defaultLogAction $ runGhc (Just
 libdir) $ do
                 fs' <- getSessionDynFlags
                 let fs = fs' { includePaths = includePaths fs' ++ ["."] }
                 setSessionDynFlags fs
                 s <- getSession
                 return (fs,s)

         {- Running the preprocessor and cleaning up after it;
          - it *must* (don't know why) go via a temp-file -}
         (df,fn') <- preprocess env ("ppbug.hs", Just $ Cpp HsSrcFile)
         cnt <- readFile fn'
         removeFile fn'

         {- Warnings aren't relevant to this example, so ignore them -}
         let res = either (printBagOfErrors df >> fail "FAILED") snd
 (parser cnt df "ppbug.hs")

         {- Reporting results -}
         let showCnt = unlines . zipWith (\n l -> show n ++ '\t':l) [1..] .
 lines
         org <- readFile "ppbug.hs"
         hdr <- readFile "ppbug.h"
         putStrLn $ "Original file:\n"     ++ showCnt org
         putStrLn $ "Header file:\n"       ++ showCnt hdr
         putStrLn $ "Preprocessed file:\n" ++ showCnt cnt
         putStrLn . showSDocDebug . ppr $ res
 }}}

 and here is the resulting output:


 {{{
 Original file:
 1       {-# LANGUAGE CPP #-}
 2       {-
 3       #include "ppbug.h"
 4       -}
 5       type Foo = Int
 6

 Header file:
 1       bar [] = []
 2       bar (x:xs) = bar xs

 Preprocessed file:
 1       # 1 "ppbug.hs"
 2       # 1 "<built-in>"
 3       # 1 "<command-line>"
 4       # 1 "ppbug.hs"
 5       {-# LANGUAGE CPP #-}
 6       {-
 7
 8       # 1 "ppbug.h" 1
 9       bar [] = []
 10      bar (x:xs) = bar xs
 11      # 4 "ppbug.hs" 2
 12      -}
 13      type Foo = Int
 14

 {ppbug.hs:1:1}
 {ppbug.hs:9:1-14}
 type {ppbug.hs:9:6-8}
      Foo{tc} =
     {ppbug.hs:9:12-14}
     Int{tc}
 }}}

 The parser has annotated the AST with location information for Foo. It
 says it's on line 9 of ppbug.hs, whilst it actually came from line 5. Line
 11 from the output of the preprocessor sets the line number back to 4
 (starting from line 12), but it seems this line control is ignored for
 residing in {- -} comments.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6144>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to