Added proper command line parsing
This commit is contained in:
parent
d8b5d6393a
commit
17515ad706
102
shellcheck.hs
102
shellcheck.hs
|
@ -19,39 +19,79 @@ 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 =
|
||||||
|
case getOpt Permute options argv of
|
||||||
|
(opts, files, []) ->
|
||||||
|
if not $ null files
|
||||||
|
then
|
||||||
|
return $ Just (opts, map specials files)
|
||||||
|
else do
|
||||||
|
printErr "No files specified.\n"
|
||||||
|
printErr $ usageInfo header options
|
||||||
|
return $ Nothing
|
||||||
|
|
||||||
|
(_, _, errors) -> do
|
||||||
|
printErr $ (unlines errors) ++ "\n" ++ usageInfo header options
|
||||||
|
return Nothing
|
||||||
|
where
|
||||||
|
specials "-" = "/dev/stdin"
|
||||||
|
specials x = x
|
||||||
|
|
||||||
|
formats = Map.fromList [
|
||||||
|
("tty", forTty)
|
||||||
|
]
|
||||||
|
|
||||||
|
forTty options files = do
|
||||||
|
output <- mapM doFile files
|
||||||
|
return $ and output
|
||||||
|
where
|
||||||
|
clear = ansi 0
|
||||||
|
ansi n = "\x1B[" ++ (show n) ++ "m"
|
||||||
|
|
||||||
|
colorForLevel "error" = 31 -- red
|
||||||
|
colorForLevel "warning" = 33 -- yellow
|
||||||
|
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
|
let actualPath = if path == "-" then "/dev/stdin" else path
|
||||||
exists <- doesFileExist actualPath
|
exists <- doesFileExist actualPath
|
||||||
if exists then do
|
if exists then do
|
||||||
contents <- readFile actualPath
|
contents <- readFile actualPath
|
||||||
doInput path contents colorFunc
|
doInput path contents
|
||||||
else do
|
else do
|
||||||
hPutStrLn stderr (colorFunc "error" $ "No such file: " ++ actualPath)
|
colorFunc <- getColorFunc
|
||||||
|
printErr (colorFunc "error" $ "No such file: " ++ actualPath)
|
||||||
return False
|
return False
|
||||||
|
|
||||||
doInput filename contents colorFunc = do
|
doInput filename contents = do
|
||||||
let fileLines = lines contents
|
let fileLines = lines contents
|
||||||
let lineCount = length fileLines
|
let lineCount = length fileLines
|
||||||
let comments = shellCheck contents
|
let comments = shellCheck contents
|
||||||
let groups = groupWith scLine comments
|
let groups = groupWith scLine comments
|
||||||
|
colorFunc <- getColorFunc
|
||||||
mapM_ (\x -> do
|
mapM_ (\x -> do
|
||||||
let lineNum = scLine (head x)
|
let lineNum = scLine (head x)
|
||||||
let line = if lineNum < 1 || lineNum > lineCount
|
let line = if lineNum < 1 || lineNum > lineCount
|
||||||
|
@ -65,23 +105,35 @@ doInput filename contents colorFunc = do
|
||||||
) groups
|
) groups
|
||||||
return $ null comments
|
return $ null comments
|
||||||
|
|
||||||
cuteIndent comment =
|
cuteIndent comment =
|
||||||
(replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (code $ scCode comment) ++ ": " ++ (scMessage comment)
|
(replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (code $ scCode comment) ++ ": " ++ (scMessage comment)
|
||||||
|
|
||||||
code code = "SC" ++ (show code)
|
code code = "SC" ++ (show code)
|
||||||
|
|
||||||
getColorFunc = do
|
getColorFunc = do
|
||||||
term <- hIsTerminalDevice stdout
|
term <- hIsTerminalDevice stdout
|
||||||
return $ if term then colorComment else const id
|
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
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue