[commit: ghc] master: Fix `ghc --make -fhpc` with imported lhs modules (f9344f3)

git at git.haskell.org git at git.haskell.org
Mon Mar 9 19:43:42 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/f9344f3646156a9efff2dcfb90e1d5d67fd4f5a1/ghc

>---------------------------------------------------------------

commit f9344f3646156a9efff2dcfb90e1d5d67fd4f5a1
Author: Thomas Miedema <thomasmiedema at gmail.com>
Date:   Tue Mar 3 23:03:44 2015 +0100

    Fix `ghc --make -fhpc` with imported lhs modules
    
    See Note [Don't normalise input filenames] in
    `compiler/main/DriverPipeline.hs`. Fixes #2991.
    
    Reviewers: austin
    
    Differential Revision: https://phabricator.haskell.org/D701


>---------------------------------------------------------------

f9344f3646156a9efff2dcfb90e1d5d67fd4f5a1
 compiler/main/DriverPipeline.hs               | 68 ++++++++++++++++++++++++++-
 testsuite/tests/{annotations => hpc}/Makefile |  0
 testsuite/tests/hpc/T2991.hs                  |  5 ++
 testsuite/tests/hpc/T2991LiterateModule.lhs   |  4 ++
 testsuite/tests/hpc/all.T                     | 17 +++++++
 5 files changed, 92 insertions(+), 2 deletions(-)

diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index 2d7ee46..24df3a2 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -809,7 +809,8 @@ runPhase (RealPhase (Unlit sf)) input_fn dflags
        let flags = [ -- The -h option passes the file name for unlit to
                      -- put in a #line directive
                      SysTools.Option     "-h"
-                   , SysTools.Option $ escape $ normalise input_fn
+                     -- See Note [Don't normalise input filenames].
+                   , SysTools.Option $ escape input_fn
                    , SysTools.FileOption "" input_fn
                    , SysTools.FileOption "" output_fn
                    ]
@@ -821,7 +822,7 @@ runPhase (RealPhase (Unlit sf)) input_fn dflags
        -- escape the characters \, ", and ', but don't try to escape
        -- Unicode or anything else (so we don't use Util.charToC
        -- here).  If we get this wrong, then in
-       -- Coverage.addTicksToBinds where we check that the filename in
+       -- Coverage.isGoodTickSrcSpan where we check that the filename in
        -- a SrcLoc is the same as the source filenaame, the two will
        -- look bogusly different. See test:
        -- libraries/hpc/tests/function/subdir/tough2.hs
@@ -2327,3 +2328,66 @@ getGhcVersionPathName dflags = do
 --       3c:  2f 00 00 00     sethi  %hi(0), %l7
 --    -                       3c: R_SPARC_PC22        _GLOBAL_OFFSET_TABLE_-0x8
 --    +                       3c: R_SPARC_HI22        _GLOBAL_OFFSET_TABLE_-0x8
+
+{- Note [Don't normalise input filenames]
+
+Summary
+  We used to normalise input filenames when starting the unlit phase. This
+  broke hpc in `--make` mode with imported literate modules (#2991).
+
+Introduction
+  1) --main
+  When compiling a module with --main, GHC scans its imports to find out which
+  other modules it needs to compile too. It turns out that there is a small
+  difference between saying `ghc --make A.hs`, when `A` imports `B`, and
+  specifying both modules on the command line with `ghc --make A.hs B.hs`. In
+  the former case, the filename for B is inferred to be './B.hs' instead of
+  'B.hs'.
+
+  2) unlit
+  When GHC compiles a literate haskell file, the source code first needs to go
+  through unlit, which turns it into normal Haskell source code. At the start
+  of the unlit phase, in `Driver.Pipeline.runPhase`, we call unlit with the
+  option `-h` and the name of the original file. We used to normalise this
+  filename using System.FilePath.normalise, which among other things removes
+  an initial './'. unlit then uses that filename in #line directives that it
+  inserts in the transformed source code.
+
+  3) SrcSpan
+  A SrcSpan represents a portion of a source code file. It has fields
+  linenumber, start column, end column, and also a reference to the file it
+  originated from. The SrcSpans for a literate haskell file refer to the
+  filename that was passed to unlit -h.
+
+  4) -fhpc
+  At some point during compilation with -fhpc, in the function
+  `deSugar.Coverage.isGoodTickSrcSpan`, we compare the filename that a
+  `SrcSpan` refers to with the name of the file we are currently compiling.
+  For some reason I don't yet understand, they can sometimes legitimally be
+  different, and then hpc ignores that SrcSpan.
+
+Problem
+  When running `ghc --make -fhpc A.hs`, where `A.hs` imports the literate
+  module `B.lhs`, `B` is inferred to be in the file `./B.lhs` (1). At the
+  start of the unlit phase, the name `./B.lhs` is normalised to `B.lhs` (2).
+  Therefore the SrcSpans of `B` refer to the file `B.lhs` (3), but we are
+  still compiling `./B.lhs`. Hpc thinks these two filenames are different (4),
+  doesn't include ticks for B, and we have unhappy customers (#2991).
+
+Solution
+  Do not normalise `input_fn` when starting the unlit phase.
+
+Alternative solution
+  Another option would be to not compare the two filenames on equality, but to
+  use System.FilePath.equalFilePath. That function first normalises its
+  arguments. The problem is that by the time we need to do the comparison, the
+  filenames have been turned into FastStrings, probably for performance
+  reasons, so System.FilePath.equalFilePath can not be used directly.
+
+Archeology
+  The call to `normalise` was added in a commit called "Fix slash
+  direction on Windows with the new filePath code" (c9b6b5e8). The problem
+  that commit was addressing has since been solved in a different manner, in a
+  commit called "Fix the filename passed to unlit" (1eedbc6b). So the
+  `normalise` is no longer necessary.
+-}
diff --git a/testsuite/tests/annotations/Makefile b/testsuite/tests/hpc/Makefile
similarity index 100%
copy from testsuite/tests/annotations/Makefile
copy to testsuite/tests/hpc/Makefile
diff --git a/testsuite/tests/hpc/T2991.hs b/testsuite/tests/hpc/T2991.hs
new file mode 100644
index 0000000..451e1eb
--- /dev/null
+++ b/testsuite/tests/hpc/T2991.hs
@@ -0,0 +1,5 @@
+module Main where
+-- Test that there are actually entries in the .mix file for an imported
+-- literate module generated with --make.
+import T2991LiterateModule
+main = return ()
diff --git a/testsuite/tests/hpc/T2991LiterateModule.lhs b/testsuite/tests/hpc/T2991LiterateModule.lhs
new file mode 100644
index 0000000..55fc31c
--- /dev/null
+++ b/testsuite/tests/hpc/T2991LiterateModule.lhs
@@ -0,0 +1,4 @@
+\begin{code}
+module T2991LiterateModule where
+cover_me = 1
+\end{code}
diff --git a/testsuite/tests/hpc/all.T b/testsuite/tests/hpc/all.T
new file mode 100644
index 0000000..d279018
--- /dev/null
+++ b/testsuite/tests/hpc/all.T
@@ -0,0 +1,17 @@
+# Do not explicitly specify '-fhpc' in extra_hc_opts, unless also setting
+# '-hpcdir' to a different value for each test. Only the `hpc` way does this
+# automatically. This way the tests in this directory can be run concurrently
+# (Main.mix might overlap otherwise).
+
+setTestOpts([only_compiler_types(['ghc']),
+             only_ways(['hpc']),
+             ])
+
+def T2991(cmd):
+  # The .mix file for the literate module should have non-zero entries.
+  # The `grep` should exit with exit code 0.
+  return(cmd + " && grep -q cover_me .hpc.T2991/T2991LiterateModule.mix")
+test('T2991', [cmd_wrapper(T2991), extra_clean(['T2991LiterateModule.hi',
+                                                'T2991LiterateModule.o'])],
+              # Run with 'ghc --main'. Do not list other modules explicitly.
+              multimod_compile_and_run, ['T2991', ''])



More information about the ghc-commits mailing list