module Trace.Hpc.Codecov.Error
(
HpcCodecovError(..)
, withBriefUsageOnError
) where
import Control.Exception (Exception (..), handle)
import System.Environment (getProgName)
import System.Exit (exitFailure)
withBriefUsageOnError :: IO a
-> IO a
withBriefUsageOnError = handle handler
where
handler :: HpcCodecovError -> IO a
handler e =
do putStr ("Error: " ++ displayException e)
name <- getProgName
putStrLn ("Run '" ++ name ++ " --help' for usage.")
exitFailure
data HpcCodecovError
= NoTixFile
| TixNotFound FilePath
| MixNotFound FilePath [FilePath]
| SrcNotFound FilePath [FilePath]
| InvalidArgs [String]
deriving (Show)
instance Exception HpcCodecovError where
displayException = hpcCodecovErrorMessage
hpcCodecovErrorMessage :: HpcCodecovError -> String
hpcCodecovErrorMessage e =
case e of
NoTixFile -> "no .tix file given\n"
TixNotFound tix -> "cannot find tix: " ++ show tix ++ "\n"
MixNotFound mix locs -> searchedLocations "mix" mix locs
SrcNotFound src locs -> searchedLocations "src" src locs
InvalidArgs msgs ->
case msgs of
[x] -> x
_ -> '\n' : concatMap (" - " ++) msgs
searchedLocations :: String -> FilePath -> [FilePath] -> String
searchedLocations what path locs =
"cannot find " ++ what ++ ": " ++ show path ++ locs'
where
locs' =
case locs of
[_] -> searched ""
_ -> searched "s"
searched post =
"\nsearched location" ++ post ++ ":\n" ++
unlines (map (" " ++) locs)