module Distribution.Simple.Hpc
    ( Way(..), guessWay
    , htmlDir
    , mixDir
    , tixDir
    , tixFilePath
    , markupPackage
    , markupTest
    ) where
import Control.Monad ( when )
import Distribution.ModuleName ( main )
import Distribution.PackageDescription
    ( TestSuite(..)
    , testModules
    )
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.Version ( anyVersion )
import Distribution.Verbosity ( Verbosity() )
import System.Directory ( createDirectoryIfMissing, doesFileExist )
import System.FilePath
data Way = Vanilla | Prof | Dyn
  deriving (Bounded, Enum, Eq, Read, Show)
hpcDir :: FilePath  
       -> Way
       -> FilePath  
hpcDir distPref way = distPref </> "hpc" </> wayDir
  where
    wayDir = case way of
      Vanilla -> "vanilla"
      Prof -> "prof"
      Dyn -> "dyn"
mixDir :: FilePath  
       -> Way
       -> FilePath  
       -> FilePath  
mixDir distPref way name = hpcDir distPref way </> "mix" </> name
tixDir :: FilePath  
       -> Way
       -> FilePath  
       -> FilePath  
tixDir distPref way name = hpcDir distPref way </> "tix" </> name
tixFilePath :: FilePath     
            -> Way
            -> FilePath     
            -> FilePath     
tixFilePath distPref way name = tixDir distPref way name </> name <.> "tix"
htmlDir :: FilePath     
        -> Way
        -> FilePath     
        -> FilePath     
htmlDir distPref way name = hpcDir distPref way </> "html" </> name
guessWay :: LocalBuildInfo -> Way
guessWay lbi
  | withProfExe lbi = Prof
  | withDynExe lbi = Dyn
  | otherwise = Vanilla
markupTest :: Verbosity
           -> LocalBuildInfo
           -> FilePath     
           -> String       
           -> TestSuite
           -> IO ()
markupTest verbosity lbi distPref libName suite = do
    tixFileExists <- doesFileExist $ tixFilePath distPref way $ testName suite
    when tixFileExists $ do
        
        
        (hpc, hpcVer, _) <- requireProgramVersion verbosity
            hpcProgram anyVersion (withPrograms lbi)
        let htmlDir_ = htmlDir distPref way $ testName suite
        markup hpc hpcVer verbosity
            (tixFilePath distPref way $ testName suite) mixDirs
            htmlDir_
            (testModules suite ++ [ main ])
        notice verbosity $ "Test coverage report written to "
                            ++ htmlDir_ </> "hpc_index" <.> "html"
  where
    way = guessWay lbi
    mixDirs = map (mixDir distPref way) [ testName suite, libName ]
markupPackage :: Verbosity
              -> LocalBuildInfo
              -> FilePath       
              -> String         
              -> [TestSuite]
              -> IO ()
markupPackage verbosity lbi distPref libName suites = do
    let tixFiles = map (tixFilePath distPref way . testName) suites
    tixFilesExist <- mapM doesFileExist tixFiles
    when (and tixFilesExist) $ do
        
        
        (hpc, hpcVer, _) <- requireProgramVersion verbosity
            hpcProgram anyVersion (withPrograms lbi)
        let outFile = tixFilePath distPref way libName
            htmlDir' = htmlDir distPref way libName
            excluded = concatMap testModules suites ++ [ main ]
        createDirectoryIfMissing True $ takeDirectory outFile
        union hpc verbosity tixFiles outFile excluded
        markup hpc hpcVer verbosity outFile mixDirs htmlDir' excluded
        notice verbosity $ "Package coverage report written to "
                           ++ htmlDir' </> "hpc_index.html"
  where
    way = guessWay lbi
    mixDirs = map (mixDir distPref way) $ libName : map testName suites