{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.Program.Hpc
( markup
, union
) where
import Prelude ()
import Distribution.Compat.Prelude
import System.Directory (makeRelativeToCurrentDirectory)
import Distribution.ModuleName
import Distribution.Simple.Program.Run
import Distribution.Simple.Program.Types
import Distribution.Pretty
import Distribution.Simple.Utils
import Distribution.Verbosity
import Distribution.Version
markup :: ConfiguredProgram
-> Version
-> Verbosity
-> FilePath
-> [FilePath]
-> FilePath
-> [ModuleName]
-> IO ()
markup :: ConfiguredProgram
-> Version
-> Verbosity
-> FilePath
-> [FilePath]
-> FilePath
-> [ModuleName]
-> IO ()
markup ConfiguredProgram
hpc Version
hpcVer Verbosity
verbosity FilePath
tixFile [FilePath]
hpcDirs FilePath
destDir [ModuleName]
excluded = do
[FilePath]
hpcDirs' <- if Version -> VersionRange -> Bool
withinRange Version
hpcVer (Version -> VersionRange
orLaterVersion Version
version07)
then [FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath]
hpcDirs
else do
Verbosity -> FilePath -> IO ()
warn Verbosity
verbosity (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Your version of HPC (" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow Version
hpcVer
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
") does not properly handle multiple search paths. "
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Coverage report generation may fail unexpectedly. These "
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"issues are addressed in version 0.7 or later (GHC 7.8 or "
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"later)."
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ if [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
droppedDirs
then FilePath
""
else FilePath
" The following search paths have been abandoned: "
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
forall a. Show a => a -> FilePath
show [FilePath]
droppedDirs
[FilePath] -> IO [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath]
passedDirs
[FilePath]
hpcDirs'' <- (FilePath -> IO FilePath) -> [FilePath] -> IO [FilePath]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse FilePath -> IO FilePath
makeRelativeToCurrentDirectory [FilePath]
hpcDirs'
Verbosity -> ProgramInvocation -> IO ()
runProgramInvocation Verbosity
verbosity
(ConfiguredProgram
-> FilePath
-> [FilePath]
-> FilePath
-> [ModuleName]
-> ProgramInvocation
markupInvocation ConfiguredProgram
hpc FilePath
tixFile [FilePath]
hpcDirs'' FilePath
destDir [ModuleName]
excluded)
where
version07 :: Version
version07 = [Int] -> Version
mkVersion [Int
0, Int
7]
([FilePath]
passedDirs, [FilePath]
droppedDirs) = Int -> [FilePath] -> ([FilePath], [FilePath])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
1 [FilePath]
hpcDirs
markupInvocation :: ConfiguredProgram
-> FilePath
-> [FilePath]
-> FilePath
-> [ModuleName]
-> ProgramInvocation
markupInvocation :: ConfiguredProgram
-> FilePath
-> [FilePath]
-> FilePath
-> [ModuleName]
-> ProgramInvocation
markupInvocation ConfiguredProgram
hpc FilePath
tixFile [FilePath]
hpcDirs FilePath
destDir [ModuleName]
excluded =
let args :: [FilePath]
args = [ FilePath
"markup", FilePath
tixFile
, FilePath
"--destdir=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
destDir
]
[FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ (FilePath -> FilePath) -> [FilePath] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath
"--hpcdir=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++) [FilePath]
hpcDirs
[FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
"--exclude=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ModuleName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow ModuleName
moduleName
| ModuleName
moduleName <- [ModuleName]
excluded ]
in ConfiguredProgram -> [FilePath] -> ProgramInvocation
programInvocation ConfiguredProgram
hpc [FilePath]
args
union :: ConfiguredProgram
-> Verbosity
-> [FilePath]
-> FilePath
-> [ModuleName]
-> IO ()
union :: ConfiguredProgram
-> Verbosity -> [FilePath] -> FilePath -> [ModuleName] -> IO ()
union ConfiguredProgram
hpc Verbosity
verbosity [FilePath]
tixFiles FilePath
outFile [ModuleName]
excluded =
Verbosity -> ProgramInvocation -> IO ()
runProgramInvocation Verbosity
verbosity
(ConfiguredProgram
-> [FilePath] -> FilePath -> [ModuleName] -> ProgramInvocation
unionInvocation ConfiguredProgram
hpc [FilePath]
tixFiles FilePath
outFile [ModuleName]
excluded)
unionInvocation :: ConfiguredProgram
-> [FilePath]
-> FilePath
-> [ModuleName]
-> ProgramInvocation
unionInvocation :: ConfiguredProgram
-> [FilePath] -> FilePath -> [ModuleName] -> ProgramInvocation
unionInvocation ConfiguredProgram
hpc [FilePath]
tixFiles FilePath
outFile [ModuleName]
excluded =
ConfiguredProgram -> [FilePath] -> ProgramInvocation
programInvocation ConfiguredProgram
hpc ([FilePath] -> ProgramInvocation)
-> [FilePath] -> ProgramInvocation
forall a b. (a -> b) -> a -> b
$ [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [FilePath
"sum", FilePath
"--union"]
, [FilePath]
tixFiles
, [FilePath
"--output=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
outFile]
, [FilePath
"--exclude=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ModuleName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow ModuleName
moduleName
| ModuleName
moduleName <- [ModuleName]
excluded ]
]