-- |
-- Module:     Trace.Hpc.Codecov.Main
-- Copyright:  (c) 2022 8c6794b6
-- License:    BSD3
-- Maintainer: 8c6794b6 <8c6794b6@gmail.com>
--
-- Main function for @hpc-codecov@.
--
module Trace.Hpc.Codecov.Main (defaultMain) where

-- base
import Control.Exception           (Exception (..), handle, throwIO)
import System.Environment          (getArgs, getProgName)
import System.Exit                 (exitFailure)

-- Internal
import Trace.Hpc.Codecov.Exception
import Trace.Hpc.Codecov.Options
import Trace.Hpc.Codecov.Report

-- | The main function for @hpc-codecov@ executable.
defaultMain :: IO ()
defaultMain :: IO ()
defaultMain = forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle forall a. HpcCodecovError -> IO a
handler (IO [String]
getArgs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [String] -> IO ()
go)
  where
    go :: [String] -> IO ()
go [String]
args =
      case [String] -> Either [String] Options
parseOptions [String]
args of
        Right Options
opts | Options -> Bool
optShowHelp Options
opts    -> IO ()
printHelp
                   | Options -> Bool
optShowVersion Options
opts -> IO ()
printVersion
                   | Options -> Bool
optShowNumeric Options
opts -> IO ()
printNumericVersion
                   | Bool
otherwise           -> Options -> IO Report
opt2rpt Options
opts forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Report -> IO ()
genReport
        Left [String]
errs -> forall e a. Exception e => e -> IO a
throwIO ([String] -> HpcCodecovError
InvalidArgs [String]
errs)

    handler :: HpcCodecovError -> IO a
    handler :: forall a. HpcCodecovError -> IO a
handler HpcCodecovError
e =
      do String -> IO ()
putStr (String
"Error: " forall a. [a] -> [a] -> [a]
++ forall e. Exception e => e -> String
displayException HpcCodecovError
e)
         String
name <- IO String
getProgName
         String -> IO ()
putStrLn (String
"Run '" forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
" --help' for usage.")
         forall a. IO a
exitFailure