Added proper command line parsing

This commit is contained in:
Vidar Holen 2013-11-12 21:22:52 -08:00
parent d8b5d6393a
commit 17515ad706
1 changed files with 102 additions and 50 deletions

View File

@ -19,69 +19,121 @@ import Control.Monad
import GHC.Exts import GHC.Exts
import GHC.IO.Device import GHC.IO.Device
import ShellCheck.Simple import ShellCheck.Simple
import System.Console.GetOpt
import System.Directory import System.Directory
import System.Environment import System.Environment
import System.Exit import System.Exit
import System.IO import System.IO
import qualified Data.Map as Map
clear = ansi 0 data Flag = Flag String String
ansi n = "\x1B[" ++ (show n) ++ "m"
colorForLevel "error" = 31 -- red header = "Usage: shellcheck [OPTIONS...] FILES..."
colorForLevel "warning" = 33 -- yellow options = [
colorForLevel "info" = 32 -- green Option ['f'] ["format"]
colorForLevel "style" = 32 -- green (ReqArg (Flag "format") "FORMAT") "output format"
colorForLevel "message" = 1 -- bold ]
colorForLevel "source" = 0 -- none
colorForLevel _ = 0 -- none
colorComment level comment = (ansi $ colorForLevel level) ++ comment ++ clear printErr = hPutStrLn stderr
doFile path colorFunc = do parseArguments argv =
let actualPath = if path == "-" then "/dev/stdin" else path case getOpt Permute options argv of
exists <- doesFileExist actualPath (opts, files, []) ->
if exists then do if not $ null files
contents <- readFile actualPath then
doInput path contents colorFunc return $ Just (opts, map specials files)
else do else do
hPutStrLn stderr (colorFunc "error" $ "No such file: " ++ actualPath) printErr "No files specified.\n"
return False printErr $ usageInfo header options
return $ Nothing
doInput filename contents colorFunc = do (_, _, errors) -> do
let fileLines = lines contents printErr $ (unlines errors) ++ "\n" ++ usageInfo header options
let lineCount = length fileLines return Nothing
let comments = shellCheck contents where
let groups = groupWith scLine comments specials "-" = "/dev/stdin"
mapM_ (\x -> do specials x = x
let lineNum = scLine (head x)
let line = if lineNum < 1 || lineNum > lineCount
then ""
else fileLines !! (lineNum - 1)
putStrLn ""
putStrLn $ colorFunc "message" ("In " ++ filename ++" line " ++ (show $ lineNum) ++ ":")
putStrLn (colorFunc "source" line)
mapM (\c -> putStrLn (colorFunc (scSeverity c) $ cuteIndent c)) x
putStrLn ""
) groups
return $ null comments
cuteIndent comment = formats = Map.fromList [
(replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (code $ scCode comment) ++ ": " ++ (scMessage comment) ("tty", forTty)
]
code code = "SC" ++ (show code) forTty options files = do
output <- mapM doFile files
return $ and output
where
clear = ansi 0
ansi n = "\x1B[" ++ (show n) ++ "m"
getColorFunc = do colorForLevel "error" = 31 -- red
term <- hIsTerminalDevice stdout colorForLevel "warning" = 33 -- yellow
return $ if term then colorComment else const id colorForLevel "info" = 32 -- green
colorForLevel "style" = 32 -- green
colorForLevel "message" = 1 -- bold
colorForLevel "source" = 0 -- none
colorForLevel _ = 0 -- none
colorComment level comment = (ansi $ colorForLevel level) ++ comment ++ clear
doFile path = do
let actualPath = if path == "-" then "/dev/stdin" else path
exists <- doesFileExist actualPath
if exists then do
contents <- readFile actualPath
doInput path contents
else do
colorFunc <- getColorFunc
printErr (colorFunc "error" $ "No such file: " ++ actualPath)
return False
doInput filename contents = do
let fileLines = lines contents
let lineCount = length fileLines
let comments = shellCheck contents
let groups = groupWith scLine comments
colorFunc <- getColorFunc
mapM_ (\x -> do
let lineNum = scLine (head x)
let line = if lineNum < 1 || lineNum > lineCount
then ""
else fileLines !! (lineNum - 1)
putStrLn ""
putStrLn $ colorFunc "message" ("In " ++ filename ++" line " ++ (show $ lineNum) ++ ":")
putStrLn (colorFunc "source" line)
mapM (\c -> putStrLn (colorFunc (scSeverity c) $ cuteIndent c)) x
putStrLn ""
) groups
return $ null comments
cuteIndent comment =
(replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (code $ scCode comment) ++ ": " ++ (scMessage comment)
code code = "SC" ++ (show code)
getColorFunc = do
term <- hIsTerminalDevice stdout
return $ if term then colorComment else const id
getOption [] _ def = def
getOption ((Flag var val):_) name _ | name == var = val
getOption (_:rest) flag def = getOption rest flag def
main = do main = do
args <- getArgs args <- getArgs
colors <- getColorFunc parsedArgs <- parseArguments args
if null args then do status <- process parsedArgs
hPutStrLn stderr "shellcheck -- bash/sh script static analysis tool" if status then exitSuccess else exitFailure
hPutStrLn stderr "Usage: shellcheck filenames..."
exitFailure process Nothing = return False
else do process (Just (options, files)) =
statuses <- mapM (\f -> doFile f colors) args let format = getOption options "format" "tty" in
if and statuses then exitSuccess else exitFailure case Map.lookup format formats of
Nothing -> do
printErr $ "Unknown format " ++ format
printErr $ "Supported formats:"
mapM_ (printErr . write) $ Map.keys formats
return False
where write s = " " ++ s
Just f -> do
f options files