Renamed from codename Shpell to final name ShellCheck.
This commit is contained in:
parent
45b98f408c
commit
e264f64266
10
Makefile
10
Makefile
|
@ -1,16 +1,16 @@
|
||||||
all: shpell .tests
|
all: shellcheck .tests
|
||||||
: Done
|
: Done
|
||||||
|
|
||||||
shpell: regardless
|
shellcheck: regardless
|
||||||
: Conditionally compiling shpell
|
: Conditionally compiling shellcheck
|
||||||
ghc --make shpell
|
ghc --make shellcheck
|
||||||
|
|
||||||
.tests: *.hs */*.hs
|
.tests: *.hs */*.hs
|
||||||
: Running unit tests
|
: Running unit tests
|
||||||
./test/runQuack && touch .tests
|
./test/runQuack && touch .tests
|
||||||
|
|
||||||
clean:
|
clean:
|
||||||
rm -f .tests shpell *.hi *.o Shpell/*.hi Shpell/*.o
|
rm -f .tests shellcheck *.hi *.o ShellCheck/*.hi ShellCheck/*.o
|
||||||
|
|
||||||
regardless:
|
regardless:
|
||||||
|
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
module Shpell.Analytics where
|
module ShellCheck.Analytics where
|
||||||
|
|
||||||
import Shpell.Parser
|
import ShellCheck.Parser
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
|
@ -1,6 +1,6 @@
|
||||||
{-# LANGUAGE NoMonomorphismRestriction #-}
|
{-# LANGUAGE NoMonomorphismRestriction #-}
|
||||||
|
|
||||||
module Shpell.Parser (Token(..), Id(..), Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), doAnalysis, doStackAnalysis, doTransform, sortNotes) where
|
module ShellCheck.Parser (Token(..), Id(..), Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), doAnalysis, doStackAnalysis, doTransform, sortNotes) where
|
||||||
|
|
||||||
import Text.Parsec
|
import Text.Parsec
|
||||||
import Debug.Trace
|
import Debug.Trace
|
|
@ -0,0 +1,33 @@
|
||||||
|
module ShellCheck.Simple (shellcheckCheck, ShellCheckComment, shellcheckLine, shellcheckColumn, shellcheckSeverity, shellcheckComment) where
|
||||||
|
|
||||||
|
import ShellCheck.Parser
|
||||||
|
import ShellCheck.Analytics
|
||||||
|
import Data.Maybe
|
||||||
|
import Text.Parsec.Pos
|
||||||
|
import Data.List
|
||||||
|
|
||||||
|
shellcheckCheck :: String -> [ShellCheckComment]
|
||||||
|
shellcheckCheck script =
|
||||||
|
let (ParseResult result notes) = parseShell "-" script in
|
||||||
|
let allNotes = notes ++ (concat $ maybeToList $ do
|
||||||
|
(tree, map) <- result
|
||||||
|
let newMap = runAllAnalytics tree map
|
||||||
|
return $ notesFromMap newMap
|
||||||
|
)
|
||||||
|
in
|
||||||
|
map formatNote $ nub $ sortNotes allNotes
|
||||||
|
|
||||||
|
data ShellCheckComment = ShellCheckComment { shellcheckLine :: Int, shellcheckColumn :: Int, shellcheckSeverity :: String, shellcheckComment :: String }
|
||||||
|
|
||||||
|
|
||||||
|
instance Show ShellCheckComment where
|
||||||
|
show c = concat ["(", show $ shellcheckLine c, ",", show $ shellcheckColumn c, ") ", shellcheckSeverity c, ": ", shellcheckComment c]
|
||||||
|
|
||||||
|
severityToString s =
|
||||||
|
case s of
|
||||||
|
ErrorC -> "error"
|
||||||
|
WarningC -> "warning"
|
||||||
|
InfoC -> "info"
|
||||||
|
StyleC -> "style"
|
||||||
|
|
||||||
|
formatNote (ParseNote pos severity text) = ShellCheckComment (sourceLine pos) (sourceColumn pos) (severityToString severity) text
|
|
@ -1,33 +0,0 @@
|
||||||
module Shpell.Simple (shpellCheck, ShpellComment, shpellLine, shpellColumn, shpellSeverity, shpellComment) where
|
|
||||||
|
|
||||||
import Shpell.Parser
|
|
||||||
import Shpell.Analytics
|
|
||||||
import Data.Maybe
|
|
||||||
import Text.Parsec.Pos
|
|
||||||
import Data.List
|
|
||||||
|
|
||||||
shpellCheck :: String -> [ShpellComment]
|
|
||||||
shpellCheck script =
|
|
||||||
let (ParseResult result notes) = parseShell "-" script in
|
|
||||||
let allNotes = notes ++ (concat $ maybeToList $ do
|
|
||||||
(tree, map) <- result
|
|
||||||
let newMap = runAllAnalytics tree map
|
|
||||||
return $ notesFromMap newMap
|
|
||||||
)
|
|
||||||
in
|
|
||||||
map formatNote $ nub $ sortNotes allNotes
|
|
||||||
|
|
||||||
data ShpellComment = ShpellComment { shpellLine :: Int, shpellColumn :: Int, shpellSeverity :: String, shpellComment :: String }
|
|
||||||
|
|
||||||
|
|
||||||
instance Show ShpellComment where
|
|
||||||
show c = concat ["(", show $ shpellLine c, ",", show $ shpellColumn c, ") ", shpellSeverity c, ": ", shpellComment c]
|
|
||||||
|
|
||||||
severityToString s =
|
|
||||||
case s of
|
|
||||||
ErrorC -> "error"
|
|
||||||
WarningC -> "warning"
|
|
||||||
InfoC -> "info"
|
|
||||||
StyleC -> "style"
|
|
||||||
|
|
||||||
formatNote (ParseNote pos severity text) = ShpellComment (sourceLine pos) (sourceColumn pos) (severityToString severity) text
|
|
|
@ -1,7 +1,7 @@
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import GHC.Exts
|
import GHC.Exts
|
||||||
import GHC.IO.Device
|
import GHC.IO.Device
|
||||||
import Shpell.Simple
|
import ShellCheck.Simple
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.Environment
|
import System.Environment
|
||||||
import System.Exit
|
import System.Exit
|
||||||
|
@ -33,25 +33,25 @@ doFile path colorFunc = do
|
||||||
doInput filename contents colorFunc = do
|
doInput filename contents colorFunc = do
|
||||||
let fileLines = lines contents
|
let fileLines = lines contents
|
||||||
let lineCount = length fileLines
|
let lineCount = length fileLines
|
||||||
let comments = shpellCheck contents
|
let comments = shellcheckCheck contents
|
||||||
let groups = groupWith shpellLine comments
|
let groups = groupWith shellcheckLine comments
|
||||||
if not $ null comments then do
|
if not $ null comments then do
|
||||||
mapM_ (\x -> do
|
mapM_ (\x -> do
|
||||||
let lineNum = shpellLine (head x)
|
let lineNum = shellcheckLine (head x)
|
||||||
let line = if lineNum < 1 || lineNum > lineCount
|
let line = if lineNum < 1 || lineNum > lineCount
|
||||||
then ""
|
then ""
|
||||||
else fileLines !! (lineNum - 1)
|
else fileLines !! (lineNum - 1)
|
||||||
putStrLn ""
|
putStrLn ""
|
||||||
putStrLn $ colorFunc "message" ("In " ++ filename ++" line " ++ (show $ lineNum) ++ ":")
|
putStrLn $ colorFunc "message" ("In " ++ filename ++" line " ++ (show $ lineNum) ++ ":")
|
||||||
putStrLn (colorFunc "source" line)
|
putStrLn (colorFunc "source" line)
|
||||||
mapM (\c -> putStrLn (colorFunc (shpellSeverity c) $ cuteIndent c)) x
|
mapM (\c -> putStrLn (colorFunc (shellcheckSeverity c) $ cuteIndent c)) x
|
||||||
putStrLn ""
|
putStrLn ""
|
||||||
) groups
|
) groups
|
||||||
else do
|
else do
|
||||||
putStrLn ("No comments for " ++ filename)
|
putStrLn ("No comments for " ++ filename)
|
||||||
|
|
||||||
cuteIndent comment =
|
cuteIndent comment =
|
||||||
(replicate ((shpellColumn comment) - 1) ' ') ++ "^-- " ++ (shpellComment comment)
|
(replicate ((shellcheckColumn comment) - 1) ' ') ++ "^-- " ++ (shellcheckComment comment)
|
||||||
|
|
||||||
getColorFunc = do
|
getColorFunc = do
|
||||||
term <- hIsTerminalDevice stdout
|
term <- hIsTerminalDevice stdout
|
||||||
|
@ -61,8 +61,8 @@ main = do
|
||||||
args <- getArgs
|
args <- getArgs
|
||||||
colors <- getColorFunc
|
colors <- getColorFunc
|
||||||
if null args then do
|
if null args then do
|
||||||
hPutStrLn stderr "shpell -- bash/sh shell script static analysis tool"
|
hPutStrLn stderr "shellcheck -- bash/sh shell script static analysis tool"
|
||||||
hPutStrLn stderr "Usage: shpell filenames..."
|
hPutStrLn stderr "Usage: shellcheck filenames..."
|
||||||
exitFailure
|
exitFailure
|
||||||
else
|
else
|
||||||
mapM (\f -> doFile f colors) args
|
mapM (\f -> doFile f colors) args
|
Loading…
Reference in New Issue