Minor reformatting
This commit is contained in:
parent
2f5a7be421
commit
cde1e2966f
|
@ -1,6 +1,6 @@
|
||||||
module Shpell.Analytics where
|
module Shpell.Analytics where
|
||||||
|
|
||||||
import Shpell.Parser
|
import Shpell.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
|
||||||
|
@ -25,8 +25,8 @@ basicChecks = [
|
||||||
modifyMap = modify
|
modifyMap = modify
|
||||||
addNoteFor id note = modifyMap $ Map.adjust (\(Metadata pos notes) -> Metadata pos (note:notes)) id
|
addNoteFor id note = modifyMap $ Map.adjust (\(Metadata pos notes) -> Metadata pos (note:notes)) id
|
||||||
|
|
||||||
willSplit x =
|
willSplit x =
|
||||||
case x of
|
case x of
|
||||||
T_DollarVariable _ _ -> True
|
T_DollarVariable _ _ -> True
|
||||||
T_DollarBraced _ _ -> True
|
T_DollarBraced _ _ -> True
|
||||||
T_DollarExpansion _ _ -> True
|
T_DollarExpansion _ _ -> True
|
||||||
|
@ -59,28 +59,28 @@ deadSimple _ = []
|
||||||
verify f s = checkBasic f s == Just True
|
verify f s = checkBasic f s == Just True
|
||||||
verifyNot f s = checkBasic f s == Just False
|
verifyNot f s = checkBasic f s == Just False
|
||||||
|
|
||||||
checkBasic f s = case parseShell "-" s of
|
checkBasic f s = case parseShell "-" s of
|
||||||
(ParseResult (Just (t, m)) _) -> Just . not $ (notesFromMap $ runBasicAnalysis f t m) == (notesFromMap m)
|
(ParseResult (Just (t, m)) _) -> Just . not $ (notesFromMap $ runBasicAnalysis f t m) == (notesFromMap m)
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
prop_checkUuoc = verify checkUuoc "cat foo | grep bar"
|
prop_checkUuoc = verify checkUuoc "cat foo | grep bar"
|
||||||
checkUuoc (T_Pipeline _ (T_Redirecting _ _ f@(T_SimpleCommand id _ _):_:_)) =
|
checkUuoc (T_Pipeline _ (T_Redirecting _ _ f@(T_SimpleCommand id _ _):_:_)) =
|
||||||
case deadSimple f of ["cat", _] -> addNoteFor id $ Note InfoC "UUOC: 'cat foo | bar | baz' is better written as 'bar < foo | baz'"
|
case deadSimple f of ["cat", _] -> addNoteFor id $ Note InfoC "UUOC: 'cat foo | bar | baz' is better written as 'bar < foo | baz'"
|
||||||
_ -> return ()
|
_ -> return ()
|
||||||
checkUuoc _ = return ()
|
checkUuoc _ = return ()
|
||||||
|
|
||||||
|
|
||||||
prop_checkForInQuoted = verify checkForInQuoted "for f in \"$(ls)\"; do echo foo; done"
|
prop_checkForInQuoted = verify checkForInQuoted "for f in \"$(ls)\"; do echo foo; done"
|
||||||
checkForInQuoted (T_ForIn _ f [T_NormalWord _ [T_DoubleQuoted id list]] _) =
|
checkForInQuoted (T_ForIn _ f [T_NormalWord _ [T_DoubleQuoted id list]] _) =
|
||||||
when (any willSplit list) $ addNoteFor id $ Note ErrorC $ "Since you double quoted this, it will not word split, and the loop will only run once"
|
when (any willSplit list) $ addNoteFor id $ Note ErrorC $ "Since you double quoted this, it will not word split, and the loop will only run once"
|
||||||
checkForInQuoted _ = return ()
|
checkForInQuoted _ = return ()
|
||||||
|
|
||||||
|
|
||||||
prop_checkForInLs = verify checkForInLs "for f in $(ls *.mp3); do mplayer \"$f\"; done"
|
prop_checkForInLs = verify checkForInLs "for f in $(ls *.mp3); do mplayer \"$f\"; done"
|
||||||
checkForInLs (T_ForIn _ f [T_NormalWord _ [T_DollarExpansion id [x]]] _) =
|
checkForInLs (T_ForIn _ f [T_NormalWord _ [T_DollarExpansion id [x]]] _) =
|
||||||
case deadSimple x of ("ls":n) -> let args = (if n == [] then ["*"] else n) in
|
case deadSimple x of ("ls":n) -> let args = (if n == [] then ["*"] else n) in
|
||||||
addNoteFor id $ Note WarningC $ "Don't use 'for "++f++" in $(ls " ++ (intercalate " " n) ++ ")'. Use 'for "++f++" in "++ (intercalate " " args) ++ "'"
|
addNoteFor id $ Note WarningC $ "Don't use 'for "++f++" in $(ls " ++ (intercalate " " n) ++ ")'. Use 'for "++f++" in "++ (intercalate " " args) ++ "'"
|
||||||
_ -> return ()
|
_ -> return ()
|
||||||
checkForInLs _ = return ()
|
checkForInLs _ = return ()
|
||||||
|
@ -88,10 +88,10 @@ checkForInLs _ = return ()
|
||||||
|
|
||||||
prop_checkMissingForQuotes = verify checkMissingForQuotes "for f in *.mp3; do rm $f; done"
|
prop_checkMissingForQuotes = verify checkMissingForQuotes "for f in *.mp3; do rm $f; done"
|
||||||
prop_checkMissingForQuotes2 = verifyNot checkMissingForQuotes "for f in foo bar; do rm $f; done"
|
prop_checkMissingForQuotes2 = verifyNot checkMissingForQuotes "for f in foo bar; do rm $f; done"
|
||||||
checkMissingForQuotes (T_ForIn _ f words cmds) =
|
checkMissingForQuotes (T_ForIn _ f words cmds) =
|
||||||
if not $ any willSplit words then return () else do
|
if not $ any willSplit words then return () else do
|
||||||
mapM_ (doAnalysis (markUnquoted f)) cmds
|
mapM_ (doAnalysis (markUnquoted f)) cmds
|
||||||
where
|
where
|
||||||
markUnquoted f (T_NormalWord _ l) = mapM_ mu l
|
markUnquoted f (T_NormalWord _ l) = mapM_ mu l
|
||||||
markUnquoted _ _ = return ()
|
markUnquoted _ _ = return ()
|
||||||
mu (T_DollarVariable id s) | s == f = warning id
|
mu (T_DollarVariable id s) | s == f = warning id
|
||||||
|
@ -102,7 +102,7 @@ checkMissingForQuotes _ = return ()
|
||||||
|
|
||||||
|
|
||||||
prop_checkUnquotedExpansions = verify checkUnquotedExpansions "rm $(ls)"
|
prop_checkUnquotedExpansions = verify checkUnquotedExpansions "rm $(ls)"
|
||||||
checkUnquotedExpansions (T_SimpleCommand _ _ cmds) = mapM_ check cmds
|
checkUnquotedExpansions (T_SimpleCommand _ _ cmds) = mapM_ check cmds
|
||||||
where check (T_NormalWord _ [T_DollarExpansion id _]) = addNoteFor id $ Note WarningC "Quote the expansion to prevent word splitting"
|
where check (T_NormalWord _ [T_DollarExpansion id _]) = addNoteFor id $ Note WarningC "Quote the expansion to prevent word splitting"
|
||||||
check _ = return ()
|
check _ = return ()
|
||||||
checkUnquotedExpansions _ = return ()
|
checkUnquotedExpansions _ = return ()
|
||||||
|
@ -110,16 +110,16 @@ checkUnquotedExpansions _ = return ()
|
||||||
prop_checkRedirectToSame = verify checkRedirectToSame "cat foo > foo"
|
prop_checkRedirectToSame = verify checkRedirectToSame "cat foo > foo"
|
||||||
prop_checkRedirectToSame2 = verify checkRedirectToSame "cat lol | sed -e 's/a/b/g' > lol"
|
prop_checkRedirectToSame2 = verify checkRedirectToSame "cat lol | sed -e 's/a/b/g' > lol"
|
||||||
prop_checkRedirectToSame3 = verifyNot checkRedirectToSame "cat lol | sed -e 's/a/b/g' > foo.bar && mv foo.bar lol"
|
prop_checkRedirectToSame3 = verifyNot checkRedirectToSame "cat lol | sed -e 's/a/b/g' > foo.bar && mv foo.bar lol"
|
||||||
checkRedirectToSame s@(T_Pipeline _ list) =
|
checkRedirectToSame s@(T_Pipeline _ list) =
|
||||||
mapM_ (\l -> (mapM_ (\x -> doAnalysis (checkOccurences x) l) (getAllRedirs list))) list
|
mapM_ (\l -> (mapM_ (\x -> doAnalysis (checkOccurences x) l) (getAllRedirs list))) list
|
||||||
where checkOccurences (T_NormalWord exceptId x) (T_NormalWord newId y) =
|
where checkOccurences (T_NormalWord exceptId x) (T_NormalWord newId y) =
|
||||||
when (x == y && exceptId /= newId) (do
|
when (x == y && exceptId /= newId) (do
|
||||||
let note = Note InfoC $ "Make sure not to read and write the same file in the same pipeline"
|
let note = Note InfoC $ "Make sure not to read and write the same file in the same pipeline"
|
||||||
addNoteFor newId $ note
|
addNoteFor newId $ note
|
||||||
addNoteFor exceptId $ note)
|
addNoteFor exceptId $ note)
|
||||||
checkOccurences _ _ = return ()
|
checkOccurences _ _ = return ()
|
||||||
getAllRedirs l = concatMap (\(T_Redirecting _ ls _) -> concatMap getRedirs ls) l
|
getAllRedirs l = concatMap (\(T_Redirecting _ ls _) -> concatMap getRedirs ls) l
|
||||||
getRedirs (T_FdRedirect _ _ (T_IoFile _ op file)) =
|
getRedirs (T_FdRedirect _ _ (T_IoFile _ op file)) =
|
||||||
case op of T_Greater _ -> [file]
|
case op of T_Greater _ -> [file]
|
||||||
T_Less _ -> [file]
|
T_Less _ -> [file]
|
||||||
T_DGREAT _ -> [file]
|
T_DGREAT _ -> [file]
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{-# LANGUAGE NoMonomorphismRestriction #-}
|
{-# LANGUAGE NoMonomorphismRestriction #-}
|
||||||
|
|
||||||
module Shpell.Parser (Token(..), Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), doAnalysis, doTransform, sortNotes) where
|
module Shpell.Parser (Token(..), Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), doAnalysis, doTransform, sortNotes) where
|
||||||
|
|
||||||
import Text.Parsec
|
import Text.Parsec
|
||||||
import Text.Parsec.Pos (initialPos)
|
import Text.Parsec.Pos (initialPos)
|
||||||
|
@ -284,11 +284,11 @@ analyze f i t = do
|
||||||
f t
|
f t
|
||||||
return . i $ t
|
return . i $ t
|
||||||
|
|
||||||
doAnalysis f t = analyze f id t
|
doAnalysis f t = analyze f id t
|
||||||
doTransform i t = runIdentity $ analyze (const $ return ()) i t
|
doTransform i t = runIdentity $ analyze (const $ return ()) i t
|
||||||
|
|
||||||
|
|
||||||
lolHax s = Re.subRegex (Re.mkRegex "(Id [0-9]+)") (show s) "(Id 0)"
|
lolHax s = Re.subRegex (Re.mkRegex "(Id [0-9]+)") (show s) "(Id 0)"
|
||||||
instance Eq Token where
|
instance Eq Token where
|
||||||
(==) a b = (lolHax a) == (lolHax b)
|
(==) a b = (lolHax a) == (lolHax b)
|
||||||
|
|
||||||
|
@ -594,7 +594,7 @@ prop_roflol = isWarning readScript "a &; b"
|
||||||
prop_roflol2 = isOk readScript "a & b"
|
prop_roflol2 = isOk readScript "a & b"
|
||||||
readSeparatorOp = do
|
readSeparatorOp = do
|
||||||
notFollowedBy (g_AND_IF <|> g_DSEMI)
|
notFollowedBy (g_AND_IF <|> g_DSEMI)
|
||||||
f <- (try $ char '&' >> spacing >> char ';' >> parseProblem ErrorC "It's not 'foo &; bar', just 'foo & bar'. " >> return '&')
|
f <- (try $ char '&' >> spacing >> char ';' >> parseProblem ErrorC "It's not 'foo &; bar', just 'foo & bar'. " >> return '&')
|
||||||
<|> char ';' <|> char '&'
|
<|> char ';' <|> char '&'
|
||||||
spacing
|
spacing
|
||||||
return f
|
return f
|
||||||
|
@ -642,7 +642,7 @@ readAndOr = chainr1 readPipeline $ do
|
||||||
op <- g_AND_IF <|> g_OR_IF
|
op <- g_AND_IF <|> g_OR_IF
|
||||||
readLineBreak
|
readLineBreak
|
||||||
return $ case op of T_AND_IF id -> T_AndIf id
|
return $ case op of T_AND_IF id -> T_AndIf id
|
||||||
T_OR_IF id -> T_OrIf id
|
T_OR_IF id -> T_OrIf id
|
||||||
|
|
||||||
readTerm = do
|
readTerm = do
|
||||||
m <- readAndOr
|
m <- readAndOr
|
||||||
|
@ -691,9 +691,9 @@ prop_readIfClause2 = isWarning readIfClause "if false; then; echo oo; fi"
|
||||||
prop_readIfClause3 = isWarning readIfClause "if false; then true; else; echo lol fi"
|
prop_readIfClause3 = isWarning readIfClause "if false; then true; else; echo lol fi"
|
||||||
readIfClause = do
|
readIfClause = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
(condition, action) <- readIfPart
|
(condition, action) <- readIfPart
|
||||||
elifs <- many readElifPart
|
elifs <- many readElifPart
|
||||||
elses <- option [] readElsePart
|
elses <- option [] readElsePart
|
||||||
g_Fi
|
g_Fi
|
||||||
return $ T_IfExpression id ((condition, action):elifs) elses
|
return $ T_IfExpression id ((condition, action):elifs) elses
|
||||||
|
|
||||||
|
@ -959,14 +959,14 @@ readScript = do
|
||||||
rp p filename contents = Ms.runState (runParserT p initialState filename contents) []
|
rp p filename contents = Ms.runState (runParserT p initialState filename contents) []
|
||||||
|
|
||||||
isWarning :: (ParsecT String (Id, Map.Map Id Metadata, [ParseNote]) (Ms.State [ParseNote]) t) -> String -> Bool
|
isWarning :: (ParsecT String (Id, Map.Map Id Metadata, [ParseNote]) (Ms.State [ParseNote]) t) -> String -> Bool
|
||||||
isWarning p s = (fst cs) && (not . null . snd $ cs) where cs = checkString p s
|
isWarning p s = (fst cs) && (not . null . snd $ cs) where cs = checkString p s
|
||||||
|
|
||||||
isOk :: (ParsecT String (Id, Map.Map Id Metadata, [ParseNote]) (Ms.State [ParseNote]) t) -> String -> Bool
|
isOk :: (ParsecT String (Id, Map.Map Id Metadata, [ParseNote]) (Ms.State [ParseNote]) t) -> String -> Bool
|
||||||
isOk p s = (fst cs) && (null . snd $ cs) where cs = checkString p s
|
isOk p s = (fst cs) && (null . snd $ cs) where cs = checkString p s
|
||||||
|
|
||||||
checkString parser string =
|
checkString parser string =
|
||||||
case rp (parser >> eof >> getMap) "-" string of
|
case rp (parser >> eof >> getMap) "-" string of
|
||||||
(Right (m), n) -> (True, (notesFromMap m) ++ n)
|
(Right (m), n) -> (True, (notesFromMap m) ++ n)
|
||||||
(Left _, n) -> (False, n)
|
(Left _, n) -> (False, n)
|
||||||
|
|
||||||
parseWithNotes parser = do
|
parseWithNotes parser = do
|
||||||
|
@ -974,7 +974,7 @@ parseWithNotes parser = do
|
||||||
map <- getMap
|
map <- getMap
|
||||||
parseNotes <- getParseNotes
|
parseNotes <- getParseNotes
|
||||||
return (item, map, nub . sortNotes $ parseNotes)
|
return (item, map, nub . sortNotes $ parseNotes)
|
||||||
|
|
||||||
toParseNotes (Metadata pos list) = map (\(Note level note) -> ParseNote pos level note) list
|
toParseNotes (Metadata pos list) = map (\(Note level note) -> ParseNote pos level note) list
|
||||||
notesFromMap map = Map.fold (\x -> (++) (toParseNotes x)) [] map
|
notesFromMap map = Map.fold (\x -> (++) (toParseNotes x)) [] map
|
||||||
|
|
||||||
|
|
|
@ -5,25 +5,25 @@ import Shpell.Analytics
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Text.Parsec.Pos
|
import Text.Parsec.Pos
|
||||||
|
|
||||||
|
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 $ sortNotes allNotes
|
||||||
|
|
||||||
data ShpellComment = ShpellComment { shpellLine :: Int, shpellColumn :: Int, shpellSeverity :: String, shpellComment :: String }
|
data ShpellComment = ShpellComment { shpellLine :: Int, shpellColumn :: Int, shpellSeverity :: String, shpellComment :: String }
|
||||||
|
|
||||||
|
|
||||||
instance Show ShpellComment where
|
instance Show ShpellComment where
|
||||||
show c = concat ["(", show $ shpellLine c, ",", show $ shpellColumn c, ") ", shpellSeverity c, ": ", shpellComment c]
|
show c = concat ["(", show $ shpellLine c, ",", show $ shpellColumn c, ") ", shpellSeverity c, ": ", shpellComment c]
|
||||||
|
|
||||||
shpellCheck script =
|
severityToString s =
|
||||||
let (ParseResult result notes) = parseShell "-" script in
|
case s of
|
||||||
let allNotes = notes ++ (concat $ maybeToList $ do
|
|
||||||
(tree, map) <- result
|
|
||||||
let newMap = runAllAnalytics tree map
|
|
||||||
return $ notesFromMap newMap
|
|
||||||
)
|
|
||||||
in
|
|
||||||
map formatNote $ sortNotes allNotes
|
|
||||||
|
|
||||||
|
|
||||||
severityToString s =
|
|
||||||
case s of
|
|
||||||
ErrorC -> "error"
|
ErrorC -> "error"
|
||||||
WarningC -> "warning"
|
WarningC -> "warning"
|
||||||
InfoC -> "info"
|
InfoC -> "info"
|
||||||
|
|
|
@ -46,7 +46,7 @@ doInput filename contents colorFunc = do
|
||||||
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 ((shpellColumn comment) - 1) ' ') ++ "^-- " ++ (shpellComment comment)
|
||||||
|
|
||||||
getColorFunc = do
|
getColorFunc = do
|
||||||
|
@ -60,6 +60,6 @@ main = do
|
||||||
hPutStrLn stderr "shpell -- bash/sh shell script static analysis tool"
|
hPutStrLn stderr "shpell -- bash/sh shell script static analysis tool"
|
||||||
hPutStrLn stderr "Usage: shpell filenames..."
|
hPutStrLn stderr "Usage: shpell filenames..."
|
||||||
exitFailure
|
exitFailure
|
||||||
else
|
else
|
||||||
mapM (\f -> doFile f colors) args
|
mapM (\f -> doFile f colors) args
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue