shellcheck.hs 2.1 KB
Newer Older
1 2 3
import Control.Monad
import GHC.Exts
import GHC.IO.Device
4
import ShellCheck.Simple
5 6 7 8 9 10 11 12 13 14 15 16
import System.Directory
import System.Environment
import System.Exit
import System.IO


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

colorForLevel "error" = 31 -- red
colorForLevel "warning" = 33 -- yellow
colorForLevel "info" = 33 -- yellow
17
colorForLevel "style" = 32 -- green
18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34
colorForLevel "message" = 1 -- bold
colorForLevel "source" = 0 -- none
colorForLevel _ = 0 -- none

colorComment level comment = (ansi $ colorForLevel level) ++ comment ++ clear

doFile path colorFunc = do
    let actualPath = if path == "-" then "/dev/stdin" else path
    exists <- doesFileExist actualPath
    if exists then do
        contents <- readFile actualPath
        doInput path contents colorFunc
      else do
        putStrLn (colorFunc "error" $ "No such file: " ++ actualPath)

doInput filename contents colorFunc = do
    let fileLines = lines contents
35
    let lineCount = length fileLines
36 37
    let comments = shellCheck contents
    let groups = groupWith scLine comments
38 39
    if not $ null comments then do
        mapM_ (\x -> do
40
            let lineNum = scLine (head x)
41
            let line = if lineNum < 1 || lineNum > lineCount
42 43
                            then ""
                            else fileLines !! (lineNum - 1)
44
            putStrLn ""
45
            putStrLn $ colorFunc "message" ("In " ++ filename ++" line " ++ (show $ lineNum) ++ ":")
46
            putStrLn (colorFunc "source" line)
47
            mapM (\c -> putStrLn (colorFunc (scSeverity c) $ cuteIndent c)) x
48 49 50 51 52
            putStrLn ""
          ) groups
      else do
        putStrLn ("No comments for " ++ filename)

V
Vidar Holen 已提交
53
cuteIndent comment =
54
    (replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (scMessage comment)
55 56 57 58 59 60 61 62 63

getColorFunc = do
    term <- hIsTerminalDevice stdout
    return $ if term then colorComment else const id

main = do
    args <- getArgs
    colors <- getColorFunc
    if null args then do
64
        hPutStrLn stderr "shellcheck -- bash/sh script static analysis tool"
65
        hPutStrLn stderr "Usage: shellcheck filenames..."
66
        exitFailure
V
Vidar Holen 已提交
67
      else
68 69
        mapM (\f -> doFile f colors) args