shellcheck.hs 2.9 KB
Newer Older
V
Vidar Holen 已提交
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17
{-
    This file is part of ShellCheck.
    http://www.vidarholen.net/contents/shellcheck

    ShellCheck is free software: you can redistribute it and/or modify
    it under the terms of the GNU Affero General Public License as published by
    the Free Software Foundation, either version 3 of the License, or
    (at your option) any later version.

    ShellCheck is distributed in the hope that it will be useful,
    but WITHOUT ANY WARRANTY; without even the implied warranty of
    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    GNU Affero General Public License for more details.

    You should have received a copy of the GNU Affero General Public License
    along with this program.  If not, see <http://www.gnu.org/licenses/>.
-}
18 19 20
import Control.Monad
import GHC.Exts
import GHC.IO.Device
21
import ShellCheck.Simple
22 23 24 25 26 27 28 29 30 31
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
V
Vidar Holen 已提交
32
colorForLevel "info" = 32 -- green
33
colorForLevel "style" = 32 -- green
34 35 36 37 38 39 40 41 42 43 44 45 46
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
47 48
        hPutStrLn stderr (colorFunc "error" $ "No such file: " ++ actualPath)
        return False
49 50 51

doInput filename contents colorFunc = do
    let fileLines = lines contents
52
    let lineCount = length fileLines
53 54
    let comments = shellCheck contents
    let groups = groupWith scLine comments
55 56 57 58 59 60 61 62 63 64 65 66
    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
67

V
Vidar Holen 已提交
68
cuteIndent comment =
69 70 71
    (replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (code $ scCode comment) ++ ": " ++ (scMessage comment)

code code = "SC" ++ (show code)
72 73 74 75 76 77 78 79 80

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

main = do
    args <- getArgs
    colors <- getColorFunc
    if null args then do
81
        hPutStrLn stderr "shellcheck -- bash/sh script static analysis tool"
82
        hPutStrLn stderr "Usage: shellcheck filenames..."
83
        exitFailure
84 85 86
      else do
        statuses <- mapM (\f -> doFile f colors) args
        if and statuses then exitSuccess else exitFailure
87