Skip to content

Commit

Permalink
Use exit status and stderr properly in terminal tool
Browse files Browse the repository at this point in the history
  • Loading branch information
koalaman committed Oct 20, 2013
1 parent b1af7bb commit 206900f
Showing 1 changed file with 17 additions and 18 deletions.
35 changes: 17 additions & 18 deletions shellcheck.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ import System.Environment
import System.Exit
import System.IO


clear = ansi 0
ansi n = "\x1B[" ++ (show n) ++ "m"

Expand All @@ -45,27 +44,26 @@ doFile path colorFunc = do
contents <- readFile actualPath
doInput path contents colorFunc
else do
putStrLn (colorFunc "error" $ "No such file: " ++ actualPath)
hPutStrLn stderr (colorFunc "error" $ "No such file: " ++ actualPath)
return False

doInput filename contents colorFunc = do
let fileLines = lines contents
let lineCount = length fileLines
let comments = shellCheck contents
let groups = groupWith scLine comments
if not $ null comments then do
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
else do
putStrLn ("No comments for " ++ filename)
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) ' ') ++ "^-- " ++ (scMessage comment)
Expand All @@ -81,6 +79,7 @@ main = do
hPutStrLn stderr "shellcheck -- bash/sh script static analysis tool"
hPutStrLn stderr "Usage: shellcheck filenames..."
exitFailure
else
mapM (\f -> doFile f colors) args
else do
statuses <- mapM (\f -> doFile f colors) args
if and statuses then exitSuccess else exitFailure

0 comments on commit 206900f

Please sign in to comment.