{-# OPTIONS_HADDOCK hide #-}
module Trace.Hpc.Codecov.Options
(
Options(..)
, defaultOptions
, emptyOptions
, parseOptions
, opt2rpt
, printHelp
, printVersion
, printNumericVersion
) where
import Control.Exception (throw, throwIO)
import Data.Version (showVersion)
import System.Console.GetOpt (ArgDescr (..), ArgOrder (..),
OptDescr (..), getOpt, usageInfo)
import System.Environment (getProgName)
import System.IO (hIsTerminalDevice, stdout)
import System.Directory (doesFileExist)
import Paths_hpc_codecov (version)
import Trace.Hpc.Codecov.Discover
import Trace.Hpc.Codecov.Exception
import Trace.Hpc.Codecov.Report
data Options = Options
{ Options -> FilePath
optTix :: FilePath
, Options -> [FilePath]
optMixDirs :: [FilePath]
, Options -> [FilePath]
optSrcDirs :: [FilePath]
, Options -> [FilePath]
optExcludes :: [String]
, Options -> Maybe FilePath
optOutFile :: Maybe FilePath
, Options -> FilePath
optFormat :: String
, Options -> Bool
optVerbose :: Bool
, Options -> FilePath
optRootDir :: FilePath
, Options -> Maybe FilePath
optBuildDir :: Maybe FilePath
, Options -> [FilePath]
optSkipDirs :: [String]
, Options -> Bool
optExprOnly :: Bool
, Options -> Bool
optIgnoreDittos :: Bool
, Options -> Bool
optShowVersion :: Bool
, Options -> Bool
optShowNumeric :: Bool
, Options -> Bool
optShowHelp :: Bool
}
emptyOptions :: Options
emptyOptions :: Options
emptyOptions = Options
{ optTix :: FilePath
optTix = HpcCodecovError -> FilePath
forall a e. Exception e => e -> a
throw HpcCodecovError
NoTarget
, optMixDirs :: [FilePath]
optMixDirs = []
, optSrcDirs :: [FilePath]
optSrcDirs = []
, optExcludes :: [FilePath]
optExcludes = []
, optOutFile :: Maybe FilePath
optOutFile = Maybe FilePath
forall a. Maybe a
Nothing
, optFormat :: FilePath
optFormat = FilePath
"codecov"
, optVerbose :: Bool
optVerbose = Bool
False
, optRootDir :: FilePath
optRootDir = FilePath
""
, optBuildDir :: Maybe FilePath
optBuildDir = Maybe FilePath
forall a. Maybe a
Nothing
, optSkipDirs :: [FilePath]
optSkipDirs = []
, optExprOnly :: Bool
optExprOnly = Bool
False
, optIgnoreDittos :: Bool
optIgnoreDittos = Bool
False
, optShowVersion :: Bool
optShowVersion = Bool
False
, optShowNumeric :: Bool
optShowNumeric = Bool
False
, optShowHelp :: Bool
optShowHelp = Bool
False
}
defaultOptions :: Options
defaultOptions :: Options
defaultOptions = Options
emptyOptions
{ optMixDirs = [".hpc"]
, optSrcDirs = [""]
}
options :: [OptDescr (Options -> Options)]
options :: [OptDescr (Options -> Options)]
options =
[ FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
'm'] [FilePath
"mix"]
((FilePath -> Options -> Options)
-> FilePath -> ArgDescr (Options -> Options)
forall a. (FilePath -> a) -> FilePath -> ArgDescr a
ReqArg (\FilePath
d Options
o -> Options
o {optMixDirs = uncommas d ++ optMixDirs o})
FilePath
"DIR")
FilePath
".mix file directory, can repeat\n\
\(default: .hpc)"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
's'] [FilePath
"src"]
((FilePath -> Options -> Options)
-> FilePath -> ArgDescr (Options -> Options)
forall a. (FilePath -> a) -> FilePath -> ArgDescr a
ReqArg (\FilePath
d Options
o -> Options
o {optSrcDirs = uncommas d ++ optSrcDirs o})
FilePath
"DIR")
FilePath
"Source directory, can repeat\n\
\(default: current directory)"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
'x'] [FilePath
"exclude"]
((FilePath -> Options -> Options)
-> FilePath -> ArgDescr (Options -> Options)
forall a. (FilePath -> a) -> FilePath -> ArgDescr a
ReqArg (\FilePath
m Options
o -> Options
o {optExcludes = uncommas m ++ optExcludes o})
FilePath
"MODULE")
FilePath
"Module name to exclude, can repeat"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
'o'] [FilePath
"out"]
((FilePath -> Options -> Options)
-> FilePath -> ArgDescr (Options -> Options)
forall a. (FilePath -> a) -> FilePath -> ArgDescr a
ReqArg (\FilePath
p Options
o -> Options
o {optOutFile = Just p}) FilePath
"FILE")
FilePath
"Output file\n\
\(default: stdout)"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
'r'] [FilePath
"root"]
((FilePath -> Options -> Options)
-> FilePath -> ArgDescr (Options -> Options)
forall a. (FilePath -> a) -> FilePath -> ArgDescr a
ReqArg (\FilePath
d Options
o -> Options
o {optRootDir = d})
FilePath
"DIR")
FilePath
"Project root directory for TOOL\n\
\Usually the directory containing\n\
\'stack.yaml' or 'cabal.project'\n\
\(default: current directory)"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
'b'] [FilePath
"build"]
((FilePath -> Options -> Options)
-> FilePath -> ArgDescr (Options -> Options)
forall a. (FilePath -> a) -> FilePath -> ArgDescr a
ReqArg (\FilePath
d Options
o -> Options
o {optBuildDir = Just d})
FilePath
"DIR")
FilePath
"Build directory made by the TOOL\n\
\(default:\n\
\ - '.stack-work' for stack\n\
\ - 'dist-newstyle' for cabal)"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
'X'] [FilePath
"skip"]
((FilePath -> Options -> Options)
-> FilePath -> ArgDescr (Options -> Options)
forall a. (FilePath -> a) -> FilePath -> ArgDescr a
ReqArg (\FilePath
d Options
o -> Options
o {optSkipDirs = uncommas d ++ optSkipDirs o})
FilePath
"DIR")
FilePath
"Basename of directory to skip while\n\
\searching data for TOOL, can repeat"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
'f'] [FilePath
"format"]
((FilePath -> Options -> Options)
-> FilePath -> ArgDescr (Options -> Options)
forall a. (FilePath -> a) -> FilePath -> ArgDescr a
ReqArg (\FilePath
s Options
o -> Options
o {optFormat = s})
FilePath
"FMT")
FilePath
"Format of generated report\n\
\'codecov', 'lcov', or 'cobertura'\n\
\(default: codecov)"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [] [FilePath
"expr-only"]
((Options -> Options) -> ArgDescr (Options -> Options)
forall a. a -> ArgDescr a
NoArg (\Options
o -> Options
o {optExprOnly = True}))
FilePath
"Count expressions only"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [] [FilePath
"ignore-dittos"]
((Options -> Options) -> ArgDescr (Options -> Options)
forall a. a -> ArgDescr a
NoArg (\Options
o -> Options
o {optIgnoreDittos = True}))
FilePath
"Ignore consecutive entries with the\n\
\same source code positions"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
'v'] [FilePath
"verbose"]
((Options -> Options) -> ArgDescr (Options -> Options)
forall a. a -> ArgDescr a
NoArg (\Options
o -> Options
o {optVerbose = True}))
FilePath
"Show verbose output"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [] [FilePath
"version"]
((Options -> Options) -> ArgDescr (Options -> Options)
forall a. a -> ArgDescr a
NoArg (\Options
o -> Options
o {optShowVersion = True}))
FilePath
"Show versoin and exit"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [] [FilePath
"numeric-version"]
((Options -> Options) -> ArgDescr (Options -> Options)
forall a. a -> ArgDescr a
NoArg (\Options
o -> Options
o {optShowNumeric = True}))
FilePath
"Show numeric version and exit"
, FilePath
-> [FilePath]
-> ArgDescr (Options -> Options)
-> FilePath
-> OptDescr (Options -> Options)
forall a.
FilePath -> [FilePath] -> ArgDescr a -> FilePath -> OptDescr a
Option [Char
'h'] [FilePath
"help"]
((Options -> Options) -> ArgDescr (Options -> Options)
forall a. a -> ArgDescr a
NoArg (\Options
o -> Options
o {optShowHelp = True}))
FilePath
"Show this help and exit"
]
parseOptions :: [String]
-> Either [String] Options
parseOptions :: [FilePath] -> Either [FilePath] Options
parseOptions [FilePath]
args =
case ArgOrder (Options -> Options)
-> [OptDescr (Options -> Options)]
-> [FilePath]
-> ([Options -> Options], [FilePath], [FilePath])
forall a.
ArgOrder a
-> [OptDescr a] -> [FilePath] -> ([a], [FilePath], [FilePath])
getOpt ArgOrder (Options -> Options)
forall a. ArgOrder a
Permute [OptDescr (Options -> Options)]
options [FilePath]
args of
([Options -> Options]
flags, [FilePath]
rest, []) ->
let opts0 :: Options
opts0 = ((Options -> Options) -> Options -> Options)
-> Options -> [Options -> Options] -> Options
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Options -> Options) -> Options -> Options
forall a b. (a -> b) -> a -> b
($) Options
emptyOptions [Options -> Options]
flags
opts1 :: Options
opts1 = Options -> Options
fillDefaultsIfNotGiven Options
opts0
in case [FilePath]
rest of
[] -> Options -> Either [FilePath] Options
forall a b. b -> Either a b
Right Options
opts1
(FilePath
tix:[FilePath]
_) -> Options -> Either [FilePath] Options
forall a b. b -> Either a b
Right (Options
opts1 {optTix = tix})
([Options -> Options]
_, [FilePath]
_, [FilePath]
errs) -> [FilePath] -> Either [FilePath] Options
forall a b. a -> Either a b
Left [FilePath]
errs
fillDefaultsIfNotGiven :: Options -> Options
fillDefaultsIfNotGiven :: Options -> Options
fillDefaultsIfNotGiven Options
opts = Options
opts
{ optMixDirs = fillIf null optMixDirs
, optSrcDirs = fillIf null optSrcDirs
}
where
fillIf :: (t -> Bool) -> (Options -> t) -> t
fillIf t -> Bool
test Options -> t
fld =
let orig :: t
orig = Options -> t
fld Options
opts
in if t -> Bool
test t
orig
then Options -> t
fld Options
defaultOptions
else t
orig
data Target
= TixFile FilePath
| TestSuite BuildTool String
parseTarget :: String -> IO Target
parseTarget :: FilePath -> IO Target
parseTarget FilePath
str = do
Bool
file_found <- FilePath -> IO Bool
doesFileExist FilePath
str
if Bool
file_found
then Target -> IO Target
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Target -> IO Target) -> Target -> IO Target
forall a b. (a -> b) -> a -> b
$ FilePath -> Target
TixFile FilePath
str
else case (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') FilePath
str of
(FilePath
"cabal", Char
':':FilePath
name) -> Target -> IO Target
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Target -> IO Target) -> Target -> IO Target
forall a b. (a -> b) -> a -> b
$ BuildTool -> FilePath -> Target
TestSuite BuildTool
Cabal FilePath
name
(FilePath
"stack", Char
':':FilePath
name) -> Target -> IO Target
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Target -> IO Target) -> Target -> IO Target
forall a b. (a -> b) -> a -> b
$ BuildTool -> FilePath -> Target
TestSuite BuildTool
Stack FilePath
name
(FilePath
tool, Char
':':FilePath
_) -> HpcCodecovError -> IO Target
forall e a. Exception e => e -> IO a
throwIO (HpcCodecovError -> IO Target) -> HpcCodecovError -> IO Target
forall a b. (a -> b) -> a -> b
$ FilePath -> HpcCodecovError
InvalidBuildTool FilePath
tool
(FilePath, FilePath)
_ -> Target -> IO Target
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Target -> IO Target) -> Target -> IO Target
forall a b. (a -> b) -> a -> b
$ FilePath -> Target
TixFile FilePath
str
parseFormat :: String -> IO Format
parseFormat :: FilePath -> IO Format
parseFormat FilePath
fmt = case FilePath
fmt of
FilePath
"codecov" -> Format -> IO Format
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
Codecov
FilePath
"lcov" -> Format -> IO Format
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
Lcov
FilePath
"cobertura" -> Format -> IO Format
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
Cobertura
FilePath
_ -> HpcCodecovError -> IO Format
forall e a. Exception e => e -> IO a
throwIO (HpcCodecovError -> IO Format) -> HpcCodecovError -> IO Format
forall a b. (a -> b) -> a -> b
$ FilePath -> HpcCodecovError
InvalidFormat FilePath
fmt
uncommas :: String -> [String]
uncommas :: FilePath -> [FilePath]
uncommas = FilePath -> [FilePath]
go
where
go :: FilePath -> [FilePath]
go FilePath
str = case (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
',') FilePath
str of
(FilePath
cs, Char
',':FilePath
rest) -> FilePath
cs FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath -> [FilePath]
go FilePath
rest
(FilePath
cs, FilePath
_) -> [FilePath
cs]
opt2rpt :: Options -> IO Report
opt2rpt :: Options -> IO Report
opt2rpt Options
opt = do
let rpt1 :: Report
rpt1 = Report
forall a. Monoid a => a
mempty
{ reportMixDirs = optMixDirs opt
, reportSrcDirs = optSrcDirs opt
, reportExcludes = optExcludes opt
, reportOutFile = optOutFile opt
, reportVerbose = verbose
, reportExprOnly = optExprOnly opt
, reportIgnoreDittos = optIgnoreDittos opt
}
verbose :: Bool
verbose = Options -> Bool
optVerbose Options
opt
Format
format <- FilePath -> IO Format
parseFormat (Options -> FilePath
optFormat Options
opt)
Target
target <- FilePath -> IO Target
parseTarget (Options -> FilePath
optTix Options
opt)
case Target
target of
TixFile FilePath
path -> Report -> IO Report
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Report
rpt1 {reportTix = path
,reportFormat = format})
TestSuite BuildTool
tool FilePath
name -> do
Report
rpt2 <- DiscoverArgs -> IO Report
discover DiscoverArgs
{ da_tool :: BuildTool
da_tool = BuildTool
tool
, da_testsuite :: FilePath
da_testsuite = FilePath
name
, da_rootdir :: FilePath
da_rootdir = Options -> FilePath
optRootDir Options
opt
, da_builddir :: Maybe FilePath
da_builddir = Options -> Maybe FilePath
optBuildDir Options
opt
, da_skipdirs :: [FilePath]
da_skipdirs = Options -> [FilePath]
optSkipDirs Options
opt
, da_verbose :: Bool
da_verbose = Bool
verbose
}
Report -> IO Report
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Report -> IO Report) -> Report -> IO Report
forall a b. (a -> b) -> a -> b
$ Report
rpt1 Report -> Report -> Report
forall a. Monoid a => a -> a -> a
`mappend` Report
rpt2 {reportFormat = format}
printHelp :: IO ()
printHelp :: IO ()
printHelp = do
FilePath
me <- IO FilePath
getProgName
Bool
is_terminal <- Handle -> IO Bool
hIsTerminalDevice Handle
stdout
FilePath -> IO ()
putStrLn (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> FilePath -> FilePath
helpMessage Bool
is_terminal FilePath
me
printVersion :: IO ()
printVersion :: IO ()
printVersion = do
FilePath
me <- IO FilePath
getProgName
FilePath -> IO ()
putStrLn (FilePath
me FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" version " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
versionString)
printNumericVersion :: IO ()
printNumericVersion :: IO ()
printNumericVersion = FilePath -> IO ()
putStrLn FilePath
versionString
boldUnderline :: Bool -> String -> String
boldUnderline :: Bool -> FilePath -> FilePath
boldUnderline Bool
is_terminal FilePath
str
| Bool
is_terminal = FilePath
"\ESC[1m\ESC[4m" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
str FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\ESC[0m"
| Bool
otherwise = FilePath
str
bold :: Bool -> String -> String
bold :: Bool -> FilePath -> FilePath
bold Bool
is_terminal FilePath
str
| Bool
is_terminal = FilePath
"\ESC[1m" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
str FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\ESC[0m"
| Bool
otherwise = FilePath
str
helpMessage :: Bool
-> String
-> String
helpMessage :: Bool -> FilePath -> FilePath
helpMessage Bool
is_terminal FilePath
name = FilePath -> [OptDescr (Options -> Options)] -> FilePath
forall a. FilePath -> [OptDescr a] -> FilePath
usageInfo FilePath
header [OptDescr (Options -> Options)]
options FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
footer
where
b :: FilePath -> FilePath
b = Bool -> FilePath -> FilePath
bold Bool
is_terminal
bu :: FilePath -> FilePath
bu = Bool -> FilePath -> FilePath
boldUnderline Bool
is_terminal
header :: FilePath
header = FilePath
"A tool to generate reports from .tix and .mix files\n\
\\n\
\" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
bu FilePath
"USAGE:" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
b FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" [OPTIONS] TARGET\n\
\\n\
\" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
bu FilePath
"ARGUMENTS:" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n\
\ <TARGET> Either a path to a .tix file or a 'TOOL:TEST_SUITE'.\n\
\ Supported TOOL values are 'stack' and 'cabal'.\n\
\ When the TOOL is 'stack' and building a project with\n\
\ multiple packages, use 'all' as the TEST_SUITE value\n\
\ to specify the combined report.\n\
\\n\
\" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
bu FilePath
"OPTIONS:"
footer :: FilePath
footer = FilePath
"\
\\n\
\For more info, see:\n\
\\n\
\ https://github.com/8c6794b6/hpc-codecov#readme\n\
\"
versionString :: String
versionString :: FilePath
versionString = Version -> FilePath
showVersion Version
version