Skip to content
Snippets Groups Projects
Commit 38f2d4dc authored by stuebinm's avatar stuebinm
Browse files

print hint for non-zero exit code in non-json mode

parent ee73be28
No related branches found
No related tags found
No related merge requests found
Pipeline #9795 passed
......@@ -6,6 +6,7 @@
module Main where
import Control.Monad (unless)
import Control.Monad.Identity (Identity)
import Data.Aeson (eitherDecode, encode)
import Data.Aeson.Encode.Pretty (encodePretty)
......@@ -13,33 +14,33 @@ import Data.Aeson.KeyMap (coercionToHashMap)
import qualified Data.ByteString.Char8 as C8
import qualified Data.ByteString.Lazy as LB
import Data.Maybe (fromMaybe)
import System.Exit (exitWith, ExitCode (..))
import System.Exit (ExitCode (..), exitWith)
import WithCli
import CheckDir (recursiveCheckDir, resultIsFatal)
import LintConfig (LintConfig (..), patch)
import LintConfig (LintConfig (..), patchConfig)
import System.IO (hPutStrLn, stderr)
import Types (Level (..))
import Util (printPretty)
import WriteRepo (writeAdjustedRepository)
import System.IO (hPutStrLn, stderr)
-- | the options this cli tool can take
data Options = Options
{ repository :: Maybe String
{ repository :: Maybe String
-- ^ path to the repository containing maps to lint
, entrypoint :: Maybe String
, entrypoint :: Maybe String
-- ^ entrypoint in that repository
, json :: Bool
, json :: Bool
-- ^ emit json if --json was given
, lintlevel :: Maybe Level
, lintlevel :: Maybe Level
-- ^ maximum lint level to print
, pretty :: Bool
, pretty :: Bool
-- ^ pretty-print the json to make it human-readable
, out :: Maybe String
, out :: Maybe String
-- ^ path to write the (possibly adjusted) maps to after linting
, configFile :: Maybe FilePath
, configFile :: Maybe FilePath
-- ^ path to a config file. Currently required.
, config :: Maybe (LintConfig Maybe)
, config :: Maybe (LintConfig Maybe)
-- ^ a "patch" for the configuration file
} deriving (Show, Generic, HasArguments)
......@@ -59,10 +60,8 @@ run options = do
Nothing -> error "Need a config file!"
Just path -> LB.readFile path >>= \res ->
case eitherDecode res :: Either String (LintConfig Identity) of
Left err -> error $ "config file invalid: " <> err
Right file -> case config options of
Just p -> pure (patch file p)
Nothing -> pure file
Left err -> error $ "config file invalid: " <> err
Right file -> pure (patchConfig file (config options))
lints <- recursiveCheckDir lintconfig repo entry
......@@ -72,11 +71,20 @@ run options = do
else printPretty (level, lints)
case out options of
Just outpath -> writeAdjustedRepository lintconfig repo outpath lints
>>= exitWith
Nothing -> exitWith $ case resultIsFatal lintconfig lints of
False -> ExitSuccess
True -> ExitFailure 1
True -> ExitFailure 1
Just outpath -> do
c <- writeAdjustedRepository lintconfig repo outpath lints
unless (json options) $
case c of
ExitFailure 1 -> putStrLn "\nMap failed linting!"
ExitFailure 2 -> putStrLn "\nOutpath already exists, not writing anything."
_ -> pure ()
exitWith c
-- | haskell's many string types are FUN …
printLB :: LB.ByteString -> IO ()
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment