Repository : ssh://darcs.haskell.org//srv/darcs/packages/Cabal

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/9f0f4c7dcc2880f274157e172cfd88167ca2b846

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

commit 9f0f4c7dcc2880f274157e172cfd88167ca2b846
Author: Thomas Tuegel <[email protected]>
Date:   Tue Jul 19 00:42:51 2011 +0000

    Added Distribution.Simple.Program.Hpc.

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

 cabal/Distribution/Simple/Program/Hpc.hs |   77 ++++++++++++++++++++++++++++++
 1 files changed, 77 insertions(+), 0 deletions(-)

diff --git a/cabal/Distribution/Simple/Program/Hpc.hs 
b/cabal/Distribution/Simple/Program/Hpc.hs
new file mode 100644
index 0000000..5164170
--- /dev/null
+++ b/cabal/Distribution/Simple/Program/Hpc.hs
@@ -0,0 +1,77 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Distribution.Simple.Program.Hpc
+-- Copyright   :  Thomas Tuegel 2011
+--
+-- Maintainer  :  [email protected]
+-- Portability :  portable
+--
+-- This module provides an library interface to the @hpc@ program.
+
+module Distribution.Simple.Program.Hpc
+    ( markup
+    , union
+    ) where
+
+import Distribution.ModuleName ( ModuleName )
+import Distribution.Simple.Program ( getProgramInvocationOutput )
+import Distribution.Simple.Program.Run ( ProgramInvocation, programInvocation )
+import Distribution.Simple.Program.Types ( ConfiguredProgram )
+import Distribution.Text ( display )
+import Distribution.Verbosity ( Verbosity )
+
+markup :: ConfiguredProgram
+       -> Verbosity
+       -> FilePath            -- ^ Path to .tix file
+       -> FilePath            -- ^ Path to directory with .mix files
+       -> FilePath            -- ^ Path where html output should be located
+       -> [ModuleName]        -- ^ List of modules to exclude from report
+       -> IO ()
+markup hpc verbosity tixFile hpcDir destDir excluded = do
+    _ <- getProgramInvocationOutput verbosity
+        (markupInvocation hpc tixFile hpcDir destDir excluded)
+    return ()
+
+markupInvocation :: ConfiguredProgram
+                 -> FilePath            -- ^ Path to .tix file
+                 -> FilePath            -- ^ Path to directory with .mix files
+                 -> FilePath            -- ^ Path where html output should be
+                                        -- located
+                 -> [ModuleName]        -- ^ List of modules to exclude from
+                                        -- report
+                 -> ProgramInvocation
+markupInvocation hpc tixFile hpcDir destDir excluded =
+    let args = [ "markup", tixFile
+               , "--hpcdir=" ++ hpcDir
+               , "--destdir=" ++ destDir
+               ] ++ exclude excluded
+    in programInvocation hpc args
+
+union :: ConfiguredProgram
+      -> Verbosity
+      -> [FilePath]         -- ^ Paths to .tix files
+      -> FilePath           -- ^ Path to resultant .tix file
+      -> [ModuleName]       -- ^ List of modules to exclude from union
+      -> IO ()
+union hpc verbosity tixFiles outFile excluded = do
+    _ <- getProgramInvocationOutput verbosity
+        $ unionInvocation hpc tixFiles outFile excluded
+    return ()
+
+unionInvocation :: ConfiguredProgram
+                -> [FilePath]       -- ^ Paths to .tix files
+                -> FilePath         -- ^ Path to resultant .tix file
+                -> [ModuleName]     -- ^ List of modules to exclude from union
+                -> ProgramInvocation
+unionInvocation hpc tixFiles outFile excluded =
+    programInvocation hpc $ concat
+        [ ["sum", "--union"]
+        , tixFiles
+        , ["--output=" ++ outFile]
+        , exclude excluded
+        ]
+
+-- | Turn a list of modules to be excluded from coverage results into a list
+-- of command line options to hpc.
+exclude :: [ModuleName] -> [String]
+exclude = map (("--exclude=" ++) . display)



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to