{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.Hpc
( Way (..)
, guessWay
, htmlDir
, mixDir
, tixDir
, tixFilePath
, HPCMarkupInfo (..)
, markupPackage
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.ModuleName (ModuleName, main)
import Distribution.PackageDescription
( TestSuite (..)
, testModules
)
import qualified Distribution.PackageDescription as PD
import Distribution.Pretty
import Distribution.Simple.LocalBuildInfo (LocalBuildInfo (..))
import Distribution.Simple.Program
( hpcProgram
, requireProgramVersion
)
import Distribution.Simple.Program.Hpc (markup, union)
import Distribution.Simple.Utils (notice)
import Distribution.Types.UnqualComponentName
import Distribution.Verbosity (Verbosity ())
import Distribution.Version (anyVersion)
import System.Directory (createDirectoryIfMissing, doesFileExist)
import System.FilePath
data Way = Vanilla | Prof | Dyn
deriving (Way
Way -> Way -> Bounded Way
forall a. a -> a -> Bounded a
$cminBound :: Way
minBound :: Way
$cmaxBound :: Way
maxBound :: Way
Bounded, Int -> Way
Way -> Int
Way -> [Way]
Way -> Way
Way -> Way -> [Way]
Way -> Way -> Way -> [Way]
(Way -> Way)
-> (Way -> Way)
-> (Int -> Way)
-> (Way -> Int)
-> (Way -> [Way])
-> (Way -> Way -> [Way])
-> (Way -> Way -> [Way])
-> (Way -> Way -> Way -> [Way])
-> Enum Way
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Way -> Way
succ :: Way -> Way
$cpred :: Way -> Way
pred :: Way -> Way
$ctoEnum :: Int -> Way
toEnum :: Int -> Way
$cfromEnum :: Way -> Int
fromEnum :: Way -> Int
$cenumFrom :: Way -> [Way]
enumFrom :: Way -> [Way]
$cenumFromThen :: Way -> Way -> [Way]
enumFromThen :: Way -> Way -> [Way]
$cenumFromTo :: Way -> Way -> [Way]
enumFromTo :: Way -> Way -> [Way]
$cenumFromThenTo :: Way -> Way -> Way -> [Way]
enumFromThenTo :: Way -> Way -> Way -> [Way]
Enum, Way -> Way -> Bool
(Way -> Way -> Bool) -> (Way -> Way -> Bool) -> Eq Way
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Way -> Way -> Bool
== :: Way -> Way -> Bool
$c/= :: Way -> Way -> Bool
/= :: Way -> Way -> Bool
Eq, ReadPrec [Way]
ReadPrec Way
Int -> ReadS Way
ReadS [Way]
(Int -> ReadS Way)
-> ReadS [Way] -> ReadPrec Way -> ReadPrec [Way] -> Read Way
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Way
readsPrec :: Int -> ReadS Way
$creadList :: ReadS [Way]
readList :: ReadS [Way]
$creadPrec :: ReadPrec Way
readPrec :: ReadPrec Way
$creadListPrec :: ReadPrec [Way]
readListPrec :: ReadPrec [Way]
Read, Int -> Way -> ShowS
[Way] -> ShowS
Way -> String
(Int -> Way -> ShowS)
-> (Way -> String) -> ([Way] -> ShowS) -> Show Way
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Way -> ShowS
showsPrec :: Int -> Way -> ShowS
$cshow :: Way -> String
show :: Way -> String
$cshowList :: [Way] -> ShowS
showList :: [Way] -> ShowS
Show)
hpcDir
:: FilePath
-> Way
-> FilePath
hpcDir :: String -> Way -> String
hpcDir String
distPref Way
way = String
distPref String -> ShowS
</> String
"hpc" String -> ShowS
</> String
wayDir
where
wayDir :: String
wayDir = case Way
way of
Way
Vanilla -> String
"vanilla"
Way
Prof -> String
"prof"
Way
Dyn -> String
"dyn"
mixDir
:: FilePath
-> Way
-> FilePath
mixDir :: String -> Way -> String
mixDir String
distPref Way
way = String -> Way -> String
hpcDir String
distPref Way
way String -> ShowS
</> String
"mix"
tixDir
:: FilePath
-> Way
-> FilePath
tixDir :: String -> Way -> String
tixDir String
distPref Way
way = String -> Way -> String
hpcDir String
distPref Way
way String -> ShowS
</> String
"tix"
tixFilePath
:: FilePath
-> Way
-> FilePath
-> FilePath
tixFilePath :: String -> Way -> ShowS
tixFilePath String
distPref Way
way String
name = String -> Way -> String
tixDir String
distPref Way
way String -> ShowS
</> String
name String -> ShowS
<.> String
"tix"
htmlDir
:: FilePath
-> Way
-> FilePath
htmlDir :: String -> Way -> String
htmlDir String
distPref Way
way = String -> Way -> String
hpcDir String
distPref Way
way String -> ShowS
</> String
"html"
guessWay :: LocalBuildInfo -> Way
guessWay :: LocalBuildInfo -> Way
guessWay LocalBuildInfo
lbi
| LocalBuildInfo -> Bool
withProfExe LocalBuildInfo
lbi = Way
Prof
| LocalBuildInfo -> Bool
withDynExe LocalBuildInfo
lbi = Way
Dyn
| Bool
otherwise = Way
Vanilla
data HPCMarkupInfo = HPCMarkupInfo
{ HPCMarkupInfo -> [String]
pathsToLibsArtifacts :: [FilePath]
, HPCMarkupInfo -> [ModuleName]
libsModulesToInclude :: [ModuleName]
}
markupPackage
:: Verbosity
-> HPCMarkupInfo
-> LocalBuildInfo
-> FilePath
-> PD.PackageDescription
-> [TestSuite]
-> IO ()
markupPackage :: Verbosity
-> HPCMarkupInfo
-> LocalBuildInfo
-> String
-> PackageDescription
-> [TestSuite]
-> IO ()
markupPackage Verbosity
verbosity HPCMarkupInfo{[String]
pathsToLibsArtifacts :: HPCMarkupInfo -> [String]
pathsToLibsArtifacts :: [String]
pathsToLibsArtifacts, [ModuleName]
libsModulesToInclude :: HPCMarkupInfo -> [ModuleName]
libsModulesToInclude :: [ModuleName]
libsModulesToInclude} LocalBuildInfo
lbi String
testDistPref PackageDescription
pkg_descr [TestSuite]
suites = do
let tixFiles :: [String]
tixFiles = ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Way -> ShowS
tixFilePath String
testDistPref Way
way) [String]
testNames
tixFilesExist <- (String -> IO Bool) -> [String] -> IO [Bool]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse String -> IO Bool
doesFileExist [String]
tixFiles
when (and tixFilesExist) $ do
(hpc, hpcVer, _) <-
requireProgramVersion
verbosity
hpcProgram
anyVersion
(withPrograms lbi)
let htmlDir' = String -> Way -> String
htmlDir String
testDistPref Way
way
tixFile <- case suites of
[TestSuite
oneTest] -> do
let testName' :: String
testName' = UnqualComponentName -> String
unUnqualComponentName (UnqualComponentName -> String) -> UnqualComponentName -> String
forall a b. (a -> b) -> a -> b
$ TestSuite -> UnqualComponentName
testName TestSuite
oneTest
String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$
String -> Way -> ShowS
tixFilePath String
testDistPref Way
way String
testName'
[TestSuite]
_ -> do
let excluded :: [ModuleName]
excluded = (TestSuite -> [ModuleName]) -> [TestSuite] -> [ModuleName]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TestSuite -> [ModuleName]
testModules [TestSuite]
suites [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ [ModuleName
main]
pkgName :: String
pkgName = PackageIdentifier -> String
forall a. Pretty a => a -> String
prettyShow (PackageIdentifier -> String) -> PackageIdentifier -> String
forall a b. (a -> b) -> a -> b
$ PackageDescription -> PackageIdentifier
PD.package PackageDescription
pkg_descr
summedTixFile :: String
summedTixFile = String -> Way -> ShowS
tixFilePath String
testDistPref Way
way String
pkgName
Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ ShowS
takeDirectory String
summedTixFile
ConfiguredProgram
-> Verbosity -> [String] -> String -> [ModuleName] -> IO ()
union ConfiguredProgram
hpc Verbosity
verbosity [String]
tixFiles String
summedTixFile [ModuleName]
excluded
String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
summedTixFile
markup hpc hpcVer verbosity tixFile mixDirs htmlDir' libsModulesToInclude
notice verbosity $
"Package coverage report written to "
++ htmlDir'
</> "hpc_index.html"
where
way :: Way
way = LocalBuildInfo -> Way
guessWay LocalBuildInfo
lbi
testNames :: [String]
testNames = (TestSuite -> String) -> [TestSuite] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UnqualComponentName -> String
unUnqualComponentName (UnqualComponentName -> String)
-> (TestSuite -> UnqualComponentName) -> TestSuite -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestSuite -> UnqualComponentName
testName) [TestSuite]
suites
mixDirs :: [String]
mixDirs = ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Way -> String
`mixDir` Way
way) [String]
pathsToLibsArtifacts