mirror of
https://github.com/koalaman/shellcheck
synced 2025-07-08 05:51:09 -07:00
Move library into src/
This commit is contained in:
parent
b33607b048
commit
cd7c077ecc
18 changed files with 3 additions and 0 deletions
386
src/ShellCheck/AST.hs
Normal file
386
src/ShellCheck/AST.hs
Normal file
|
@ -0,0 +1,386 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
module ShellCheck.AST where
|
||||
|
||||
import Control.Monad.Identity
|
||||
import Text.Parsec
|
||||
import qualified ShellCheck.Regex as Re
|
||||
import Prelude hiding (id)
|
||||
|
||||
newtype Id = Id Int deriving (Show, Eq, Ord)
|
||||
|
||||
data Quoted = Quoted | Unquoted deriving (Show, Eq)
|
||||
data Dashed = Dashed | Undashed deriving (Show, Eq)
|
||||
data AssignmentMode = Assign | Append deriving (Show, Eq)
|
||||
newtype FunctionKeyword = FunctionKeyword Bool deriving (Show, Eq)
|
||||
newtype FunctionParentheses = FunctionParentheses Bool deriving (Show, Eq)
|
||||
data CaseType = CaseBreak | CaseFallThrough | CaseContinue deriving (Show, Eq)
|
||||
|
||||
newtype Root = Root Token
|
||||
data Token =
|
||||
TA_Binary Id String Token Token
|
||||
| TA_Assignment Id String Token Token
|
||||
| TA_Variable Id String [Token]
|
||||
| TA_Expansion Id [Token]
|
||||
| TA_Sequence Id [Token]
|
||||
| TA_Trinary Id Token Token Token
|
||||
| TA_Unary Id String Token
|
||||
| TC_And Id ConditionType String Token Token
|
||||
| TC_Binary Id ConditionType String Token Token
|
||||
| TC_Group Id ConditionType Token
|
||||
| TC_Nullary Id ConditionType Token
|
||||
| TC_Or Id ConditionType String Token Token
|
||||
| TC_Unary Id ConditionType String Token
|
||||
| TC_Empty Id ConditionType
|
||||
| T_AND_IF Id
|
||||
| T_AndIf Id Token Token
|
||||
| T_Arithmetic Id Token
|
||||
| T_Array Id [Token]
|
||||
| T_IndexedElement Id [Token] Token
|
||||
-- Store the index as string, and parse as arithmetic or string later
|
||||
| T_UnparsedIndex Id SourcePos String
|
||||
| T_Assignment Id AssignmentMode String [Token] Token
|
||||
| T_Backgrounded Id Token
|
||||
| T_Backticked Id [Token]
|
||||
| T_Bang Id
|
||||
| T_Banged Id Token
|
||||
| T_BraceExpansion Id [Token]
|
||||
| T_BraceGroup Id [Token]
|
||||
| T_CLOBBER Id
|
||||
| T_Case Id
|
||||
| T_CaseExpression Id Token [(CaseType, [Token], [Token])]
|
||||
| T_Condition Id ConditionType Token
|
||||
| T_DGREAT Id
|
||||
| T_DLESS Id
|
||||
| T_DLESSDASH Id
|
||||
| T_DSEMI Id
|
||||
| T_Do Id
|
||||
| T_DollarArithmetic Id Token
|
||||
| T_DollarBraced Id Token
|
||||
| T_DollarBracket Id Token
|
||||
| T_DollarDoubleQuoted Id [Token]
|
||||
| T_DollarExpansion Id [Token]
|
||||
| T_DollarSingleQuoted Id String
|
||||
| T_DollarBraceCommandExpansion Id [Token]
|
||||
| T_Done Id
|
||||
| T_DoubleQuoted Id [Token]
|
||||
| T_EOF Id
|
||||
| T_Elif Id
|
||||
| T_Else Id
|
||||
| T_Esac Id
|
||||
| T_Extglob Id String [Token]
|
||||
| T_FdRedirect Id String Token
|
||||
| T_Fi Id
|
||||
| T_For Id
|
||||
| T_ForArithmetic Id Token Token Token [Token]
|
||||
| T_ForIn Id String [Token] [Token]
|
||||
| T_Function Id FunctionKeyword FunctionParentheses String Token
|
||||
| T_GREATAND Id
|
||||
| T_Glob Id String
|
||||
| T_Greater Id
|
||||
| T_HereDoc Id Dashed Quoted String [Token]
|
||||
| T_HereString Id Token
|
||||
| T_If Id
|
||||
| T_IfExpression Id [([Token],[Token])] [Token]
|
||||
| T_In Id
|
||||
| T_IoFile Id Token Token
|
||||
| T_IoDuplicate Id Token String
|
||||
| T_LESSAND Id
|
||||
| T_LESSGREAT Id
|
||||
| T_Lbrace Id
|
||||
| T_Less Id
|
||||
| T_Literal Id String
|
||||
| T_Lparen Id
|
||||
| T_NEWLINE Id
|
||||
| T_NormalWord Id [Token]
|
||||
| T_OR_IF Id
|
||||
| T_OrIf Id Token Token
|
||||
| T_ParamSubSpecialChar Id String -- e.g. '%' in ${foo%bar} or '/' in ${foo/bar/baz}
|
||||
| T_Pipeline Id [Token] [Token] -- [Pipe separators] [Commands]
|
||||
| T_ProcSub Id String [Token]
|
||||
| T_Rbrace Id
|
||||
| T_Redirecting Id [Token] Token
|
||||
| T_Rparen Id
|
||||
| T_Script Id String [Token]
|
||||
| T_Select Id
|
||||
| T_SelectIn Id String [Token] [Token]
|
||||
| T_Semi Id
|
||||
| T_SimpleCommand Id [Token] [Token]
|
||||
| T_SingleQuoted Id String
|
||||
| T_Subshell Id [Token]
|
||||
| T_Then Id
|
||||
| T_Until Id
|
||||
| T_UntilExpression Id [Token] [Token]
|
||||
| T_While Id
|
||||
| T_WhileExpression Id [Token] [Token]
|
||||
| T_Annotation Id [Annotation] Token
|
||||
| T_Pipe Id String
|
||||
| T_CoProc Id (Maybe String) Token
|
||||
| T_CoProcBody Id Token
|
||||
| T_Include Id Token Token -- . & source: SimpleCommand T_Script
|
||||
deriving (Show)
|
||||
|
||||
data Annotation =
|
||||
DisableComment Integer
|
||||
| SourceOverride String
|
||||
| ShellOverride String
|
||||
deriving (Show, Eq)
|
||||
data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq)
|
||||
|
||||
-- This is an abomination.
|
||||
tokenEquals :: Token -> Token -> Bool
|
||||
tokenEquals a b = kludge a == kludge b
|
||||
where kludge s = Re.subRegex (Re.mkRegex "\\(Id [0-9]+\\)") (show s) "(Id 0)"
|
||||
|
||||
instance Eq Token where
|
||||
(==) = tokenEquals
|
||||
|
||||
analyze :: Monad m => (Token -> m ()) -> (Token -> m ()) -> (Token -> m Token) -> Token -> m Token
|
||||
analyze f g i =
|
||||
round
|
||||
where
|
||||
round t = do
|
||||
f t
|
||||
newT <- delve t
|
||||
g t
|
||||
i newT
|
||||
roundAll = mapM round
|
||||
|
||||
dl l v = do
|
||||
x <- roundAll l
|
||||
return $ v x
|
||||
dll l m v = do
|
||||
x <- roundAll l
|
||||
y <- roundAll m
|
||||
return $ v x y
|
||||
d1 t v = do
|
||||
x <- round t
|
||||
return $ v x
|
||||
d2 t1 t2 v = do
|
||||
x <- round t1
|
||||
y <- round t2
|
||||
return $ v x y
|
||||
|
||||
delve (T_NormalWord id list) = dl list $ T_NormalWord id
|
||||
delve (T_DoubleQuoted id list) = dl list $ T_DoubleQuoted id
|
||||
delve (T_DollarDoubleQuoted id list) = dl list $ T_DollarDoubleQuoted id
|
||||
delve (T_DollarExpansion id list) = dl list $ T_DollarExpansion id
|
||||
delve (T_DollarBraceCommandExpansion id list) = dl list $ T_DollarBraceCommandExpansion id
|
||||
delve (T_BraceExpansion id list) = dl list $ T_BraceExpansion id
|
||||
delve (T_Backticked id list) = dl list $ T_Backticked id
|
||||
delve (T_DollarArithmetic id c) = d1 c $ T_DollarArithmetic id
|
||||
delve (T_DollarBracket id c) = d1 c $ T_DollarBracket id
|
||||
delve (T_IoFile id op file) = d2 op file $ T_IoFile id
|
||||
delve (T_IoDuplicate id op num) = d1 op $ \x -> T_IoDuplicate id x num
|
||||
delve (T_HereString id word) = d1 word $ T_HereString id
|
||||
delve (T_FdRedirect id v t) = d1 t $ T_FdRedirect id v
|
||||
delve (T_Assignment id mode var indices value) = do
|
||||
a <- roundAll indices
|
||||
b <- round value
|
||||
return $ T_Assignment id mode var a b
|
||||
delve (T_Array id t) = dl t $ T_Array id
|
||||
delve (T_IndexedElement id indices t) = do
|
||||
a <- roundAll indices
|
||||
b <- round t
|
||||
return $ T_IndexedElement id a b
|
||||
delve (T_Redirecting id redirs cmd) = do
|
||||
a <- roundAll redirs
|
||||
b <- round cmd
|
||||
return $ T_Redirecting id a b
|
||||
delve (T_SimpleCommand id vars cmds) = dll vars cmds $ T_SimpleCommand id
|
||||
delve (T_Pipeline id l1 l2) = dll l1 l2 $ T_Pipeline id
|
||||
delve (T_Banged id l) = d1 l $ T_Banged id
|
||||
delve (T_AndIf id t u) = d2 t u $ T_AndIf id
|
||||
delve (T_OrIf id t u) = d2 t u $ T_OrIf id
|
||||
delve (T_Backgrounded id l) = d1 l $ T_Backgrounded id
|
||||
delve (T_Subshell id l) = dl l $ T_Subshell id
|
||||
delve (T_ProcSub id typ l) = dl l $ T_ProcSub id typ
|
||||
delve (T_Arithmetic id c) = d1 c $ T_Arithmetic id
|
||||
delve (T_IfExpression id conditions elses) = do
|
||||
newConds <- mapM (\(c, t) -> do
|
||||
x <- mapM round c
|
||||
y <- mapM round t
|
||||
return (x,y)
|
||||
) conditions
|
||||
newElses <- roundAll elses
|
||||
return $ T_IfExpression id newConds newElses
|
||||
delve (T_BraceGroup id l) = dl l $ T_BraceGroup id
|
||||
delve (T_WhileExpression id c l) = dll c l $ T_WhileExpression id
|
||||
delve (T_UntilExpression id c l) = dll c l $ T_UntilExpression id
|
||||
delve (T_ForIn id v w l) = dll w l $ T_ForIn id v
|
||||
delve (T_SelectIn id v w l) = dll w l $ T_SelectIn id v
|
||||
delve (T_CaseExpression id word cases) = do
|
||||
newWord <- round word
|
||||
newCases <- mapM (\(o, c, t) -> do
|
||||
x <- mapM round c
|
||||
y <- mapM round t
|
||||
return (o, x,y)
|
||||
) cases
|
||||
return $ T_CaseExpression id newWord newCases
|
||||
|
||||
delve (T_ForArithmetic id a b c group) = do
|
||||
x <- round a
|
||||
y <- round b
|
||||
z <- round c
|
||||
list <- mapM round group
|
||||
return $ T_ForArithmetic id x y z list
|
||||
|
||||
delve (T_Script id s l) = dl l $ T_Script id s
|
||||
delve (T_Function id a b name body) = d1 body $ T_Function id a b name
|
||||
delve (T_Condition id typ token) = d1 token $ T_Condition id typ
|
||||
delve (T_Extglob id str l) = dl l $ T_Extglob id str
|
||||
delve (T_DollarBraced id op) = d1 op $ T_DollarBraced id
|
||||
delve (T_HereDoc id d q str l) = dl l $ T_HereDoc id d q str
|
||||
|
||||
delve (TC_And id typ str t1 t2) = d2 t1 t2 $ TC_And id typ str
|
||||
delve (TC_Or id typ str t1 t2) = d2 t1 t2 $ TC_Or id typ str
|
||||
delve (TC_Group id typ token) = d1 token $ TC_Group id typ
|
||||
delve (TC_Binary id typ op lhs rhs) = d2 lhs rhs $ TC_Binary id typ op
|
||||
delve (TC_Unary id typ op token) = d1 token $ TC_Unary id typ op
|
||||
delve (TC_Nullary id typ token) = d1 token $ TC_Nullary id typ
|
||||
|
||||
delve (TA_Binary id op t1 t2) = d2 t1 t2 $ TA_Binary id op
|
||||
delve (TA_Assignment id op t1 t2) = d2 t1 t2 $ TA_Assignment id op
|
||||
delve (TA_Unary id op t1) = d1 t1 $ TA_Unary id op
|
||||
delve (TA_Sequence id l) = dl l $ TA_Sequence id
|
||||
delve (TA_Trinary id t1 t2 t3) = do
|
||||
a <- round t1
|
||||
b <- round t2
|
||||
c <- round t3
|
||||
return $ TA_Trinary id a b c
|
||||
delve (TA_Expansion id t) = dl t $ TA_Expansion id
|
||||
delve (TA_Variable id str t) = dl t $ TA_Variable id str
|
||||
delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns
|
||||
delve (T_CoProc id var body) = d1 body $ T_CoProc id var
|
||||
delve (T_CoProcBody id t) = d1 t $ T_CoProcBody id
|
||||
delve (T_Include id includer script) = d2 includer script $ T_Include id
|
||||
delve t = return t
|
||||
|
||||
getId :: Token -> Id
|
||||
getId t = case t of
|
||||
T_AND_IF id -> id
|
||||
T_OR_IF id -> id
|
||||
T_DSEMI id -> id
|
||||
T_Semi id -> id
|
||||
T_DLESS id -> id
|
||||
T_DGREAT id -> id
|
||||
T_LESSAND id -> id
|
||||
T_GREATAND id -> id
|
||||
T_LESSGREAT id -> id
|
||||
T_DLESSDASH id -> id
|
||||
T_CLOBBER id -> id
|
||||
T_If id -> id
|
||||
T_Then id -> id
|
||||
T_Else id -> id
|
||||
T_Elif id -> id
|
||||
T_Fi id -> id
|
||||
T_Do id -> id
|
||||
T_Done id -> id
|
||||
T_Case id -> id
|
||||
T_Esac id -> id
|
||||
T_While id -> id
|
||||
T_Until id -> id
|
||||
T_For id -> id
|
||||
T_Select id -> id
|
||||
T_Lbrace id -> id
|
||||
T_Rbrace id -> id
|
||||
T_Lparen id -> id
|
||||
T_Rparen id -> id
|
||||
T_Bang id -> id
|
||||
T_In id -> id
|
||||
T_NEWLINE id -> id
|
||||
T_EOF id -> id
|
||||
T_Less id -> id
|
||||
T_Greater id -> id
|
||||
T_SingleQuoted id _ -> id
|
||||
T_Literal id _ -> id
|
||||
T_NormalWord id _ -> id
|
||||
T_DoubleQuoted id _ -> id
|
||||
T_DollarExpansion id _ -> id
|
||||
T_DollarBraced id _ -> id
|
||||
T_DollarArithmetic id _ -> id
|
||||
T_BraceExpansion id _ -> id
|
||||
T_ParamSubSpecialChar id _ -> id
|
||||
T_DollarBraceCommandExpansion id _ -> id
|
||||
T_IoFile id _ _ -> id
|
||||
T_IoDuplicate id _ _ -> id
|
||||
T_HereDoc id _ _ _ _ -> id
|
||||
T_HereString id _ -> id
|
||||
T_FdRedirect id _ _ -> id
|
||||
T_Assignment id _ _ _ _ -> id
|
||||
T_Array id _ -> id
|
||||
T_IndexedElement id _ _ -> id
|
||||
T_Redirecting id _ _ -> id
|
||||
T_SimpleCommand id _ _ -> id
|
||||
T_Pipeline id _ _ -> id
|
||||
T_Banged id _ -> id
|
||||
T_AndIf id _ _ -> id
|
||||
T_OrIf id _ _ -> id
|
||||
T_Backgrounded id _ -> id
|
||||
T_IfExpression id _ _ -> id
|
||||
T_Subshell id _ -> id
|
||||
T_BraceGroup id _ -> id
|
||||
T_WhileExpression id _ _ -> id
|
||||
T_UntilExpression id _ _ -> id
|
||||
T_ForIn id _ _ _ -> id
|
||||
T_SelectIn id _ _ _ -> id
|
||||
T_CaseExpression id _ _ -> id
|
||||
T_Function id _ _ _ _ -> id
|
||||
T_Arithmetic id _ -> id
|
||||
T_Script id _ _ -> id
|
||||
T_Condition id _ _ -> id
|
||||
T_Extglob id _ _ -> id
|
||||
T_Backticked id _ -> id
|
||||
TC_And id _ _ _ _ -> id
|
||||
TC_Or id _ _ _ _ -> id
|
||||
TC_Group id _ _ -> id
|
||||
TC_Binary id _ _ _ _ -> id
|
||||
TC_Unary id _ _ _ -> id
|
||||
TC_Nullary id _ _ -> id
|
||||
TA_Binary id _ _ _ -> id
|
||||
TA_Assignment id _ _ _ -> id
|
||||
TA_Unary id _ _ -> id
|
||||
TA_Sequence id _ -> id
|
||||
TA_Trinary id _ _ _ -> id
|
||||
TA_Expansion id _ -> id
|
||||
T_ProcSub id _ _ -> id
|
||||
T_Glob id _ -> id
|
||||
T_ForArithmetic id _ _ _ _ -> id
|
||||
T_DollarSingleQuoted id _ -> id
|
||||
T_DollarDoubleQuoted id _ -> id
|
||||
T_DollarBracket id _ -> id
|
||||
T_Annotation id _ _ -> id
|
||||
T_Pipe id _ -> id
|
||||
T_CoProc id _ _ -> id
|
||||
T_CoProcBody id _ -> id
|
||||
T_Include id _ _ -> id
|
||||
T_UnparsedIndex id _ _ -> id
|
||||
TC_Empty id _ -> id
|
||||
TA_Variable id _ _ -> id
|
||||
|
||||
blank :: Monad m => Token -> m ()
|
||||
blank = const $ return ()
|
||||
doAnalysis :: Monad m => (Token -> m ()) -> Token -> m Token
|
||||
doAnalysis f = analyze f blank return
|
||||
doStackAnalysis :: Monad m => (Token -> m ()) -> (Token -> m ()) -> Token -> m Token
|
||||
doStackAnalysis startToken endToken = analyze startToken endToken return
|
||||
doTransform :: (Token -> Token) -> Token -> Token
|
||||
doTransform i = runIdentity . analyze blank blank (return . i)
|
||||
|
437
src/ShellCheck/ASTLib.hs
Normal file
437
src/ShellCheck/ASTLib.hs
Normal file
|
@ -0,0 +1,437 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
module ShellCheck.ASTLib where
|
||||
|
||||
import ShellCheck.AST
|
||||
|
||||
import Control.Monad.Writer
|
||||
import Control.Monad
|
||||
import Data.Functor
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
|
||||
-- Is this a type of loop?
|
||||
isLoop t = case t of
|
||||
T_WhileExpression {} -> True
|
||||
T_UntilExpression {} -> True
|
||||
T_ForIn {} -> True
|
||||
T_ForArithmetic {} -> True
|
||||
T_SelectIn {} -> True
|
||||
_ -> False
|
||||
|
||||
-- Will this split into multiple words when used as an argument?
|
||||
willSplit x =
|
||||
case x of
|
||||
T_DollarBraced {} -> True
|
||||
T_DollarExpansion {} -> True
|
||||
T_Backticked {} -> True
|
||||
T_BraceExpansion {} -> True
|
||||
T_Glob {} -> True
|
||||
T_Extglob {} -> True
|
||||
T_NormalWord _ l -> any willSplit l
|
||||
_ -> False
|
||||
|
||||
isGlob T_Extglob {} = True
|
||||
isGlob T_Glob {} = True
|
||||
isGlob (T_NormalWord _ l) = any isGlob l
|
||||
isGlob _ = False
|
||||
|
||||
-- Is this shell word a constant?
|
||||
isConstant token =
|
||||
case token of
|
||||
-- This ignores some cases like ~"foo":
|
||||
T_NormalWord _ (T_Literal _ ('~':_) : _) -> False
|
||||
T_NormalWord _ l -> all isConstant l
|
||||
T_DoubleQuoted _ l -> all isConstant l
|
||||
T_SingleQuoted _ _ -> True
|
||||
T_Literal _ _ -> True
|
||||
_ -> False
|
||||
|
||||
-- Is this an empty literal?
|
||||
isEmpty token =
|
||||
case token of
|
||||
T_NormalWord _ l -> all isEmpty l
|
||||
T_DoubleQuoted _ l -> all isEmpty l
|
||||
T_SingleQuoted _ "" -> True
|
||||
T_Literal _ "" -> True
|
||||
_ -> False
|
||||
|
||||
-- Quick&lazy oversimplification of commands, throwing away details
|
||||
-- and returning a list like ["find", ".", "-name", "${VAR}*" ].
|
||||
oversimplify token =
|
||||
case token of
|
||||
(T_NormalWord _ l) -> [concat (concatMap oversimplify l)]
|
||||
(T_DoubleQuoted _ l) -> [concat (concatMap oversimplify l)]
|
||||
(T_SingleQuoted _ s) -> [s]
|
||||
(T_DollarBraced _ _) -> ["${VAR}"]
|
||||
(T_DollarArithmetic _ _) -> ["${VAR}"]
|
||||
(T_DollarExpansion _ _) -> ["${VAR}"]
|
||||
(T_Backticked _ _) -> ["${VAR}"]
|
||||
(T_Glob _ s) -> [s]
|
||||
(T_Pipeline _ _ [x]) -> oversimplify x
|
||||
(T_Literal _ x) -> [x]
|
||||
(T_ParamSubSpecialChar _ x) -> [x]
|
||||
(T_SimpleCommand _ vars words) -> concatMap oversimplify words
|
||||
(T_Redirecting _ _ foo) -> oversimplify foo
|
||||
(T_DollarSingleQuoted _ s) -> [s]
|
||||
(T_Annotation _ _ s) -> oversimplify s
|
||||
-- Workaround for let "foo = bar" parsing
|
||||
(TA_Sequence _ [TA_Expansion _ v]) -> concatMap oversimplify v
|
||||
_ -> []
|
||||
|
||||
|
||||
-- Turn a SimpleCommand foo -avz --bar=baz into args "a", "v", "z", "bar",
|
||||
-- each in a tuple of (token, stringFlag). Non-flag arguments are added with
|
||||
-- stringFlag == "".
|
||||
getFlagsUntil stopCondition (T_SimpleCommand _ _ (_:args)) =
|
||||
let tokenAndText = map (\x -> (x, concat $ oversimplify x)) args
|
||||
(flagArgs, rest) = break (stopCondition . snd) tokenAndText
|
||||
in
|
||||
concatMap flag flagArgs ++ map (\(t, _) -> (t, "")) rest
|
||||
where
|
||||
flag (x, '-':'-':arg) = [ (x, takeWhile (/= '=') arg) ]
|
||||
flag (x, '-':args) = map (\v -> (x, [v])) args
|
||||
flag (x, _) = [ (x, "") ]
|
||||
getFlagsUntil _ _ = error "Internal shellcheck error, please report! (getFlags on non-command)"
|
||||
|
||||
-- Get all flags in a GNU way, up until --
|
||||
getAllFlags :: Token -> [(Token, String)]
|
||||
getAllFlags = getFlagsUntil (== "--")
|
||||
-- Get all flags in a BSD way, up until first non-flag argument or --
|
||||
getLeadingFlags = getFlagsUntil (\x -> x == "--" || (not $ "-" `isPrefixOf` x))
|
||||
|
||||
-- Check if a command has a flag.
|
||||
hasFlag cmd str = str `elem` (map snd $ getAllFlags cmd)
|
||||
|
||||
-- Is this token a word that starts with a dash?
|
||||
isFlag token =
|
||||
case getWordParts token of
|
||||
T_Literal _ ('-':_) : _ -> True
|
||||
_ -> False
|
||||
|
||||
-- Is this token a flag where the - is unquoted?
|
||||
isUnquotedFlag token = fromMaybe False $ do
|
||||
str <- getLeadingUnquotedString token
|
||||
return $ "-" `isPrefixOf` str
|
||||
|
||||
-- Given a T_DollarBraced, return a simplified version of the string contents.
|
||||
bracedString (T_DollarBraced _ l) = concat $ oversimplify l
|
||||
bracedString _ = error "Internal shellcheck error, please report! (bracedString on non-variable)"
|
||||
|
||||
-- Is this an expansion of multiple items of an array?
|
||||
isArrayExpansion t@(T_DollarBraced _ _) =
|
||||
let string = bracedString t in
|
||||
"@" `isPrefixOf` string ||
|
||||
not ("#" `isPrefixOf` string) && "[@]" `isInfixOf` string
|
||||
isArrayExpansion _ = False
|
||||
|
||||
-- Is it possible that this arg becomes multiple args?
|
||||
mayBecomeMultipleArgs t = willBecomeMultipleArgs t || f t
|
||||
where
|
||||
f t@(T_DollarBraced _ _) =
|
||||
let string = bracedString t in
|
||||
"!" `isPrefixOf` string
|
||||
f (T_DoubleQuoted _ parts) = any f parts
|
||||
f (T_NormalWord _ parts) = any f parts
|
||||
f _ = False
|
||||
|
||||
-- Is it certain that this word will becomes multiple words?
|
||||
willBecomeMultipleArgs t = willConcatInAssignment t || f t
|
||||
where
|
||||
f T_Extglob {} = True
|
||||
f T_Glob {} = True
|
||||
f T_BraceExpansion {} = True
|
||||
f (T_DoubleQuoted _ parts) = any f parts
|
||||
f (T_NormalWord _ parts) = any f parts
|
||||
f _ = False
|
||||
|
||||
-- This does token cause implicit concatenation in assignments?
|
||||
willConcatInAssignment token =
|
||||
case token of
|
||||
t@T_DollarBraced {} -> isArrayExpansion t
|
||||
(T_DoubleQuoted _ parts) -> any willConcatInAssignment parts
|
||||
(T_NormalWord _ parts) -> any willConcatInAssignment parts
|
||||
_ -> False
|
||||
|
||||
-- Maybe get the literal string corresponding to this token
|
||||
getLiteralString :: Token -> Maybe String
|
||||
getLiteralString = getLiteralStringExt (const Nothing)
|
||||
|
||||
-- Definitely get a literal string, skipping over all non-literals
|
||||
onlyLiteralString :: Token -> String
|
||||
onlyLiteralString = fromJust . getLiteralStringExt (const $ return "")
|
||||
|
||||
-- Maybe get a literal string, but only if it's an unquoted argument.
|
||||
getUnquotedLiteral (T_NormalWord _ list) =
|
||||
concat <$> mapM str list
|
||||
where
|
||||
str (T_Literal _ s) = return s
|
||||
str _ = Nothing
|
||||
getUnquotedLiteral _ = Nothing
|
||||
|
||||
-- Get the last unquoted T_Literal in a word like "${var}foo"THIS
|
||||
-- or nothing if the word does not end in an unquoted literal.
|
||||
getTrailingUnquotedLiteral :: Token -> Maybe Token
|
||||
getTrailingUnquotedLiteral t =
|
||||
case t of
|
||||
(T_NormalWord _ list@(_:_)) ->
|
||||
from (last list)
|
||||
_ -> Nothing
|
||||
where
|
||||
from t =
|
||||
case t of
|
||||
T_Literal {} -> return t
|
||||
_ -> Nothing
|
||||
|
||||
-- Get the leading, unquoted, literal string of a token (if any).
|
||||
getLeadingUnquotedString :: Token -> Maybe String
|
||||
getLeadingUnquotedString t =
|
||||
case t of
|
||||
T_NormalWord _ ((T_Literal _ s) : _) -> return s
|
||||
_ -> Nothing
|
||||
|
||||
-- Maybe get the literal string of this token and any globs in it.
|
||||
getGlobOrLiteralString = getLiteralStringExt f
|
||||
where
|
||||
f (T_Glob _ str) = return str
|
||||
f _ = Nothing
|
||||
|
||||
-- Maybe get the literal value of a token, using a custom function
|
||||
-- to map unrecognized Tokens into strings.
|
||||
getLiteralStringExt :: (Token -> Maybe String) -> Token -> Maybe String
|
||||
getLiteralStringExt more = g
|
||||
where
|
||||
allInList = fmap concat . mapM g
|
||||
g (T_DoubleQuoted _ l) = allInList l
|
||||
g (T_DollarDoubleQuoted _ l) = allInList l
|
||||
g (T_NormalWord _ l) = allInList l
|
||||
g (TA_Expansion _ l) = allInList l
|
||||
g (T_SingleQuoted _ s) = return s
|
||||
g (T_Literal _ s) = return s
|
||||
g (T_ParamSubSpecialChar _ s) = return s
|
||||
g x = more x
|
||||
|
||||
-- Is this token a string literal?
|
||||
isLiteral t = isJust $ getLiteralString t
|
||||
|
||||
|
||||
-- Turn a NormalWord like foo="bar $baz" into a series of constituent elements like [foo=,bar ,$baz]
|
||||
getWordParts (T_NormalWord _ l) = concatMap getWordParts l
|
||||
getWordParts (T_DoubleQuoted _ l) = l
|
||||
-- TA_Expansion is basically T_NormalWord for arithmetic expressions
|
||||
getWordParts (TA_Expansion _ l) = concatMap getWordParts l
|
||||
getWordParts other = [other]
|
||||
|
||||
-- Return a list of NormalWords that would result from brace expansion
|
||||
braceExpand (T_NormalWord id list) = take 1000 $ do
|
||||
items <- mapM part list
|
||||
return $ T_NormalWord id items
|
||||
where
|
||||
part (T_BraceExpansion id items) = do
|
||||
item <- items
|
||||
braceExpand item
|
||||
part x = return x
|
||||
|
||||
-- Maybe get a SimpleCommand from immediate wrappers like T_Redirections
|
||||
getCommand t =
|
||||
case t of
|
||||
T_Redirecting _ _ w -> getCommand w
|
||||
T_SimpleCommand _ _ (w:_) -> return t
|
||||
T_Annotation _ _ t -> getCommand t
|
||||
_ -> Nothing
|
||||
|
||||
-- Maybe get the command name of a token representing a command
|
||||
getCommandName t = do
|
||||
(T_SimpleCommand _ _ (w:rest)) <- getCommand t
|
||||
s <- getLiteralString w
|
||||
if "busybox" `isSuffixOf` s
|
||||
then
|
||||
case rest of
|
||||
(applet:_) -> getLiteralString applet
|
||||
_ -> return s
|
||||
else
|
||||
return s
|
||||
|
||||
-- If a command substitution is a single command, get its name.
|
||||
-- $(date +%s) = Just "date"
|
||||
getCommandNameFromExpansion :: Token -> Maybe String
|
||||
getCommandNameFromExpansion t =
|
||||
case t of
|
||||
T_DollarExpansion _ [c] -> extract c
|
||||
T_Backticked _ [c] -> extract c
|
||||
T_DollarBraceCommandExpansion _ [c] -> extract c
|
||||
_ -> Nothing
|
||||
where
|
||||
extract (T_Pipeline _ _ [cmd]) = getCommandName cmd
|
||||
extract _ = Nothing
|
||||
|
||||
-- Get the basename of a token representing a command
|
||||
getCommandBasename = fmap basename . getCommandName
|
||||
where
|
||||
basename = reverse . takeWhile (/= '/') . reverse
|
||||
|
||||
isAssignment t =
|
||||
case t of
|
||||
T_Redirecting _ _ w -> isAssignment w
|
||||
T_SimpleCommand _ (w:_) [] -> True
|
||||
T_Assignment {} -> True
|
||||
T_Annotation _ _ w -> isAssignment w
|
||||
_ -> False
|
||||
|
||||
isOnlyRedirection t =
|
||||
case t of
|
||||
T_Pipeline _ _ [x] -> isOnlyRedirection x
|
||||
T_Annotation _ _ w -> isOnlyRedirection w
|
||||
T_Redirecting _ (_:_) c -> isOnlyRedirection c
|
||||
T_SimpleCommand _ [] [] -> True
|
||||
_ -> False
|
||||
|
||||
isFunction t = case t of T_Function {} -> True; _ -> False
|
||||
|
||||
isBraceExpansion t = case t of T_BraceExpansion {} -> True; _ -> False
|
||||
|
||||
-- Get the lists of commands from tokens that contain them, such as
|
||||
-- the body of while loops or branches of if statements.
|
||||
getCommandSequences :: Token -> [[Token]]
|
||||
getCommandSequences t =
|
||||
case t of
|
||||
T_Script _ _ cmds -> [cmds]
|
||||
T_BraceGroup _ cmds -> [cmds]
|
||||
T_Subshell _ cmds -> [cmds]
|
||||
T_WhileExpression _ _ cmds -> [cmds]
|
||||
T_UntilExpression _ _ cmds -> [cmds]
|
||||
T_ForIn _ _ _ cmds -> [cmds]
|
||||
T_ForArithmetic _ _ _ _ cmds -> [cmds]
|
||||
T_IfExpression _ thens elses -> map snd thens ++ [elses]
|
||||
T_Annotation _ _ t -> getCommandSequences t
|
||||
_ -> []
|
||||
|
||||
-- Get a list of names of associative arrays
|
||||
getAssociativeArrays t =
|
||||
nub . execWriter $ doAnalysis f t
|
||||
where
|
||||
f :: Token -> Writer [String] ()
|
||||
f t@T_SimpleCommand {} = fromMaybe (return ()) $ do
|
||||
name <- getCommandName t
|
||||
let assocNames = ["declare","local","typeset"]
|
||||
guard $ elem name assocNames
|
||||
let flags = getAllFlags t
|
||||
guard $ elem "A" $ map snd flags
|
||||
let args = map fst . filter ((==) "" . snd) $ flags
|
||||
let names = mapMaybe (getLiteralStringExt nameAssignments) args
|
||||
return $ tell names
|
||||
f _ = return ()
|
||||
|
||||
nameAssignments t =
|
||||
case t of
|
||||
T_Assignment _ _ name _ _ -> return name
|
||||
_ -> Nothing
|
||||
|
||||
-- A Pseudoglob is a wildcard pattern used for checking if a match can succeed.
|
||||
-- For example, [[ $(cmd).jpg == [a-z] ]] will give the patterns *.jpg and ?, which
|
||||
-- can be proven never to match.
|
||||
data PseudoGlob = PGAny | PGMany | PGChar Char
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- Turn a word into a PG pattern, replacing all unknown/runtime values with
|
||||
-- PGMany.
|
||||
wordToPseudoGlob :: Token -> Maybe [PseudoGlob]
|
||||
wordToPseudoGlob word =
|
||||
simplifyPseudoGlob . concat <$> mapM f (getWordParts word)
|
||||
where
|
||||
f x = case x of
|
||||
T_Literal _ s -> return $ map PGChar s
|
||||
T_SingleQuoted _ s -> return $ map PGChar s
|
||||
|
||||
T_DollarBraced {} -> return [PGMany]
|
||||
T_DollarExpansion {} -> return [PGMany]
|
||||
T_Backticked {} -> return [PGMany]
|
||||
|
||||
T_Glob _ "?" -> return [PGAny]
|
||||
T_Glob _ ('[':_) -> return [PGAny]
|
||||
T_Glob {} -> return [PGMany]
|
||||
|
||||
T_Extglob {} -> return [PGMany]
|
||||
|
||||
_ -> return [PGMany]
|
||||
|
||||
-- Turn a word into a PG pattern, but only if we can preserve
|
||||
-- exact semantics.
|
||||
wordToExactPseudoGlob :: Token -> Maybe [PseudoGlob]
|
||||
wordToExactPseudoGlob word =
|
||||
simplifyPseudoGlob . concat <$> mapM f (getWordParts word)
|
||||
where
|
||||
f x = case x of
|
||||
T_Literal _ s -> return $ map PGChar s
|
||||
T_SingleQuoted _ s -> return $ map PGChar s
|
||||
T_Glob _ "?" -> return [PGAny]
|
||||
T_Glob _ "*" -> return [PGMany]
|
||||
_ -> fail "Unknown token type"
|
||||
|
||||
-- Reorder a PseudoGlob for more efficient matching, e.g.
|
||||
-- f?*?**g -> f??*g
|
||||
simplifyPseudoGlob :: [PseudoGlob] -> [PseudoGlob]
|
||||
simplifyPseudoGlob = f
|
||||
where
|
||||
f [] = []
|
||||
f (x@(PGChar _) : rest ) = x : f rest
|
||||
f list =
|
||||
let (anys, rest) = span (\x -> x == PGMany || x == PGAny) list in
|
||||
order anys ++ f rest
|
||||
|
||||
order s = let (any, many) = partition (== PGAny) s in
|
||||
any ++ take 1 many
|
||||
|
||||
-- Check whether the two patterns can ever overlap.
|
||||
pseudoGlobsCanOverlap :: [PseudoGlob] -> [PseudoGlob] -> Bool
|
||||
pseudoGlobsCanOverlap = matchable
|
||||
where
|
||||
matchable x@(xf:xs) y@(yf:ys) =
|
||||
case (xf, yf) of
|
||||
(PGMany, _) -> matchable x ys || matchable xs y
|
||||
(_, PGMany) -> matchable x ys || matchable xs y
|
||||
(PGAny, _) -> matchable xs ys
|
||||
(_, PGAny) -> matchable xs ys
|
||||
(_, _) -> xf == yf && matchable xs ys
|
||||
|
||||
matchable [] [] = True
|
||||
matchable (PGMany : rest) [] = matchable rest []
|
||||
matchable (_:_) [] = False
|
||||
matchable [] r = matchable r []
|
||||
|
||||
-- Check whether the first pattern always overlaps the second.
|
||||
pseudoGlobIsSuperSetof :: [PseudoGlob] -> [PseudoGlob] -> Bool
|
||||
pseudoGlobIsSuperSetof = matchable
|
||||
where
|
||||
matchable x@(xf:xs) y@(yf:ys) =
|
||||
case (xf, yf) of
|
||||
(PGMany, PGMany) -> matchable x ys
|
||||
(PGMany, _) -> matchable x ys || matchable xs y
|
||||
(_, PGMany) -> False
|
||||
(PGAny, _) -> matchable xs ys
|
||||
(_, PGAny) -> False
|
||||
(_, _) -> xf == yf && matchable xs ys
|
||||
|
||||
matchable [] [] = True
|
||||
matchable (PGMany : rest) [] = matchable rest []
|
||||
matchable _ _ = False
|
||||
|
||||
wordsCanBeEqual x y = fromMaybe True $
|
||||
liftM2 pseudoGlobsCanOverlap (wordToPseudoGlob x) (wordToPseudoGlob y)
|
2912
src/ShellCheck/Analytics.hs
Normal file
2912
src/ShellCheck/Analytics.hs
Normal file
File diff suppressed because it is too large
Load diff
45
src/ShellCheck/Analyzer.hs
Normal file
45
src/ShellCheck/Analyzer.hs
Normal file
|
@ -0,0 +1,45 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
module ShellCheck.Analyzer (analyzeScript) where
|
||||
|
||||
import ShellCheck.Analytics
|
||||
import ShellCheck.AnalyzerLib
|
||||
import ShellCheck.Interface
|
||||
import Data.List
|
||||
import Data.Monoid
|
||||
import qualified ShellCheck.Checks.Commands
|
||||
import qualified ShellCheck.Checks.ShellSupport
|
||||
|
||||
|
||||
-- TODO: Clean up the cruft this is layered on
|
||||
analyzeScript :: AnalysisSpec -> AnalysisResult
|
||||
analyzeScript spec = AnalysisResult {
|
||||
arComments =
|
||||
filterByAnnotation spec params . nub $
|
||||
runAnalytics spec
|
||||
++ runChecker params (checkers params)
|
||||
}
|
||||
where
|
||||
params = makeParameters spec
|
||||
|
||||
checkers params = mconcat $ map ($ params) [
|
||||
ShellCheck.Checks.Commands.checker,
|
||||
ShellCheck.Checks.ShellSupport.checker
|
||||
]
|
868
src/ShellCheck/AnalyzerLib.hs
Normal file
868
src/ShellCheck/AnalyzerLib.hs
Normal file
|
@ -0,0 +1,868 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
module ShellCheck.AnalyzerLib where
|
||||
import ShellCheck.AST
|
||||
import ShellCheck.ASTLib
|
||||
import ShellCheck.Data
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.Parser
|
||||
import ShellCheck.Regex
|
||||
|
||||
import Control.Arrow (first)
|
||||
import Control.Monad.Identity
|
||||
import Control.Monad.RWS
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Writer
|
||||
import Data.Char
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import qualified Data.Map as Map
|
||||
|
||||
import Test.QuickCheck.All (forAllProperties)
|
||||
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
|
||||
|
||||
type Analysis = AnalyzerM ()
|
||||
type AnalyzerM a = RWS Parameters [TokenComment] Cache a
|
||||
nullCheck = const $ return ()
|
||||
|
||||
|
||||
data Checker = Checker {
|
||||
perScript :: Root -> Analysis,
|
||||
perToken :: Token -> Analysis
|
||||
}
|
||||
|
||||
runChecker :: Parameters -> Checker -> [TokenComment]
|
||||
runChecker params checker = notes
|
||||
where
|
||||
root = rootNode params
|
||||
check = perScript checker `composeAnalyzers` (\(Root x) -> void $ doAnalysis (perToken checker) x)
|
||||
notes = snd $ evalRWS (check $ Root root) params Cache
|
||||
|
||||
instance Monoid Checker where
|
||||
mempty = Checker {
|
||||
perScript = nullCheck,
|
||||
perToken = nullCheck
|
||||
}
|
||||
mappend x y = Checker {
|
||||
perScript = perScript x `composeAnalyzers` perScript y,
|
||||
perToken = perToken x `composeAnalyzers` perToken y
|
||||
}
|
||||
|
||||
|
||||
composeAnalyzers :: (a -> Analysis) -> (a -> Analysis) -> a -> Analysis
|
||||
composeAnalyzers f g x = f x >> g x
|
||||
|
||||
data Parameters = Parameters {
|
||||
hasLastpipe :: Bool, -- Whether this script has the 'lastpipe' option set/default.
|
||||
hasSetE :: Bool, -- Whether this script has 'set -e' anywhere.
|
||||
variableFlow :: [StackData], -- A linear (bad) analysis of data flow
|
||||
parentMap :: Map.Map Id Token, -- A map from Id to parent Token
|
||||
shellType :: Shell, -- The shell type, such as Bash or Ksh
|
||||
shellTypeSpecified :: Bool, -- True if shell type was forced via flags
|
||||
rootNode :: Token -- The root node of the AST
|
||||
}
|
||||
|
||||
-- TODO: Cache results of common AST ops here
|
||||
data Cache = Cache {}
|
||||
|
||||
data Scope = SubshellScope String | NoneScope deriving (Show, Eq)
|
||||
data StackData =
|
||||
StackScope Scope
|
||||
| StackScopeEnd
|
||||
-- (Base expression, specific position, var name, assigned values)
|
||||
| Assignment (Token, Token, String, DataType)
|
||||
| Reference (Token, Token, String)
|
||||
deriving (Show)
|
||||
|
||||
data DataType = DataString DataSource | DataArray DataSource
|
||||
deriving (Show)
|
||||
|
||||
data DataSource =
|
||||
SourceFrom [Token]
|
||||
| SourceExternal
|
||||
| SourceDeclaration
|
||||
| SourceInteger
|
||||
| SourceChecked
|
||||
deriving (Show)
|
||||
|
||||
data VariableState = Dead Token String | Alive deriving (Show)
|
||||
|
||||
defaultSpec root = AnalysisSpec {
|
||||
asScript = root,
|
||||
asShellType = Nothing,
|
||||
asCheckSourced = False,
|
||||
asExecutionMode = Executed
|
||||
}
|
||||
|
||||
pScript s =
|
||||
let
|
||||
pSpec = ParseSpec {
|
||||
psFilename = "script",
|
||||
psScript = s,
|
||||
psCheckSourced = False
|
||||
}
|
||||
in prRoot . runIdentity $ parseScript (mockedSystemInterface []) pSpec
|
||||
|
||||
-- For testing. If parsed, returns whether there are any comments
|
||||
producesComments :: Checker -> String -> Maybe Bool
|
||||
producesComments c s = do
|
||||
root <- pScript s
|
||||
let spec = defaultSpec root
|
||||
let params = makeParameters spec
|
||||
return . not . null $ runChecker params c
|
||||
|
||||
makeComment :: Severity -> Id -> Code -> String -> TokenComment
|
||||
makeComment severity id code note =
|
||||
TokenComment id $ Comment severity code note
|
||||
|
||||
addComment note = tell [note]
|
||||
|
||||
warn :: MonadWriter [TokenComment] m => Id -> Code -> String -> m ()
|
||||
warn id code str = addComment $ makeComment WarningC id code str
|
||||
err id code str = addComment $ makeComment ErrorC id code str
|
||||
info id code str = addComment $ makeComment InfoC id code str
|
||||
style id code str = addComment $ makeComment StyleC id code str
|
||||
|
||||
makeParameters spec =
|
||||
let params = Parameters {
|
||||
rootNode = root,
|
||||
shellType = fromMaybe (determineShell root) $ asShellType spec,
|
||||
hasSetE = containsSetE root,
|
||||
hasLastpipe =
|
||||
case shellType params of
|
||||
Bash -> containsLastpipe root
|
||||
Dash -> False
|
||||
Sh -> False
|
||||
Ksh -> True,
|
||||
|
||||
shellTypeSpecified = isJust $ asShellType spec,
|
||||
parentMap = getParentTree root,
|
||||
variableFlow = getVariableFlow params root
|
||||
} in params
|
||||
where root = asScript spec
|
||||
|
||||
|
||||
-- Does this script mention 'set -e' anywhere?
|
||||
-- Used as a hack to disable certain warnings.
|
||||
containsSetE root = isNothing $ doAnalysis (guard . not . isSetE) root
|
||||
where
|
||||
isSetE t =
|
||||
case t of
|
||||
T_Script _ str _ -> str `matches` re
|
||||
T_SimpleCommand {} ->
|
||||
t `isUnqualifiedCommand` "set" &&
|
||||
("errexit" `elem` oversimplify t ||
|
||||
"e" `elem` map snd (getAllFlags t))
|
||||
_ -> False
|
||||
re = mkRegex "[[:space:]]-[^-]*e"
|
||||
|
||||
-- Does this script mention 'shopt -s lastpipe' anywhere?
|
||||
-- Also used as a hack.
|
||||
containsLastpipe root =
|
||||
isNothing $ doAnalysis (guard . not . isShoptLastPipe) root
|
||||
where
|
||||
isShoptLastPipe t =
|
||||
case t of
|
||||
T_SimpleCommand {} ->
|
||||
t `isUnqualifiedCommand` "shopt" &&
|
||||
("lastpipe" `elem` oversimplify t)
|
||||
_ -> False
|
||||
|
||||
|
||||
prop_determineShell0 = determineShell (fromJust $ pScript "#!/bin/sh") == Sh
|
||||
prop_determineShell1 = determineShell (fromJust $ pScript "#!/usr/bin/env ksh") == Ksh
|
||||
prop_determineShell2 = determineShell (fromJust $ pScript "") == Bash
|
||||
prop_determineShell3 = determineShell (fromJust $ pScript "#!/bin/sh -e") == Sh
|
||||
prop_determineShell4 = determineShell (fromJust $ pScript
|
||||
"#!/bin/ksh\n#shellcheck shell=sh\nfoo") == Sh
|
||||
prop_determineShell5 = determineShell (fromJust $ pScript
|
||||
"#shellcheck shell=sh\nfoo") == Sh
|
||||
prop_determineShell6 = determineShell (fromJust $ pScript "#! /bin/sh") == Sh
|
||||
prop_determineShell7 = determineShell (fromJust $ pScript "#! /bin/ash") == Dash
|
||||
determineShell t = fromMaybe Bash $ do
|
||||
shellString <- foldl mplus Nothing $ getCandidates t
|
||||
shellForExecutable shellString
|
||||
where
|
||||
forAnnotation t =
|
||||
case t of
|
||||
(ShellOverride s) -> return s
|
||||
_ -> fail ""
|
||||
getCandidates :: Token -> [Maybe String]
|
||||
getCandidates t@T_Script {} = [Just $ fromShebang t]
|
||||
getCandidates (T_Annotation _ annotations s) =
|
||||
map forAnnotation annotations ++
|
||||
[Just $ fromShebang s]
|
||||
fromShebang (T_Script _ s t) = executableFromShebang s
|
||||
|
||||
-- Given a string like "/bin/bash" or "/usr/bin/env dash",
|
||||
-- return the shell basename like "bash" or "dash"
|
||||
executableFromShebang :: String -> String
|
||||
executableFromShebang = shellFor
|
||||
where
|
||||
shellFor s | "/env " `isInfixOf` s = head (drop 1 (words s)++[""])
|
||||
shellFor s | ' ' `elem` s = shellFor $ takeWhile (/= ' ') s
|
||||
shellFor s = reverse . takeWhile (/= '/') . reverse $ s
|
||||
|
||||
|
||||
|
||||
-- Given a root node, make a map from Id to parent Token.
|
||||
-- This is used to populate parentMap in Parameters
|
||||
getParentTree :: Token -> Map.Map Id Token
|
||||
getParentTree t =
|
||||
snd . snd $ runState (doStackAnalysis pre post t) ([], Map.empty)
|
||||
where
|
||||
pre t = modify (first ((:) t))
|
||||
post t = do
|
||||
(_:rest, map) <- get
|
||||
case rest of [] -> put (rest, map)
|
||||
(x:_) -> put (rest, Map.insert (getId t) x map)
|
||||
|
||||
-- Given a root node, make a map from Id to Token
|
||||
getTokenMap :: Token -> Map.Map Id Token
|
||||
getTokenMap t =
|
||||
execState (doAnalysis f t) Map.empty
|
||||
where
|
||||
f t = modify (Map.insert (getId t) t)
|
||||
|
||||
|
||||
-- Is this token in a quoting free context? (i.e. would variable expansion split)
|
||||
-- True: Assignments, [[ .. ]], here docs, already in double quotes
|
||||
-- False: Regular words
|
||||
isStrictlyQuoteFree = isQuoteFreeNode True
|
||||
|
||||
-- Like above, but also allow some cases where splitting may be desired.
|
||||
-- True: Like above + for loops
|
||||
-- False: Like above
|
||||
isQuoteFree = isQuoteFreeNode False
|
||||
|
||||
|
||||
isQuoteFreeNode strict tree t =
|
||||
(isQuoteFreeElement t == Just True) ||
|
||||
head (mapMaybe isQuoteFreeContext (drop 1 $ getPath tree t) ++ [False])
|
||||
where
|
||||
-- Is this node self-quoting in itself?
|
||||
isQuoteFreeElement t =
|
||||
case t of
|
||||
T_Assignment {} -> return True
|
||||
T_FdRedirect {} -> return True
|
||||
_ -> Nothing
|
||||
|
||||
-- Are any subnodes inherently self-quoting?
|
||||
isQuoteFreeContext t =
|
||||
case t of
|
||||
TC_Nullary _ DoubleBracket _ -> return True
|
||||
TC_Unary _ DoubleBracket _ _ -> return True
|
||||
TC_Binary _ DoubleBracket _ _ _ -> return True
|
||||
TA_Sequence {} -> return True
|
||||
T_Arithmetic {} -> return True
|
||||
T_Assignment {} -> return True
|
||||
T_Redirecting {} -> return False
|
||||
T_DoubleQuoted _ _ -> return True
|
||||
T_DollarDoubleQuoted _ _ -> return True
|
||||
T_CaseExpression {} -> return True
|
||||
T_HereDoc {} -> return True
|
||||
T_DollarBraced {} -> return True
|
||||
-- When non-strict, pragmatically assume it's desirable to split here
|
||||
T_ForIn {} -> return (not strict)
|
||||
T_SelectIn {} -> return (not strict)
|
||||
_ -> Nothing
|
||||
|
||||
-- Check if a token is a parameter to a certain command by name:
|
||||
-- Example: isParamTo (parentMap params) "sed" t
|
||||
isParamTo :: Map.Map Id Token -> String -> Token -> Bool
|
||||
isParamTo tree cmd =
|
||||
go
|
||||
where
|
||||
go x = case Map.lookup (getId x) tree of
|
||||
Nothing -> False
|
||||
Just parent -> check parent
|
||||
check t =
|
||||
case t of
|
||||
T_SingleQuoted _ _ -> go t
|
||||
T_DoubleQuoted _ _ -> go t
|
||||
T_NormalWord _ _ -> go t
|
||||
T_SimpleCommand {} -> isCommand t cmd
|
||||
T_Redirecting {} -> isCommand t cmd
|
||||
_ -> False
|
||||
|
||||
-- Get the parent command (T_Redirecting) of a Token, if any.
|
||||
getClosestCommand :: Map.Map Id Token -> Token -> Maybe Token
|
||||
getClosestCommand tree t =
|
||||
findFirst findCommand $ getPath tree t
|
||||
where
|
||||
findCommand t =
|
||||
case t of
|
||||
T_Redirecting {} -> return True
|
||||
T_Script {} -> return False
|
||||
_ -> Nothing
|
||||
|
||||
-- Like above, if koala_man knew Haskell when starting this project.
|
||||
getClosestCommandM t = do
|
||||
tree <- asks parentMap
|
||||
return $ getClosestCommand tree t
|
||||
|
||||
-- Is the token used as a command name (the first word in a T_SimpleCommand)?
|
||||
usedAsCommandName tree token = go (getId token) (tail $ getPath tree token)
|
||||
where
|
||||
go currentId (T_NormalWord id [word]:rest)
|
||||
| currentId == getId word = go id rest
|
||||
go currentId (T_DoubleQuoted id [word]:rest)
|
||||
| currentId == getId word = go id rest
|
||||
go currentId (T_SimpleCommand _ _ (word:_):_)
|
||||
| currentId == getId word = True
|
||||
go _ _ = False
|
||||
|
||||
-- A list of the element and all its parents up to the root node.
|
||||
getPath tree t = t :
|
||||
case Map.lookup (getId t) tree of
|
||||
Nothing -> []
|
||||
Just parent -> getPath tree parent
|
||||
|
||||
-- Version of the above taking the map from the current context
|
||||
-- Todo: give this the name "getPath"
|
||||
getPathM t = do
|
||||
map <- asks parentMap
|
||||
return $ getPath map t
|
||||
|
||||
isParentOf tree parent child =
|
||||
elem (getId parent) . map getId $ getPath tree child
|
||||
|
||||
parents params = getPath (parentMap params)
|
||||
|
||||
pathTo t = do
|
||||
parents <- reader parentMap
|
||||
return $ getPath parents t
|
||||
|
||||
-- Find the first match in a list where the predicate is Just True.
|
||||
-- Stops if it's Just False and ignores Nothing.
|
||||
findFirst :: (a -> Maybe Bool) -> [a] -> Maybe a
|
||||
findFirst p l =
|
||||
case l of
|
||||
[] -> Nothing
|
||||
(x:xs) ->
|
||||
case p x of
|
||||
Just True -> return x
|
||||
Just False -> Nothing
|
||||
Nothing -> findFirst p xs
|
||||
|
||||
-- Check whether a word is entirely output from a single command
|
||||
tokenIsJustCommandOutput t = case t of
|
||||
T_NormalWord id [T_DollarExpansion _ cmds] -> check cmds
|
||||
T_NormalWord id [T_DoubleQuoted _ [T_DollarExpansion _ cmds]] -> check cmds
|
||||
T_NormalWord id [T_Backticked _ cmds] -> check cmds
|
||||
T_NormalWord id [T_DoubleQuoted _ [T_Backticked _ cmds]] -> check cmds
|
||||
_ -> False
|
||||
where
|
||||
check [x] = not $ isOnlyRedirection x
|
||||
check _ = False
|
||||
|
||||
-- TODO: Replace this with a proper Control Flow Graph
|
||||
getVariableFlow params t =
|
||||
let (_, stack) = runState (doStackAnalysis startScope endScope t) []
|
||||
in reverse stack
|
||||
where
|
||||
startScope t =
|
||||
let scopeType = leadType params t
|
||||
in do
|
||||
when (scopeType /= NoneScope) $ modify (StackScope scopeType:)
|
||||
when (assignFirst t) $ setWritten t
|
||||
|
||||
endScope t =
|
||||
let scopeType = leadType params t
|
||||
in do
|
||||
setRead t
|
||||
unless (assignFirst t) $ setWritten t
|
||||
when (scopeType /= NoneScope) $ modify (StackScopeEnd:)
|
||||
|
||||
assignFirst T_ForIn {} = True
|
||||
assignFirst T_SelectIn {} = True
|
||||
assignFirst _ = False
|
||||
|
||||
setRead t =
|
||||
let read = getReferencedVariables (parentMap params) t
|
||||
in mapM_ (\v -> modify (Reference v:)) read
|
||||
|
||||
setWritten t =
|
||||
let written = getModifiedVariables t
|
||||
in mapM_ (\v -> modify (Assignment v:)) written
|
||||
|
||||
|
||||
leadType params t =
|
||||
case t of
|
||||
T_DollarExpansion _ _ -> SubshellScope "$(..) expansion"
|
||||
T_Backticked _ _ -> SubshellScope "`..` expansion"
|
||||
T_Backgrounded _ _ -> SubshellScope "backgrounding &"
|
||||
T_Subshell _ _ -> SubshellScope "(..) group"
|
||||
T_CoProcBody _ _ -> SubshellScope "coproc"
|
||||
T_Redirecting {} ->
|
||||
if fromMaybe False causesSubshell
|
||||
then SubshellScope "pipeline"
|
||||
else NoneScope
|
||||
_ -> NoneScope
|
||||
where
|
||||
parentPipeline = do
|
||||
parent <- Map.lookup (getId t) (parentMap params)
|
||||
case parent of
|
||||
T_Pipeline {} -> return parent
|
||||
_ -> Nothing
|
||||
|
||||
causesSubshell = do
|
||||
(T_Pipeline _ _ list) <- parentPipeline
|
||||
if length list <= 1
|
||||
then return False
|
||||
else if not $ hasLastpipe params
|
||||
then return True
|
||||
else return . not $ (getId . head $ reverse list) == getId t
|
||||
|
||||
getModifiedVariables t =
|
||||
case t of
|
||||
T_SimpleCommand _ vars [] ->
|
||||
concatMap (\x -> case x of
|
||||
T_Assignment id _ name _ w ->
|
||||
[(x, x, name, dataTypeFrom DataString w)]
|
||||
_ -> []
|
||||
) vars
|
||||
c@T_SimpleCommand {} ->
|
||||
getModifiedVariableCommand c
|
||||
|
||||
TA_Unary _ "++|" v@(TA_Variable _ name _) ->
|
||||
[(t, v, name, DataString $ SourceFrom [v])]
|
||||
TA_Unary _ "|++" v@(TA_Variable _ name _) ->
|
||||
[(t, v, name, DataString $ SourceFrom [v])]
|
||||
TA_Assignment _ op (TA_Variable _ name _) rhs -> maybeToList $ do
|
||||
guard $ op `elem` ["=", "*=", "/=", "%=", "+=", "-=", "<<=", ">>=", "&=", "^=", "|="]
|
||||
return (t, t, name, DataString $ SourceFrom [rhs])
|
||||
|
||||
-- Count [[ -v foo ]] as an "assignment".
|
||||
-- This is to prevent [ -v foo ] being unassigned or unused.
|
||||
TC_Unary id _ "-v" token -> maybeToList $ do
|
||||
str <- fmap (takeWhile (/= '[')) $ -- Quoted index
|
||||
flip getLiteralStringExt token $ \x ->
|
||||
case x of
|
||||
T_Glob _ s -> return s -- Unquoted index
|
||||
_ -> Nothing
|
||||
|
||||
guard . not . null $ str
|
||||
return (t, token, str, DataString $ SourceChecked)
|
||||
|
||||
T_DollarBraced _ l -> maybeToList $ do
|
||||
let string = bracedString t
|
||||
let modifier = getBracedModifier string
|
||||
guard $ ":=" `isPrefixOf` modifier
|
||||
return (t, t, getBracedReference string, DataString $ SourceFrom [l])
|
||||
|
||||
t@(T_FdRedirect _ ('{':var) op) -> -- {foo}>&2 modifies foo
|
||||
[(t, t, takeWhile (/= '}') var, DataString SourceInteger) | not $ isClosingFileOp op]
|
||||
|
||||
t@(T_CoProc _ name _) ->
|
||||
[(t, t, fromMaybe "COPROC" name, DataArray SourceInteger)]
|
||||
|
||||
--Points to 'for' rather than variable
|
||||
T_ForIn id str [] _ -> [(t, t, str, DataString SourceExternal)]
|
||||
T_ForIn id str words _ -> [(t, t, str, DataString $ SourceFrom words)]
|
||||
T_SelectIn id str words _ -> [(t, t, str, DataString $ SourceFrom words)]
|
||||
_ -> []
|
||||
|
||||
isClosingFileOp op =
|
||||
case op of
|
||||
T_IoDuplicate _ (T_GREATAND _) "-" -> True
|
||||
T_IoDuplicate _ (T_LESSAND _) "-" -> True
|
||||
_ -> False
|
||||
|
||||
|
||||
-- Consider 'export/declare -x' a reference, since it makes the var available
|
||||
getReferencedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal _ x:_):rest)) =
|
||||
case x of
|
||||
"export" -> if "f" `elem` flags
|
||||
then []
|
||||
else concatMap getReference rest
|
||||
"declare" -> if any (`elem` flags) ["x", "p"]
|
||||
then concatMap getReference rest
|
||||
else []
|
||||
"readonly" ->
|
||||
if any (`elem` flags) ["f", "p"]
|
||||
then []
|
||||
else concatMap getReference rest
|
||||
"trap" ->
|
||||
case rest of
|
||||
head:_ -> map (\x -> (head, head, x)) $ getVariablesFromLiteralToken head
|
||||
_ -> []
|
||||
_ -> []
|
||||
where
|
||||
getReference t@(T_Assignment _ _ name _ value) = [(t, t, name)]
|
||||
getReference t@(T_NormalWord _ [T_Literal _ name]) | not ("-" `isPrefixOf` name) = [(t, t, name)]
|
||||
getReference _ = []
|
||||
flags = map snd $ getAllFlags base
|
||||
|
||||
getReferencedVariableCommand _ = []
|
||||
|
||||
getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal _ x:_):rest)) =
|
||||
filter (\(_,_,s,_) -> not ("-" `isPrefixOf` s)) $
|
||||
case x of
|
||||
"read" ->
|
||||
let params = map getLiteral rest in
|
||||
catMaybes . takeWhile isJust . reverse $ params
|
||||
"getopts" ->
|
||||
case rest of
|
||||
opts:var:_ -> maybeToList $ getLiteral var
|
||||
_ -> []
|
||||
|
||||
"let" -> concatMap letParamToLiteral rest
|
||||
|
||||
"export" ->
|
||||
if "f" `elem` flags then [] else concatMap getModifierParamString rest
|
||||
|
||||
"declare" -> if any (`elem` flags) ["F", "f", "p"] then [] else declaredVars
|
||||
"typeset" -> declaredVars
|
||||
|
||||
"local" -> concatMap getModifierParamString rest
|
||||
"readonly" ->
|
||||
if any (`elem` flags) ["f", "p"]
|
||||
then []
|
||||
else concatMap getModifierParamString rest
|
||||
"set" -> maybeToList $ do
|
||||
params <- getSetParams rest
|
||||
return (base, base, "@", DataString $ SourceFrom params)
|
||||
|
||||
"printf" -> maybeToList $ getPrintfVariable rest
|
||||
|
||||
"mapfile" -> maybeToList $ getMapfileArray base rest
|
||||
"readarray" -> maybeToList $ getMapfileArray base rest
|
||||
|
||||
_ -> []
|
||||
where
|
||||
flags = map snd $ getAllFlags base
|
||||
stripEquals s = let rest = dropWhile (/= '=') s in
|
||||
if rest == "" then "" else tail rest
|
||||
stripEqualsFrom (T_NormalWord id1 (T_Literal id2 s:rs)) =
|
||||
T_NormalWord id1 (T_Literal id2 (stripEquals s):rs)
|
||||
stripEqualsFrom (T_NormalWord id1 [T_DoubleQuoted id2 [T_Literal id3 s]]) =
|
||||
T_NormalWord id1 [T_DoubleQuoted id2 [T_Literal id3 (stripEquals s)]]
|
||||
stripEqualsFrom t = t
|
||||
|
||||
declaredVars = concatMap (getModifierParam defaultType) rest
|
||||
where
|
||||
defaultType = if any (`elem` flags) ["a", "A"] then DataArray else DataString
|
||||
|
||||
getLiteral t = do
|
||||
s <- getLiteralString t
|
||||
when ("-" `isPrefixOf` s) $ fail "argument"
|
||||
return (base, t, s, DataString SourceExternal)
|
||||
|
||||
getModifierParamString = getModifierParam DataString
|
||||
|
||||
getModifierParam def t@(T_Assignment _ _ name _ value) =
|
||||
[(base, t, name, dataTypeFrom def value)]
|
||||
getModifierParam def t@T_NormalWord {} = maybeToList $ do
|
||||
name <- getLiteralString t
|
||||
guard $ isVariableName name
|
||||
return (base, t, name, def SourceDeclaration)
|
||||
getModifierParam _ _ = []
|
||||
|
||||
letParamToLiteral token =
|
||||
if var == ""
|
||||
then []
|
||||
else [(base, token, var, DataString $ SourceFrom [stripEqualsFrom token])]
|
||||
where var = takeWhile isVariableChar $ dropWhile (`elem` "+-") $ concat $ oversimplify token
|
||||
|
||||
getSetParams (t:_:rest) | getLiteralString t == Just "-o" = getSetParams rest
|
||||
getSetParams (t:rest) =
|
||||
let s = getLiteralString t in
|
||||
case s of
|
||||
Just "--" -> return rest
|
||||
Just ('-':_) -> getSetParams rest
|
||||
_ -> return (t:fromMaybe [] (getSetParams rest))
|
||||
getSetParams [] = Nothing
|
||||
|
||||
getPrintfVariable list = f $ map (\x -> (x, getLiteralString x)) list
|
||||
where
|
||||
f ((_, Just "-v") : (t, Just var) : _) = return (base, t, var, DataString $ SourceFrom list)
|
||||
f (_:rest) = f rest
|
||||
f [] = fail "not found"
|
||||
|
||||
-- mapfile has some curious syntax allowing flags plus 0..n variable names
|
||||
-- where only the first non-option one is used if any. Here we cheat and
|
||||
-- just get the last one, if it's a variable name.
|
||||
getMapfileArray base arguments = do
|
||||
lastArg <- listToMaybe (reverse arguments)
|
||||
name <- getLiteralString lastArg
|
||||
guard $ isVariableName name
|
||||
return (base, lastArg, name, DataArray SourceExternal)
|
||||
|
||||
getModifiedVariableCommand _ = []
|
||||
|
||||
getIndexReferences s = fromMaybe [] $ do
|
||||
match <- matchRegex re s
|
||||
index <- match !!! 0
|
||||
return $ matchAllStrings variableNameRegex index
|
||||
where
|
||||
re = mkRegex "(\\[.*\\])"
|
||||
|
||||
getOffsetReferences mods = fromMaybe [] $ do
|
||||
match <- matchRegex re mods
|
||||
offsets <- match !!! 0
|
||||
return $ matchAllStrings variableNameRegex offsets
|
||||
where
|
||||
re = mkRegex "^ *:([^-=?+].*)"
|
||||
|
||||
getReferencedVariables parents t =
|
||||
case t of
|
||||
T_DollarBraced id l -> let str = bracedString t in
|
||||
(t, t, getBracedReference str) :
|
||||
map (\x -> (l, l, x)) (
|
||||
getIndexReferences str
|
||||
++ getOffsetReferences (getBracedModifier str))
|
||||
TA_Variable id name _ ->
|
||||
if isArithmeticAssignment t
|
||||
then []
|
||||
else [(t, t, name)]
|
||||
T_Assignment id mode str _ word ->
|
||||
[(t, t, str) | mode == Append] ++ specialReferences str t word
|
||||
|
||||
TC_Unary id _ "-v" token -> getIfReference t token
|
||||
TC_Unary id _ "-R" token -> getIfReference t token
|
||||
TC_Binary id DoubleBracket op lhs rhs ->
|
||||
if isDereferencing op
|
||||
then concatMap (getIfReference t) [lhs, rhs]
|
||||
else []
|
||||
|
||||
t@(T_FdRedirect _ ('{':var) op) -> -- {foo}>&- references and closes foo
|
||||
[(t, t, takeWhile (/= '}') var) | isClosingFileOp op]
|
||||
x -> getReferencedVariableCommand x
|
||||
where
|
||||
-- Try to reduce false positives for unused vars only referenced from evaluated vars
|
||||
specialReferences name base word =
|
||||
if name `elem` [
|
||||
"PS1", "PS2", "PS3", "PS4",
|
||||
"PROMPT_COMMAND"
|
||||
]
|
||||
then
|
||||
map (\x -> (base, base, x)) $
|
||||
getVariablesFromLiteralToken word
|
||||
else []
|
||||
|
||||
literalizer t = case t of
|
||||
T_Glob _ s -> return s -- Also when parsed as globs
|
||||
_ -> Nothing
|
||||
|
||||
getIfReference context token = maybeToList $ do
|
||||
str <- getLiteralStringExt literalizer token
|
||||
guard . not $ null str
|
||||
when (isDigit $ head str) $ fail "is a number"
|
||||
return (context, token, getBracedReference str)
|
||||
|
||||
isDereferencing = (`elem` ["-eq", "-ne", "-lt", "-le", "-gt", "-ge"])
|
||||
|
||||
isArithmeticAssignment t = case getPath parents t of
|
||||
this: TA_Assignment _ "=" lhs _ :_ -> lhs == t
|
||||
_ -> False
|
||||
|
||||
dataTypeFrom defaultType v = (case v of T_Array {} -> DataArray; _ -> defaultType) $ SourceFrom [v]
|
||||
|
||||
|
||||
--- Command specific checks
|
||||
|
||||
-- Compare a command to a string: t `isCommand` "sed" (also matches /usr/bin/sed)
|
||||
isCommand token str = isCommandMatch token (\cmd -> cmd == str || ('/' : str) `isSuffixOf` cmd)
|
||||
|
||||
-- Compare a command to a literal. Like above, but checks full path.
|
||||
isUnqualifiedCommand token str = isCommandMatch token (== str)
|
||||
|
||||
isCommandMatch token matcher = fromMaybe False $ do
|
||||
cmd <- getCommandName token
|
||||
return $ matcher cmd
|
||||
|
||||
-- Does this regex look like it was intended as a glob?
|
||||
-- True: *foo*
|
||||
-- False: .*foo.*
|
||||
isConfusedGlobRegex :: String -> Bool
|
||||
isConfusedGlobRegex ('*':_) = True
|
||||
isConfusedGlobRegex [x,'*'] | x /= '\\' = True
|
||||
isConfusedGlobRegex _ = False
|
||||
|
||||
isVariableStartChar x = x == '_' || isAsciiLower x || isAsciiUpper x
|
||||
isVariableChar x = isVariableStartChar x || isDigit x
|
||||
variableNameRegex = mkRegex "[_a-zA-Z][_a-zA-Z0-9]*"
|
||||
|
||||
prop_isVariableName1 = isVariableName "_fo123"
|
||||
prop_isVariableName2 = not $ isVariableName "4"
|
||||
prop_isVariableName3 = not $ isVariableName "test: "
|
||||
isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
|
||||
isVariableName _ = False
|
||||
|
||||
getVariablesFromLiteralToken token =
|
||||
getVariablesFromLiteral (fromJust $ getLiteralStringExt (const $ return " ") token)
|
||||
|
||||
-- Try to get referenced variables from a literal string like "$foo"
|
||||
-- Ignores tons of cases like arithmetic evaluation and array indices.
|
||||
prop_getVariablesFromLiteral1 =
|
||||
getVariablesFromLiteral "$foo${bar//a/b}$BAZ" == ["foo", "bar", "BAZ"]
|
||||
getVariablesFromLiteral string =
|
||||
map (!! 0) $ matchAllSubgroups variableRegex string
|
||||
where
|
||||
variableRegex = mkRegex "\\$\\{?([A-Za-z0-9_]+)"
|
||||
|
||||
-- Get the variable name from an expansion like ${var:-foo}
|
||||
prop_getBracedReference1 = getBracedReference "foo" == "foo"
|
||||
prop_getBracedReference2 = getBracedReference "#foo" == "foo"
|
||||
prop_getBracedReference3 = getBracedReference "#" == "#"
|
||||
prop_getBracedReference4 = getBracedReference "##" == "#"
|
||||
prop_getBracedReference5 = getBracedReference "#!" == "!"
|
||||
prop_getBracedReference6 = getBracedReference "!#" == "#"
|
||||
prop_getBracedReference7 = getBracedReference "!foo#?" == "foo"
|
||||
prop_getBracedReference8 = getBracedReference "foo-bar" == "foo"
|
||||
prop_getBracedReference9 = getBracedReference "foo:-bar" == "foo"
|
||||
prop_getBracedReference10= getBracedReference "foo: -1" == "foo"
|
||||
prop_getBracedReference11= getBracedReference "!os*" == ""
|
||||
prop_getBracedReference12= getBracedReference "!os?bar**" == ""
|
||||
prop_getBracedReference13= getBracedReference "foo[bar]" == "foo"
|
||||
getBracedReference s = fromMaybe s $
|
||||
nameExpansion s `mplus` takeName noPrefix `mplus` getSpecial noPrefix `mplus` getSpecial s
|
||||
where
|
||||
noPrefix = dropPrefix s
|
||||
dropPrefix (c:rest) = if c `elem` "!#" then rest else c:rest
|
||||
dropPrefix "" = ""
|
||||
takeName s = do
|
||||
let name = takeWhile isVariableChar s
|
||||
guard . not $ null name
|
||||
return name
|
||||
getSpecial (c:_) =
|
||||
if c `elem` "*@#?-$!" then return [c] else fail "not special"
|
||||
getSpecial _ = fail "empty"
|
||||
|
||||
nameExpansion ('!':rest) = do -- e.g. ${!foo*bar*}
|
||||
let suffix = dropWhile isVariableChar rest
|
||||
guard $ suffix /= rest -- e.g. ${!@}
|
||||
first <- suffix !!! 0
|
||||
guard $ first `elem` "*?"
|
||||
return ""
|
||||
nameExpansion _ = Nothing
|
||||
|
||||
prop_getBracedModifier1 = getBracedModifier "foo:bar:baz" == ":bar:baz"
|
||||
prop_getBracedModifier2 = getBracedModifier "!var:-foo" == ":-foo"
|
||||
prop_getBracedModifier3 = getBracedModifier "foo[bar]" == "[bar]"
|
||||
getBracedModifier s = fromMaybe "" . listToMaybe $ do
|
||||
let var = getBracedReference s
|
||||
a <- dropModifier s
|
||||
dropPrefix var a
|
||||
where
|
||||
dropPrefix [] t = return t
|
||||
dropPrefix (a:b) (c:d) | a == c = dropPrefix b d
|
||||
dropPrefix _ _ = []
|
||||
|
||||
dropModifier (c:rest) | c `elem` "#!" = [rest, c:rest]
|
||||
dropModifier x = [x]
|
||||
|
||||
-- Useful generic functions.
|
||||
|
||||
-- Run an action in a Maybe (or do nothing).
|
||||
-- Example:
|
||||
-- potentially $ do
|
||||
-- s <- getLiteralString cmd
|
||||
-- guard $ s `elem` ["--recursive", "-r"]
|
||||
-- return $ warn .. "Something something recursive"
|
||||
potentially :: Monad m => Maybe (m ()) -> m ()
|
||||
potentially = fromMaybe (return ())
|
||||
|
||||
-- Get element 0 or a default. Like `head` but safe.
|
||||
headOrDefault _ (a:_) = a
|
||||
headOrDefault def _ = def
|
||||
|
||||
--- Get element n of a list, or Nothing. Like `!!` but safe.
|
||||
(!!!) list i =
|
||||
case drop i list of
|
||||
[] -> Nothing
|
||||
(r:_) -> Just r
|
||||
|
||||
-- Run a command if the shell is in the given list
|
||||
whenShell l c = do
|
||||
shell <- asks shellType
|
||||
when (shell `elem` l ) c
|
||||
|
||||
|
||||
filterByAnnotation asSpec params =
|
||||
filter (not . shouldIgnore)
|
||||
where
|
||||
token = asScript asSpec
|
||||
idFor (TokenComment id _) = id
|
||||
shouldIgnore note =
|
||||
any (shouldIgnoreFor (getCode note)) $
|
||||
getPath parents (T_Bang $ idFor note)
|
||||
shouldIgnoreFor num (T_Annotation _ anns _) =
|
||||
any hasNum anns
|
||||
where
|
||||
hasNum (DisableComment ts) = num == ts
|
||||
hasNum _ = False
|
||||
shouldIgnoreFor _ T_Include {} = not $ asCheckSourced asSpec
|
||||
shouldIgnoreFor _ _ = False
|
||||
parents = parentMap params
|
||||
getCode (TokenComment _ (Comment _ c _)) = c
|
||||
|
||||
-- Is this a ${#anything}, to get string length or array count?
|
||||
isCountingReference (T_DollarBraced id token) =
|
||||
case concat $ oversimplify token of
|
||||
'#':_ -> True
|
||||
_ -> False
|
||||
isCountingReference _ = False
|
||||
|
||||
-- FIXME: doesn't handle ${a:+$var} vs ${a:+"$var"}
|
||||
isQuotedAlternativeReference t =
|
||||
case t of
|
||||
T_DollarBraced _ _ ->
|
||||
getBracedModifier (bracedString t) `matches` re
|
||||
_ -> False
|
||||
where
|
||||
re = mkRegex "(^|\\]):?\\+"
|
||||
|
||||
-- getOpts "erd:u:" will parse a SimpleCommand like
|
||||
-- read -re -d : -u 3 bar
|
||||
-- into
|
||||
-- Just [("r", -re), ("e", -re), ("d", :), ("u", 3), ("", bar)]
|
||||
-- where flags with arguments map to arguments, while others map to themselves.
|
||||
-- Any unrecognized flag will result in Nothing.
|
||||
getOpts :: String -> Token -> Maybe [(String, Token)]
|
||||
getOpts string cmd = process flags
|
||||
where
|
||||
flags = getAllFlags cmd
|
||||
flagList (c:':':rest) = ([c], True) : flagList rest
|
||||
flagList (c:rest) = ([c], False) : flagList rest
|
||||
flagList [] = []
|
||||
flagMap = Map.fromList $ ("", False) : flagList string
|
||||
|
||||
process [] = return []
|
||||
process [(token, flag)] = do
|
||||
takesArg <- Map.lookup flag flagMap
|
||||
guard $ not takesArg
|
||||
return [(flag, token)]
|
||||
process ((token1, flag1):rest2@((token2, flag2):rest)) = do
|
||||
takesArg <- Map.lookup flag1 flagMap
|
||||
if takesArg
|
||||
then do
|
||||
guard $ flag2 == ""
|
||||
more <- process rest
|
||||
return $ (flag1, token2) : more
|
||||
else do
|
||||
more <- process rest2
|
||||
return $ (flag1, token1) : more
|
||||
|
||||
return []
|
||||
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
198
src/ShellCheck/Checker.hs
Normal file
198
src/ShellCheck/Checker.hs
Normal file
|
@ -0,0 +1,198 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
module ShellCheck.Checker (checkScript, ShellCheck.Checker.runTests) where
|
||||
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.Parser
|
||||
import ShellCheck.Analyzer
|
||||
|
||||
import Data.Either
|
||||
import Data.Functor
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Ord
|
||||
import Control.Monad.Identity
|
||||
import qualified Data.Map as Map
|
||||
import qualified System.IO
|
||||
import Prelude hiding (readFile)
|
||||
import Control.Monad
|
||||
|
||||
import Test.QuickCheck.All
|
||||
|
||||
tokenToPosition map (TokenComment id c) = fromMaybe fail $ do
|
||||
position <- Map.lookup id map
|
||||
return $ PositionedComment position position c
|
||||
where
|
||||
fail = error "Internal shellcheck error: id doesn't exist. Please report!"
|
||||
|
||||
checkScript :: Monad m => SystemInterface m -> CheckSpec -> m CheckResult
|
||||
checkScript sys spec = do
|
||||
results <- checkScript (csScript spec)
|
||||
return CheckResult {
|
||||
crFilename = csFilename spec,
|
||||
crComments = results
|
||||
}
|
||||
where
|
||||
checkScript contents = do
|
||||
result <- parseScript sys ParseSpec {
|
||||
psFilename = csFilename spec,
|
||||
psScript = contents,
|
||||
psCheckSourced = csCheckSourced spec
|
||||
}
|
||||
let parseMessages = prComments result
|
||||
let analysisMessages =
|
||||
fromMaybe [] $
|
||||
(arComments . analyzeScript . analysisSpec)
|
||||
<$> prRoot result
|
||||
let translator = tokenToPosition (prTokenPositions result)
|
||||
return . nub . sortMessages . filter shouldInclude $
|
||||
(parseMessages ++ map translator analysisMessages)
|
||||
|
||||
shouldInclude (PositionedComment _ _ (Comment _ code _)) =
|
||||
code `notElem` csExcludedWarnings spec
|
||||
|
||||
sortMessages = sortBy (comparing order)
|
||||
order (PositionedComment pos _ (Comment severity code message)) =
|
||||
(posFile pos, posLine pos, posColumn pos, severity, code, message)
|
||||
getPosition (PositionedComment pos _ _) = pos
|
||||
|
||||
analysisSpec root =
|
||||
AnalysisSpec {
|
||||
asScript = root,
|
||||
asShellType = csShellTypeOverride spec,
|
||||
asCheckSourced = csCheckSourced spec,
|
||||
asExecutionMode = Executed
|
||||
}
|
||||
|
||||
getErrors sys spec =
|
||||
sort . map getCode . crComments $
|
||||
runIdentity (checkScript sys spec)
|
||||
where
|
||||
getCode (PositionedComment _ _ (Comment _ code _)) = code
|
||||
|
||||
check = checkWithIncludes []
|
||||
|
||||
checkWithSpec includes =
|
||||
getErrors (mockedSystemInterface includes)
|
||||
|
||||
checkWithIncludes includes src =
|
||||
checkWithSpec includes emptyCheckSpec {
|
||||
csScript = src,
|
||||
csExcludedWarnings = [2148]
|
||||
}
|
||||
|
||||
checkRecursive includes src =
|
||||
checkWithSpec includes emptyCheckSpec {
|
||||
csScript = src,
|
||||
csExcludedWarnings = [2148],
|
||||
csCheckSourced = True
|
||||
}
|
||||
|
||||
prop_findsParseIssue = check "echo \"$12\"" == [1037]
|
||||
|
||||
prop_commentDisablesParseIssue1 =
|
||||
null $ check "#shellcheck disable=SC1037\necho \"$12\""
|
||||
prop_commentDisablesParseIssue2 =
|
||||
null $ check "#shellcheck disable=SC1037\n#lol\necho \"$12\""
|
||||
|
||||
prop_findsAnalysisIssue =
|
||||
check "echo $1" == [2086]
|
||||
prop_commentDisablesAnalysisIssue1 =
|
||||
null $ check "#shellcheck disable=SC2086\necho $1"
|
||||
prop_commentDisablesAnalysisIssue2 =
|
||||
null $ check "#shellcheck disable=SC2086\n#lol\necho $1"
|
||||
|
||||
prop_optionDisablesIssue1 =
|
||||
null $ getErrors
|
||||
(mockedSystemInterface [])
|
||||
emptyCheckSpec {
|
||||
csScript = "echo $1",
|
||||
csExcludedWarnings = [2148, 2086]
|
||||
}
|
||||
|
||||
prop_optionDisablesIssue2 =
|
||||
null $ getErrors
|
||||
(mockedSystemInterface [])
|
||||
emptyCheckSpec {
|
||||
csScript = "echo \"$10\"",
|
||||
csExcludedWarnings = [2148, 1037]
|
||||
}
|
||||
|
||||
prop_canParseDevNull =
|
||||
[] == check "source /dev/null"
|
||||
|
||||
prop_failsWhenNotSourcing =
|
||||
[1091, 2154] == check "source lol; echo \"$bar\""
|
||||
|
||||
prop_worksWhenSourcing =
|
||||
null $ checkWithIncludes [("lib", "bar=1")] "source lib; echo \"$bar\""
|
||||
|
||||
prop_worksWhenDotting =
|
||||
null $ checkWithIncludes [("lib", "bar=1")] ". lib; echo \"$bar\""
|
||||
|
||||
prop_noInfiniteSourcing =
|
||||
[] == checkWithIncludes [("lib", "source lib")] "source lib"
|
||||
|
||||
prop_canSourceBadSyntax =
|
||||
[1094, 2086] == checkWithIncludes [("lib", "for f; do")] "source lib; echo $1"
|
||||
|
||||
prop_cantSourceDynamic =
|
||||
[1090] == checkWithIncludes [("lib", "")] ". \"$1\""
|
||||
|
||||
prop_cantSourceDynamic2 =
|
||||
[1090] == checkWithIncludes [("lib", "")] "source ~/foo"
|
||||
|
||||
prop_canSourceDynamicWhenRedirected =
|
||||
null $ checkWithIncludes [("lib", "")] "#shellcheck source=lib\n. \"$1\""
|
||||
|
||||
prop_recursiveAnalysis =
|
||||
[2086] == checkRecursive [("lib", "echo $1")] "source lib"
|
||||
|
||||
prop_recursiveParsing =
|
||||
[1037] == checkRecursive [("lib", "echo \"$10\"")] "source lib"
|
||||
|
||||
prop_sourceDirectiveDoesntFollowFile =
|
||||
null $ checkWithIncludes
|
||||
[("foo", "source bar"), ("bar", "baz=3")]
|
||||
"#shellcheck source=foo\n. \"$1\"; echo \"$baz\""
|
||||
|
||||
prop_filewideAnnotationBase = [2086] == check "#!/bin/sh\necho $1"
|
||||
prop_filewideAnnotation1 = null $
|
||||
check "#!/bin/sh\n# shellcheck disable=2086\necho $1"
|
||||
prop_filewideAnnotation2 = null $
|
||||
check "#!/bin/sh\n# shellcheck disable=2086\ntrue\necho $1"
|
||||
prop_filewideAnnotation3 = null $
|
||||
check "#!/bin/sh\n#unerlated\n# shellcheck disable=2086\ntrue\necho $1"
|
||||
prop_filewideAnnotation4 = null $
|
||||
check "#!/bin/sh\n# shellcheck disable=2086\n#unrelated\ntrue\necho $1"
|
||||
prop_filewideAnnotation5 = null $
|
||||
check "#!/bin/sh\n\n\n\n#shellcheck disable=2086\ntrue\necho $1"
|
||||
prop_filewideAnnotation6 = null $
|
||||
check "#shellcheck shell=sh\n#unrelated\n#shellcheck disable=2086\ntrue\necho $1"
|
||||
prop_filewideAnnotation7 = null $
|
||||
check "#!/bin/sh\n# shellcheck disable=2086\n#unrelated\ntrue\necho $1"
|
||||
|
||||
prop_filewideAnnotationBase2 = [2086, 2181] == check "true\n[ $? == 0 ] && echo $1"
|
||||
prop_filewideAnnotation8 = null $
|
||||
check "# Disable $? warning\n#shellcheck disable=SC2181\n# Disable quoting warning\n#shellcheck disable=2086\ntrue\n[ $? == 0 ] && echo $1"
|
||||
|
||||
return []
|
||||
runTests = $quickCheckAll
|
948
src/ShellCheck/Checks/Commands.hs
Normal file
948
src/ShellCheck/Checks/Commands.hs
Normal file
|
@ -0,0 +1,948 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
|
||||
-- This module contains checks that examine specific commands by name.
|
||||
module ShellCheck.Checks.Commands (checker
|
||||
, ShellCheck.Checks.Commands.runTests
|
||||
) where
|
||||
|
||||
import ShellCheck.AST
|
||||
import ShellCheck.ASTLib
|
||||
import ShellCheck.AnalyzerLib
|
||||
import ShellCheck.Data
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.Parser
|
||||
import ShellCheck.Regex
|
||||
|
||||
import Control.Monad
|
||||
import Control.Monad.RWS
|
||||
import Data.Char
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Test.QuickCheck.All (forAllProperties)
|
||||
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
|
||||
|
||||
data CommandName = Exactly String | Basename String
|
||||
deriving (Eq, Ord)
|
||||
|
||||
data CommandCheck =
|
||||
CommandCheck CommandName (Token -> Analysis)
|
||||
|
||||
|
||||
verify :: CommandCheck -> String -> Bool
|
||||
verify f s = producesComments (getChecker [f]) s == Just True
|
||||
verifyNot f s = producesComments (getChecker [f]) s == Just False
|
||||
|
||||
arguments (T_SimpleCommand _ _ (cmd:args)) = args
|
||||
|
||||
commandChecks :: [CommandCheck]
|
||||
commandChecks = [
|
||||
checkTr
|
||||
,checkFindNameGlob
|
||||
,checkNeedlessExpr
|
||||
,checkGrepRe
|
||||
,checkTrapQuotes
|
||||
,checkReturn
|
||||
,checkFindExecWithSingleArgument
|
||||
,checkUnusedEchoEscapes
|
||||
,checkInjectableFindSh
|
||||
,checkFindActionPrecedence
|
||||
,checkMkdirDashPM
|
||||
,checkNonportableSignals
|
||||
,checkInteractiveSu
|
||||
,checkSshCommandString
|
||||
,checkPrintfVar
|
||||
,checkUuoeCmd
|
||||
,checkSetAssignment
|
||||
,checkExportedExpansions
|
||||
,checkAliasesUsesArgs
|
||||
,checkAliasesExpandEarly
|
||||
,checkUnsetGlobs
|
||||
,checkFindWithoutPath
|
||||
,checkTimeParameters
|
||||
,checkTimedCommand
|
||||
,checkLocalScope
|
||||
,checkDeprecatedTempfile
|
||||
,checkDeprecatedEgrep
|
||||
,checkDeprecatedFgrep
|
||||
,checkWhileGetoptsCase
|
||||
,checkCatastrophicRm
|
||||
,checkLetUsage
|
||||
,checkMvArguments, checkCpArguments, checkLnArguments
|
||||
,checkFindRedirections
|
||||
,checkReadExpansions
|
||||
,checkWhich
|
||||
]
|
||||
|
||||
buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis)
|
||||
buildCommandMap = foldl' addCheck Map.empty
|
||||
where
|
||||
addCheck map (CommandCheck name function) =
|
||||
Map.insertWith composeAnalyzers name function map
|
||||
|
||||
|
||||
checkCommand :: Map.Map CommandName (Token -> Analysis) -> Token -> Analysis
|
||||
checkCommand map t@(T_SimpleCommand id _ (cmd:rest)) = fromMaybe (return ()) $ do
|
||||
name <- getLiteralString cmd
|
||||
return $
|
||||
if '/' `elem` name
|
||||
then
|
||||
Map.findWithDefault nullCheck (Basename $ basename name) map t
|
||||
else do
|
||||
Map.findWithDefault nullCheck (Exactly name) map t
|
||||
Map.findWithDefault nullCheck (Basename name) map t
|
||||
|
||||
where
|
||||
basename = reverse . takeWhile (/= '/') . reverse
|
||||
checkCommand _ _ = return ()
|
||||
|
||||
getChecker :: [CommandCheck] -> Checker
|
||||
getChecker list = Checker {
|
||||
perScript = const $ return (),
|
||||
perToken = checkCommand map
|
||||
}
|
||||
where
|
||||
map = buildCommandMap list
|
||||
|
||||
|
||||
checker :: Parameters -> Checker
|
||||
checker params = getChecker commandChecks
|
||||
|
||||
prop_checkTr1 = verify checkTr "tr [a-f] [A-F]"
|
||||
prop_checkTr2 = verify checkTr "tr 'a-z' 'A-Z'"
|
||||
prop_checkTr2a= verify checkTr "tr '[a-z]' '[A-Z]'"
|
||||
prop_checkTr3 = verifyNot checkTr "tr -d '[:lower:]'"
|
||||
prop_checkTr3a= verifyNot checkTr "tr -d '[:upper:]'"
|
||||
prop_checkTr3b= verifyNot checkTr "tr -d '|/_[:upper:]'"
|
||||
prop_checkTr4 = verifyNot checkTr "ls [a-z]"
|
||||
prop_checkTr5 = verify checkTr "tr foo bar"
|
||||
prop_checkTr6 = verify checkTr "tr 'hello' 'world'"
|
||||
prop_checkTr8 = verifyNot checkTr "tr aeiou _____"
|
||||
prop_checkTr9 = verifyNot checkTr "a-z n-za-m"
|
||||
prop_checkTr10= verifyNot checkTr "tr --squeeze-repeats rl lr"
|
||||
prop_checkTr11= verifyNot checkTr "tr abc '[d*]'"
|
||||
checkTr = CommandCheck (Basename "tr") (mapM_ f . arguments)
|
||||
where
|
||||
f w | isGlob w = -- The user will go [ab] -> '[ab]' -> 'ab'. Fixme?
|
||||
warn (getId w) 2060 "Quote parameters to tr to prevent glob expansion."
|
||||
f word =
|
||||
case getLiteralString word of
|
||||
Just "a-z" -> info (getId word) 2018 "Use '[:lower:]' to support accents and foreign alphabets."
|
||||
Just "A-Z" -> info (getId word) 2019 "Use '[:upper:]' to support accents and foreign alphabets."
|
||||
Just s -> do -- Eliminate false positives by only looking for dupes in SET2?
|
||||
when (not ("-" `isPrefixOf` s || "[:" `isInfixOf` s) && duplicated s) $
|
||||
info (getId word) 2020 "tr replaces sets of chars, not words (mentioned due to duplicates)."
|
||||
unless ("[:" `isPrefixOf` s) $
|
||||
when ("[" `isPrefixOf` s && "]" `isSuffixOf` s && (length s > 2) && ('*' `notElem` s)) $
|
||||
info (getId word) 2021 "Don't use [] around classes in tr, it replaces literal square brackets."
|
||||
Nothing -> return ()
|
||||
|
||||
duplicated s =
|
||||
let relevant = filter isAlpha s
|
||||
in relevant /= nub relevant
|
||||
|
||||
prop_checkFindNameGlob1 = verify checkFindNameGlob "find / -name *.php"
|
||||
prop_checkFindNameGlob2 = verify checkFindNameGlob "find / -type f -ipath *(foo)"
|
||||
prop_checkFindNameGlob3 = verifyNot checkFindNameGlob "find * -name '*.php'"
|
||||
checkFindNameGlob = CommandCheck (Basename "find") (f . arguments) where
|
||||
acceptsGlob (Just s) = s `elem` [ "-ilname", "-iname", "-ipath", "-iregex", "-iwholename", "-lname", "-name", "-path", "-regex", "-wholename" ]
|
||||
acceptsGlob _ = False
|
||||
f [] = return ()
|
||||
f [x] = return ()
|
||||
f (a:b:r) = do
|
||||
when (acceptsGlob (getLiteralString a) && isGlob b) $ do
|
||||
let (Just s) = getLiteralString a
|
||||
warn (getId b) 2061 $ "Quote the parameter to " ++ s ++ " so the shell won't interpret it."
|
||||
f (b:r)
|
||||
|
||||
|
||||
prop_checkNeedlessExpr = verify checkNeedlessExpr "foo=$(expr 3 + 2)"
|
||||
prop_checkNeedlessExpr2 = verify checkNeedlessExpr "foo=`echo \\`expr 3 + 2\\``"
|
||||
prop_checkNeedlessExpr3 = verifyNot checkNeedlessExpr "foo=$(expr foo : regex)"
|
||||
prop_checkNeedlessExpr4 = verifyNot checkNeedlessExpr "foo=$(expr foo \\< regex)"
|
||||
checkNeedlessExpr = CommandCheck (Basename "expr") f where
|
||||
f t =
|
||||
when (all (`notElem` exceptions) (words $ arguments t)) $
|
||||
style (getId t) 2003
|
||||
"expr is antiquated. Consider rewriting this using $((..)), ${} or [[ ]]."
|
||||
-- These operators are hard to replicate in POSIX
|
||||
exceptions = [ ":", "<", ">", "<=", ">=" ]
|
||||
words = mapMaybe getLiteralString
|
||||
|
||||
|
||||
prop_checkGrepRe1 = verify checkGrepRe "cat foo | grep *.mp3"
|
||||
prop_checkGrepRe2 = verify checkGrepRe "grep -Ev cow*test *.mp3"
|
||||
prop_checkGrepRe3 = verify checkGrepRe "grep --regex=*.mp3 file"
|
||||
prop_checkGrepRe4 = verifyNot checkGrepRe "grep foo *.mp3"
|
||||
prop_checkGrepRe5 = verifyNot checkGrepRe "grep-v --regex=moo *"
|
||||
prop_checkGrepRe6 = verifyNot checkGrepRe "grep foo \\*.mp3"
|
||||
prop_checkGrepRe7 = verify checkGrepRe "grep *foo* file"
|
||||
prop_checkGrepRe8 = verify checkGrepRe "ls | grep foo*.jpg"
|
||||
prop_checkGrepRe9 = verifyNot checkGrepRe "grep '[0-9]*' file"
|
||||
prop_checkGrepRe10= verifyNot checkGrepRe "grep '^aa*' file"
|
||||
prop_checkGrepRe11= verifyNot checkGrepRe "grep --include=*.png foo"
|
||||
prop_checkGrepRe12= verifyNot checkGrepRe "grep -F 'Foo*' file"
|
||||
prop_checkGrepRe13= verifyNot checkGrepRe "grep -- -foo bar*"
|
||||
prop_checkGrepRe14= verifyNot checkGrepRe "grep -e -foo bar*"
|
||||
prop_checkGrepRe15= verifyNot checkGrepRe "grep --regex -foo bar*"
|
||||
|
||||
checkGrepRe = CommandCheck (Basename "grep") check where
|
||||
check cmd = f cmd (arguments cmd)
|
||||
-- --regex=*(extglob) doesn't work. Fixme?
|
||||
skippable (Just s) = not ("--regex=" `isPrefixOf` s) && "-" `isPrefixOf` s
|
||||
skippable _ = False
|
||||
f _ [] = return ()
|
||||
f cmd (x:r) =
|
||||
let str = getLiteralStringExt (const $ return "_") x
|
||||
in
|
||||
if str `elem` [Just "--", Just "-e", Just "--regex"]
|
||||
then checkRE cmd r -- Regex is *after* this
|
||||
else
|
||||
if skippable str
|
||||
then f cmd r -- Regex is elsewhere
|
||||
else checkRE cmd (x:r) -- Regex is this
|
||||
|
||||
checkRE _ [] = return ()
|
||||
checkRE cmd (re:_) = do
|
||||
when (isGlob re) $
|
||||
warn (getId re) 2062 "Quote the grep pattern so the shell won't interpret it."
|
||||
|
||||
unless (cmd `hasFlag` "F") $ do
|
||||
let string = concat $ oversimplify re
|
||||
if isConfusedGlobRegex string then
|
||||
warn (getId re) 2063 "Grep uses regex, but this looks like a glob."
|
||||
else potentially $ do
|
||||
char <- getSuspiciousRegexWildcard string
|
||||
return $ info (getId re) 2022 $
|
||||
"Note that unlike globs, " ++ [char] ++ "* here matches '" ++ [char, char, char] ++ "' but not '" ++ wordStartingWith char ++ "'."
|
||||
|
||||
wordStartingWith c =
|
||||
head . filter ([c] `isPrefixOf`) $ candidates
|
||||
where
|
||||
candidates =
|
||||
sampleWords ++ map (\(x:r) -> toUpper x : r) sampleWords ++ [c:"test"]
|
||||
|
||||
getSuspiciousRegexWildcard str =
|
||||
if not $ str `matches` contra
|
||||
then do
|
||||
match <- matchRegex suspicious str
|
||||
str <- match !!! 0
|
||||
str !!! 0
|
||||
else
|
||||
fail "looks good"
|
||||
where
|
||||
suspicious = mkRegex "([A-Za-z1-9])\\*"
|
||||
contra = mkRegex "[^a-zA-Z1-9]\\*|[][^$+\\\\]"
|
||||
|
||||
|
||||
prop_checkTrapQuotes1 = verify checkTrapQuotes "trap \"echo $num\" INT"
|
||||
prop_checkTrapQuotes1a= verify checkTrapQuotes "trap \"echo `ls`\" INT"
|
||||
prop_checkTrapQuotes2 = verifyNot checkTrapQuotes "trap 'echo $num' INT"
|
||||
prop_checkTrapQuotes3 = verify checkTrapQuotes "trap \"echo $((1+num))\" EXIT DEBUG"
|
||||
checkTrapQuotes = CommandCheck (Exactly "trap") (f . arguments) where
|
||||
f (x:_) = checkTrap x
|
||||
f _ = return ()
|
||||
checkTrap (T_NormalWord _ [T_DoubleQuoted _ rs]) = mapM_ checkExpansions rs
|
||||
checkTrap _ = return ()
|
||||
warning id = warn id 2064 "Use single quotes, otherwise this expands now rather than when signalled."
|
||||
checkExpansions (T_DollarExpansion id _) = warning id
|
||||
checkExpansions (T_Backticked id _) = warning id
|
||||
checkExpansions (T_DollarBraced id _) = warning id
|
||||
checkExpansions (T_DollarArithmetic id _) = warning id
|
||||
checkExpansions _ = return ()
|
||||
|
||||
|
||||
prop_checkReturn1 = verifyNot checkReturn "return"
|
||||
prop_checkReturn2 = verifyNot checkReturn "return 1"
|
||||
prop_checkReturn3 = verifyNot checkReturn "return $var"
|
||||
prop_checkReturn4 = verifyNot checkReturn "return $((a|b))"
|
||||
prop_checkReturn5 = verify checkReturn "return -1"
|
||||
prop_checkReturn6 = verify checkReturn "return 1000"
|
||||
prop_checkReturn7 = verify checkReturn "return 'hello world'"
|
||||
checkReturn = CommandCheck (Exactly "return") (f . arguments)
|
||||
where
|
||||
f (first:second:_) =
|
||||
err (getId second) 2151
|
||||
"Only one integer 0-255 can be returned. Use stdout for other data."
|
||||
f [value] =
|
||||
when (isInvalid $ literal value) $
|
||||
err (getId value) 2152
|
||||
"Can only return 0-255. Other data should be written to stdout."
|
||||
f _ = return ()
|
||||
|
||||
isInvalid s = s == "" || any (not . isDigit) s || length s > 5
|
||||
|| let value = (read s :: Integer) in value > 255
|
||||
|
||||
literal token = fromJust $ getLiteralStringExt lit token
|
||||
lit (T_DollarBraced {}) = return "0"
|
||||
lit (T_DollarArithmetic {}) = return "0"
|
||||
lit (T_DollarExpansion {}) = return "0"
|
||||
lit (T_Backticked {}) = return "0"
|
||||
lit _ = return "WTF"
|
||||
|
||||
|
||||
prop_checkFindExecWithSingleArgument1 = verify checkFindExecWithSingleArgument "find . -exec 'cat {} | wc -l' \\;"
|
||||
prop_checkFindExecWithSingleArgument2 = verify checkFindExecWithSingleArgument "find . -execdir 'cat {} | wc -l' +"
|
||||
prop_checkFindExecWithSingleArgument3 = verifyNot checkFindExecWithSingleArgument "find . -exec wc -l {} \\;"
|
||||
checkFindExecWithSingleArgument = CommandCheck (Basename "find") (f . arguments)
|
||||
where
|
||||
f = void . sequence . mapMaybe check . tails
|
||||
check (exec:arg:term:_) = do
|
||||
execS <- getLiteralString exec
|
||||
termS <- getLiteralString term
|
||||
cmdS <- getLiteralStringExt (const $ return " ") arg
|
||||
|
||||
guard $ execS `elem` ["-exec", "-execdir"] && termS `elem` [";", "+"]
|
||||
guard $ cmdS `matches` commandRegex
|
||||
return $ warn (getId exec) 2150 "-exec does not invoke a shell. Rewrite or use -exec sh -c .. ."
|
||||
check _ = Nothing
|
||||
commandRegex = mkRegex "[ |;]"
|
||||
|
||||
|
||||
prop_checkUnusedEchoEscapes1 = verify checkUnusedEchoEscapes "echo 'foo\\nbar\\n'"
|
||||
prop_checkUnusedEchoEscapes2 = verifyNot checkUnusedEchoEscapes "echo -e 'foi\\nbar'"
|
||||
prop_checkUnusedEchoEscapes3 = verify checkUnusedEchoEscapes "echo \"n:\\t42\""
|
||||
prop_checkUnusedEchoEscapes4 = verifyNot checkUnusedEchoEscapes "echo lol"
|
||||
prop_checkUnusedEchoEscapes5 = verifyNot checkUnusedEchoEscapes "echo -n -e '\n'"
|
||||
checkUnusedEchoEscapes = CommandCheck (Basename "echo") (f . arguments)
|
||||
where
|
||||
isDashE = mkRegex "^-.*e"
|
||||
hasEscapes = mkRegex "\\\\[rnt]"
|
||||
f args | concat (concatMap oversimplify allButLast) `matches` isDashE =
|
||||
return ()
|
||||
where allButLast = reverse . drop 1 . reverse $ args
|
||||
f args = mapM_ checkEscapes args
|
||||
|
||||
checkEscapes (T_NormalWord _ args) =
|
||||
mapM_ checkEscapes args
|
||||
checkEscapes (T_DoubleQuoted id args) =
|
||||
mapM_ checkEscapes args
|
||||
checkEscapes (T_Literal id str) = examine id str
|
||||
checkEscapes (T_SingleQuoted id str) = examine id str
|
||||
checkEscapes _ = return ()
|
||||
|
||||
examine id str =
|
||||
when (str `matches` hasEscapes) $
|
||||
info id 2028 "echo won't expand escape sequences. Consider printf."
|
||||
|
||||
|
||||
prop_checkInjectableFindSh1 = verify checkInjectableFindSh "find . -exec sh -c 'echo {}' \\;"
|
||||
prop_checkInjectableFindSh2 = verify checkInjectableFindSh "find . -execdir bash -c 'rm \"{}\"' ';'"
|
||||
prop_checkInjectableFindSh3 = verifyNot checkInjectableFindSh "find . -exec sh -c 'rm \"$@\"' _ {} \\;"
|
||||
checkInjectableFindSh = CommandCheck (Basename "find") (check . arguments)
|
||||
where
|
||||
check args = do
|
||||
let idStrings = map (\x -> (getId x, onlyLiteralString x)) args
|
||||
match pattern idStrings
|
||||
|
||||
match _ [] = return ()
|
||||
match [] (next:_) = action next
|
||||
match (p:tests) ((id, arg):args) = do
|
||||
when (p arg) $ match tests args
|
||||
match (p:tests) args
|
||||
|
||||
pattern = [
|
||||
(`elem` ["-exec", "-execdir"]),
|
||||
(`elem` ["sh", "bash", "dash", "ksh"]),
|
||||
(== "-c")
|
||||
]
|
||||
action (id, arg) =
|
||||
when ("{}" `isInfixOf` arg) $
|
||||
warn id 2156 "Injecting filenames is fragile and insecure. Use parameters."
|
||||
|
||||
|
||||
prop_checkFindActionPrecedence1 = verify checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au' -exec rm {} +"
|
||||
prop_checkFindActionPrecedence2 = verifyNot checkFindActionPrecedence "find . -name '*.wav' -o \\( -name '*.au' -exec rm {} + \\)"
|
||||
prop_checkFindActionPrecedence3 = verifyNot checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au'"
|
||||
checkFindActionPrecedence = CommandCheck (Basename "find") (f . arguments)
|
||||
where
|
||||
pattern = [isMatch, const True, isParam ["-o", "-or"], isMatch, const True, isAction]
|
||||
f list | length list < length pattern = return ()
|
||||
f list@(_:rest) =
|
||||
if and (zipWith ($) pattern list)
|
||||
then warnFor (list !! (length pattern - 1))
|
||||
else f rest
|
||||
isMatch = isParam [ "-name", "-regex", "-iname", "-iregex", "-wholename", "-iwholename" ]
|
||||
isAction = isParam [ "-exec", "-execdir", "-delete", "-print", "-print0", "-fls", "-fprint", "-fprint0", "-fprintf", "-ls", "-ok", "-okdir", "-printf" ]
|
||||
isParam strs t = fromMaybe False $ do
|
||||
param <- getLiteralString t
|
||||
return $ param `elem` strs
|
||||
warnFor t = warn (getId t) 2146 "This action ignores everything before the -o. Use \\( \\) to group."
|
||||
|
||||
|
||||
prop_checkMkdirDashPM0 = verify checkMkdirDashPM "mkdir -p -m 0755 a/b"
|
||||
prop_checkMkdirDashPM1 = verify checkMkdirDashPM "mkdir -pm 0755 $dir"
|
||||
prop_checkMkdirDashPM2 = verify checkMkdirDashPM "mkdir -vpm 0755 a/b"
|
||||
prop_checkMkdirDashPM3 = verify checkMkdirDashPM "mkdir -pm 0755 -v a/b"
|
||||
prop_checkMkdirDashPM4 = verify checkMkdirDashPM "mkdir --parents --mode=0755 a/b"
|
||||
prop_checkMkdirDashPM5 = verify checkMkdirDashPM "mkdir --parents --mode 0755 a/b"
|
||||
prop_checkMkdirDashPM6 = verify checkMkdirDashPM "mkdir -p --mode=0755 a/b"
|
||||
prop_checkMkdirDashPM7 = verify checkMkdirDashPM "mkdir --parents -m 0755 a/b"
|
||||
prop_checkMkdirDashPM8 = verifyNot checkMkdirDashPM "mkdir -p a/b"
|
||||
prop_checkMkdirDashPM9 = verifyNot checkMkdirDashPM "mkdir -m 0755 a/b"
|
||||
prop_checkMkdirDashPM10 = verifyNot checkMkdirDashPM "mkdir a/b"
|
||||
prop_checkMkdirDashPM11 = verifyNot checkMkdirDashPM "mkdir --parents a/b"
|
||||
prop_checkMkdirDashPM12 = verifyNot checkMkdirDashPM "mkdir --mode=0755 a/b"
|
||||
prop_checkMkdirDashPM13 = verifyNot checkMkdirDashPM "mkdir_func -pm 0755 a/b"
|
||||
prop_checkMkdirDashPM14 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 singlelevel"
|
||||
prop_checkMkdirDashPM15 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../bin"
|
||||
prop_checkMkdirDashPM16 = verify checkMkdirDashPM "mkdir -p -m 0755 ../bin/laden"
|
||||
prop_checkMkdirDashPM17 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./bin"
|
||||
prop_checkMkdirDashPM18 = verify checkMkdirDashPM "mkdir -p -m 0755 ./bin/laden"
|
||||
prop_checkMkdirDashPM19 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./../bin"
|
||||
prop_checkMkdirDashPM20 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 .././bin"
|
||||
prop_checkMkdirDashPM21 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../../bin"
|
||||
checkMkdirDashPM = CommandCheck (Basename "mkdir") check
|
||||
where
|
||||
check t = potentially $ do
|
||||
let flags = getAllFlags t
|
||||
dashP <- find ((\f -> f == "p" || f == "parents") . snd) flags
|
||||
dashM <- find ((\f -> f == "m" || f == "mode") . snd) flags
|
||||
-- mkdir -pm 0700 dir is fine, so is ../dir, but dir/subdir is not.
|
||||
guard $ any couldHaveSubdirs (drop 1 $ arguments t)
|
||||
return $ warn (getId $ fst dashM) 2174 "When used with -p, -m only applies to the deepest directory."
|
||||
couldHaveSubdirs t = fromMaybe True $ do
|
||||
name <- getLiteralString t
|
||||
return $ '/' `elem` name && not (name `matches` re)
|
||||
re = mkRegex "^(\\.\\.?\\/)+[^/]+$"
|
||||
|
||||
|
||||
prop_checkNonportableSignals1 = verify checkNonportableSignals "trap f 8"
|
||||
prop_checkNonportableSignals2 = verifyNot checkNonportableSignals "trap f 0"
|
||||
prop_checkNonportableSignals3 = verifyNot checkNonportableSignals "trap f 14"
|
||||
prop_checkNonportableSignals4 = verify checkNonportableSignals "trap f SIGKILL"
|
||||
prop_checkNonportableSignals5 = verify checkNonportableSignals "trap f 9"
|
||||
prop_checkNonportableSignals6 = verify checkNonportableSignals "trap f stop"
|
||||
prop_checkNonportableSignals7 = verifyNot checkNonportableSignals "trap 'stop' int"
|
||||
checkNonportableSignals = CommandCheck (Exactly "trap") (f . arguments)
|
||||
where
|
||||
f args = case args of
|
||||
first:rest -> unless (isFlag first) $ mapM_ check rest
|
||||
_ -> return ()
|
||||
|
||||
check param = potentially $ do
|
||||
str <- getLiteralString param
|
||||
let id = getId param
|
||||
return $ sequence_ $ mapMaybe (\f -> f id str) [
|
||||
checkNumeric,
|
||||
checkUntrappable
|
||||
]
|
||||
|
||||
checkNumeric id str = do
|
||||
guard $ not (null str)
|
||||
guard $ all isDigit str
|
||||
guard $ str /= "0" -- POSIX exit trap
|
||||
guard $ str `notElem` ["1", "2", "3", "6", "9", "14", "15" ] -- XSI
|
||||
return $ warn id 2172
|
||||
"Trapping signals by number is not well defined. Prefer signal names."
|
||||
|
||||
checkUntrappable id str = do
|
||||
guard $ map toLower str `elem` ["kill", "9", "sigkill", "stop", "sigstop"]
|
||||
return $ err id 2173
|
||||
"SIGKILL/SIGSTOP can not be trapped."
|
||||
|
||||
|
||||
prop_checkInteractiveSu1 = verify checkInteractiveSu "su; rm file; su $USER"
|
||||
prop_checkInteractiveSu2 = verify checkInteractiveSu "su foo; something; exit"
|
||||
prop_checkInteractiveSu3 = verifyNot checkInteractiveSu "echo rm | su foo"
|
||||
prop_checkInteractiveSu4 = verifyNot checkInteractiveSu "su root < script"
|
||||
checkInteractiveSu = CommandCheck (Basename "su") f
|
||||
where
|
||||
f cmd = when (length (arguments cmd) <= 1) $ do
|
||||
path <- pathTo cmd
|
||||
when (all undirected path) $
|
||||
info (getId cmd) 2117
|
||||
"To run commands as another user, use su -c or sudo."
|
||||
|
||||
undirected (T_Pipeline _ _ l) = length l <= 1
|
||||
-- This should really just be modifications to stdin, but meh
|
||||
undirected (T_Redirecting _ list _) = null list
|
||||
undirected _ = True
|
||||
|
||||
|
||||
-- This is hard to get right without properly parsing ssh args
|
||||
prop_checkSshCmdStr1 = verify checkSshCommandString "ssh host \"echo $PS1\""
|
||||
prop_checkSshCmdStr2 = verifyNot checkSshCommandString "ssh host \"ls foo\""
|
||||
prop_checkSshCmdStr3 = verifyNot checkSshCommandString "ssh \"$host\""
|
||||
prop_checkSshCmdStr4 = verifyNot checkSshCommandString "ssh -i key \"$host\""
|
||||
checkSshCommandString = CommandCheck (Basename "ssh") (f . arguments)
|
||||
where
|
||||
isOption x = "-" `isPrefixOf` (concat $ oversimplify x)
|
||||
f args =
|
||||
case partition isOption args of
|
||||
([], hostport:r@(_:_)) -> checkArg $ last r
|
||||
_ -> return ()
|
||||
checkArg (T_NormalWord _ [T_DoubleQuoted id parts]) =
|
||||
case filter (not . isConstant) parts of
|
||||
[] -> return ()
|
||||
(x:_) -> info (getId x) 2029
|
||||
"Note that, unescaped, this expands on the client side."
|
||||
checkArg _ = return ()
|
||||
|
||||
|
||||
prop_checkPrintfVar1 = verify checkPrintfVar "printf \"Lol: $s\""
|
||||
prop_checkPrintfVar2 = verifyNot checkPrintfVar "printf 'Lol: $s'"
|
||||
prop_checkPrintfVar3 = verify checkPrintfVar "printf -v cow $(cmd)"
|
||||
prop_checkPrintfVar4 = verifyNot checkPrintfVar "printf \"%${count}s\" var"
|
||||
prop_checkPrintfVar5 = verify checkPrintfVar "printf '%s %s %s' foo bar"
|
||||
prop_checkPrintfVar6 = verify checkPrintfVar "printf foo bar baz"
|
||||
prop_checkPrintfVar7 = verify checkPrintfVar "printf -- foo bar baz"
|
||||
prop_checkPrintfVar8 = verifyNot checkPrintfVar "printf '%s %s %s' \"${var[@]}\""
|
||||
prop_checkPrintfVar9 = verifyNot checkPrintfVar "printf '%s %s %s\\n' *.png"
|
||||
prop_checkPrintfVar10= verifyNot checkPrintfVar "printf '%s %s %s' foo bar baz"
|
||||
prop_checkPrintfVar11= verifyNot checkPrintfVar "printf '%(%s%s)T' -1"
|
||||
checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
|
||||
f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest
|
||||
f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest
|
||||
f (format:params) = check format params
|
||||
f _ = return ()
|
||||
|
||||
countFormats string =
|
||||
case string of
|
||||
'%':'%':rest -> countFormats rest
|
||||
'%':'(':rest -> 1 + countFormats (dropWhile (/= ')') rest)
|
||||
'%':rest -> 1 + countFormats rest
|
||||
_:rest -> countFormats rest
|
||||
[] -> 0
|
||||
|
||||
check format more = do
|
||||
fromMaybe (return ()) $ do
|
||||
string <- getLiteralString format
|
||||
let vars = countFormats string
|
||||
|
||||
return $ do
|
||||
when (vars == 0 && more /= []) $
|
||||
err (getId format) 2182
|
||||
"This printf format string has no variables. Other arguments are ignored."
|
||||
|
||||
when (vars > 0
|
||||
&& length more < vars
|
||||
&& all (not . mayBecomeMultipleArgs) more) $
|
||||
warn (getId format) 2183 $
|
||||
"This format string has " ++ show vars ++ " variables, but is passed " ++ show (length more) ++ " arguments."
|
||||
|
||||
|
||||
unless ('%' `elem` concat (oversimplify format) || isLiteral format) $
|
||||
info (getId format) 2059
|
||||
"Don't use variables in the printf format string. Use printf \"..%s..\" \"$foo\"."
|
||||
|
||||
|
||||
|
||||
|
||||
prop_checkUuoeCmd1 = verify checkUuoeCmd "echo $(date)"
|
||||
prop_checkUuoeCmd2 = verify checkUuoeCmd "echo `date`"
|
||||
prop_checkUuoeCmd3 = verify checkUuoeCmd "echo \"$(date)\""
|
||||
prop_checkUuoeCmd4 = verify checkUuoeCmd "echo \"`date`\""
|
||||
prop_checkUuoeCmd5 = verifyNot checkUuoeCmd "echo \"The time is $(date)\""
|
||||
prop_checkUuoeCmd6 = verifyNot checkUuoeCmd "echo \"$(<file)\""
|
||||
checkUuoeCmd = CommandCheck (Exactly "echo") (f . arguments) where
|
||||
msg id = style id 2005 "Useless echo? Instead of 'echo $(cmd)', just use 'cmd'."
|
||||
f [token] = when (tokenIsJustCommandOutput token) $ msg (getId token)
|
||||
f _ = return ()
|
||||
|
||||
|
||||
prop_checkSetAssignment1 = verify checkSetAssignment "set foo 42"
|
||||
prop_checkSetAssignment2 = verify checkSetAssignment "set foo = 42"
|
||||
prop_checkSetAssignment3 = verify checkSetAssignment "set foo=42"
|
||||
prop_checkSetAssignment4 = verifyNot checkSetAssignment "set -- if=/dev/null"
|
||||
prop_checkSetAssignment5 = verifyNot checkSetAssignment "set 'a=5'"
|
||||
prop_checkSetAssignment6 = verifyNot checkSetAssignment "set"
|
||||
checkSetAssignment = CommandCheck (Exactly "set") (f . arguments)
|
||||
where
|
||||
f (var:value:rest) =
|
||||
let str = literal var in
|
||||
when (isVariableName str || isAssignment str) $
|
||||
msg (getId var)
|
||||
f (var:_) =
|
||||
when (isAssignment $ literal var) $
|
||||
msg (getId var)
|
||||
f _ = return ()
|
||||
|
||||
msg id = warn id 2121 "To assign a variable, use just 'var=value', no 'set ..'."
|
||||
|
||||
isAssignment str = '=' `elem` str
|
||||
literal (T_NormalWord _ l) = concatMap literal l
|
||||
literal (T_Literal _ str) = str
|
||||
literal _ = "*"
|
||||
|
||||
|
||||
prop_checkExportedExpansions1 = verify checkExportedExpansions "export $foo"
|
||||
prop_checkExportedExpansions2 = verify checkExportedExpansions "export \"$foo\""
|
||||
prop_checkExportedExpansions3 = verifyNot checkExportedExpansions "export foo"
|
||||
prop_checkExportedExpansions4 = verifyNot checkExportedExpansions "export ${foo?}"
|
||||
checkExportedExpansions = CommandCheck (Exactly "export") (mapM_ check . arguments)
|
||||
where
|
||||
check t = potentially $ do
|
||||
var <- getSingleUnmodifiedVariable t
|
||||
let name = bracedString var
|
||||
return . warn (getId t) 2163 $
|
||||
"This does not export '" ++ name ++ "'. Remove $/${} for that, or use ${var?} to quiet."
|
||||
|
||||
prop_checkReadExpansions1 = verify checkReadExpansions "read $var"
|
||||
prop_checkReadExpansions2 = verify checkReadExpansions "read -r $var"
|
||||
prop_checkReadExpansions3 = verifyNot checkReadExpansions "read -p $var"
|
||||
prop_checkReadExpansions4 = verifyNot checkReadExpansions "read -rd $delim name"
|
||||
prop_checkReadExpansions5 = verify checkReadExpansions "read \"$var\""
|
||||
prop_checkReadExpansions6 = verify checkReadExpansions "read -a $var"
|
||||
prop_checkReadExpansions7 = verifyNot checkReadExpansions "read $1"
|
||||
prop_checkReadExpansions8 = verifyNot checkReadExpansions "read ${var?}"
|
||||
checkReadExpansions = CommandCheck (Exactly "read") check
|
||||
where
|
||||
options = getOpts "sreu:n:N:i:p:a:"
|
||||
getVars cmd = fromMaybe [] $ do
|
||||
opts <- options cmd
|
||||
return . map snd $ filter (\(x,_) -> x == "" || x == "a") opts
|
||||
|
||||
check cmd = mapM_ warning $ getVars cmd
|
||||
warning t = potentially $ do
|
||||
var <- getSingleUnmodifiedVariable t
|
||||
let name = bracedString var
|
||||
guard $ isVariableName name -- e.g. not $1
|
||||
return . warn (getId t) 2229 $
|
||||
"This does not read '" ++ name ++ "'. Remove $/${} for that, or use ${var?} to quiet."
|
||||
|
||||
-- Return the single variable expansion that makes up this word, if any.
|
||||
-- e.g. $foo -> $foo, "$foo"'' -> $foo , "hello $name" -> Nothing
|
||||
getSingleUnmodifiedVariable :: Token -> Maybe Token
|
||||
getSingleUnmodifiedVariable word =
|
||||
case getWordParts word of
|
||||
[t@(T_DollarBraced {})] ->
|
||||
let contents = bracedString t
|
||||
name = getBracedReference contents
|
||||
in guard (contents == name) >> return t
|
||||
_ -> Nothing
|
||||
|
||||
prop_checkAliasesUsesArgs1 = verify checkAliasesUsesArgs "alias a='cp $1 /a'"
|
||||
prop_checkAliasesUsesArgs2 = verifyNot checkAliasesUsesArgs "alias $1='foo'"
|
||||
prop_checkAliasesUsesArgs3 = verify checkAliasesUsesArgs "alias a=\"echo \\${@}\""
|
||||
checkAliasesUsesArgs = CommandCheck (Exactly "alias") (f . arguments)
|
||||
where
|
||||
re = mkRegex "\\$\\{?[0-9*@]"
|
||||
f = mapM_ checkArg
|
||||
checkArg arg =
|
||||
let string = fromJust $ getLiteralStringExt (const $ return "_") arg in
|
||||
when ('=' `elem` string && string `matches` re) $
|
||||
err (getId arg) 2142
|
||||
"Aliases can't use positional parameters. Use a function."
|
||||
|
||||
|
||||
prop_checkAliasesExpandEarly1 = verify checkAliasesExpandEarly "alias foo=\"echo $PWD\""
|
||||
prop_checkAliasesExpandEarly2 = verifyNot checkAliasesExpandEarly "alias -p"
|
||||
prop_checkAliasesExpandEarly3 = verifyNot checkAliasesExpandEarly "alias foo='echo {1..10}'"
|
||||
checkAliasesExpandEarly = CommandCheck (Exactly "alias") (f . arguments)
|
||||
where
|
||||
f = mapM_ checkArg
|
||||
checkArg arg | '=' `elem` concat (oversimplify arg) =
|
||||
forM_ (take 1 $ filter (not . isLiteral) $ getWordParts arg) $
|
||||
\x -> warn (getId x) 2139 "This expands when defined, not when used. Consider escaping."
|
||||
checkArg _ = return ()
|
||||
|
||||
|
||||
prop_checkUnsetGlobs1 = verify checkUnsetGlobs "unset foo[1]"
|
||||
prop_checkUnsetGlobs2 = verifyNot checkUnsetGlobs "unset foo"
|
||||
checkUnsetGlobs = CommandCheck (Exactly "unset") (mapM_ check . arguments)
|
||||
where
|
||||
check arg =
|
||||
when (isGlob arg) $
|
||||
warn (getId arg) 2184 "Quote arguments to unset so they're not glob expanded."
|
||||
|
||||
|
||||
prop_checkFindWithoutPath1 = verify checkFindWithoutPath "find -type f"
|
||||
prop_checkFindWithoutPath2 = verify checkFindWithoutPath "find"
|
||||
prop_checkFindWithoutPath3 = verifyNot checkFindWithoutPath "find . -type f"
|
||||
prop_checkFindWithoutPath4 = verifyNot checkFindWithoutPath "find -H -L \"$path\" -print"
|
||||
prop_checkFindWithoutPath5 = verifyNot checkFindWithoutPath "find -O3 ."
|
||||
prop_checkFindWithoutPath6 = verifyNot checkFindWithoutPath "find -D exec ."
|
||||
checkFindWithoutPath = CommandCheck (Basename "find") f
|
||||
where
|
||||
f (T_SimpleCommand _ _ (cmd:args)) =
|
||||
unless (hasPath args) $
|
||||
info (getId cmd) 2185 "Some finds don't have a default path. Specify '.' explicitly."
|
||||
|
||||
-- This is a bit of a kludge. find supports flag arguments both before and after the path,
|
||||
-- as well as multiple non-flag arguments that are not the path. We assume that all the
|
||||
-- pre-path flags are single characters, which is generally the case except for -O3.
|
||||
hasPath (first:rest) =
|
||||
let flag = fromJust $ getLiteralStringExt (const $ return "___") first in
|
||||
not ("-" `isPrefixOf` flag) || isLeadingFlag flag && hasPath rest
|
||||
hasPath [] = False
|
||||
isLeadingFlag flag = length flag <= 2 || "-O" `isPrefixOf` flag
|
||||
|
||||
|
||||
prop_checkTimeParameters1 = verify checkTimeParameters "time -f lol sleep 10"
|
||||
prop_checkTimeParameters2 = verifyNot checkTimeParameters "time sleep 10"
|
||||
prop_checkTimeParameters3 = verifyNot checkTimeParameters "time -p foo"
|
||||
prop_checkTimeParameters4 = verifyNot checkTimeParameters "command time -f lol sleep 10"
|
||||
checkTimeParameters = CommandCheck (Exactly "time") f
|
||||
where
|
||||
f (T_SimpleCommand _ _ (cmd:args:_)) =
|
||||
whenShell [Bash, Sh] $
|
||||
let s = concat $ oversimplify args in
|
||||
when ("-" `isPrefixOf` s && s /= "-p") $
|
||||
info (getId cmd) 2023 "The shell may override 'time' as seen in man time(1). Use 'command time ..' for that one."
|
||||
|
||||
f _ = return ()
|
||||
|
||||
prop_checkTimedCommand1 = verify checkTimedCommand "#!/bin/sh\ntime -p foo | bar"
|
||||
prop_checkTimedCommand2 = verify checkTimedCommand "#!/bin/dash\ntime ( foo; bar; )"
|
||||
prop_checkTimedCommand3 = verifyNot checkTimedCommand "#!/bin/sh\ntime sleep 1"
|
||||
checkTimedCommand = CommandCheck (Exactly "time") f where
|
||||
f (T_SimpleCommand _ _ (c:args@(_:_))) =
|
||||
whenShell [Sh, Dash] $ do
|
||||
let cmd = last args -- "time" is parsed with a command as argument
|
||||
when (isPiped cmd) $
|
||||
warn (getId c) 2176 "'time' is undefined for pipelines. time single stage or bash -c instead."
|
||||
when (isSimple cmd == Just False) $
|
||||
warn (getId cmd) 2177 "'time' is undefined for compound commands, time sh -c instead."
|
||||
f _ = return ()
|
||||
isPiped cmd =
|
||||
case cmd of
|
||||
T_Pipeline _ _ (_:_:_) -> True
|
||||
_ -> False
|
||||
getCommand cmd =
|
||||
case cmd of
|
||||
T_Pipeline _ _ (T_Redirecting _ _ a : _) -> return a
|
||||
_ -> fail ""
|
||||
isSimple cmd = do
|
||||
innerCommand <- getCommand cmd
|
||||
case innerCommand of
|
||||
T_SimpleCommand {} -> return True
|
||||
_ -> return False
|
||||
|
||||
prop_checkLocalScope1 = verify checkLocalScope "local foo=3"
|
||||
prop_checkLocalScope2 = verifyNot checkLocalScope "f() { local foo=3; }"
|
||||
checkLocalScope = CommandCheck (Exactly "local") $ \t ->
|
||||
whenShell [Bash, Dash] $ do -- Ksh allows it, Sh doesn't support local
|
||||
path <- getPathM t
|
||||
unless (any isFunction path) $
|
||||
err (getId t) 2168 "'local' is only valid in functions."
|
||||
|
||||
prop_checkDeprecatedTempfile1 = verify checkDeprecatedTempfile "var=$(tempfile)"
|
||||
prop_checkDeprecatedTempfile2 = verifyNot checkDeprecatedTempfile "tempfile=$(mktemp)"
|
||||
checkDeprecatedTempfile = CommandCheck (Basename "tempfile") $
|
||||
\t -> warn (getId t) 2186 "tempfile is deprecated. Use mktemp instead."
|
||||
|
||||
prop_checkDeprecatedEgrep = verify checkDeprecatedEgrep "egrep '.+'"
|
||||
checkDeprecatedEgrep = CommandCheck (Basename "egrep") $
|
||||
\t -> info (getId t) 2196 "egrep is non-standard and deprecated. Use grep -E instead."
|
||||
|
||||
prop_checkDeprecatedFgrep = verify checkDeprecatedFgrep "fgrep '*' files"
|
||||
checkDeprecatedFgrep = CommandCheck (Basename "fgrep") $
|
||||
\t -> info (getId t) 2197 "fgrep is non-standard and deprecated. Use grep -F instead."
|
||||
|
||||
prop_checkWhileGetoptsCase1 = verify checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; esac; done"
|
||||
prop_checkWhileGetoptsCase2 = verify checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; b) bar;; esac; done"
|
||||
prop_checkWhileGetoptsCase3 = verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; b) bar;; *) :;esac; done"
|
||||
prop_checkWhileGetoptsCase4 = verifyNot checkWhileGetoptsCase "while getopts 'a:123' x; do case $x in a) foo;; [0-9]) bar;; esac; done"
|
||||
prop_checkWhileGetoptsCase5 = verifyNot checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; \\?) bar;; *) baz;; esac; done"
|
||||
checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f
|
||||
where
|
||||
f :: Token -> Analysis
|
||||
f t@(T_SimpleCommand _ _ (cmd:arg1:_)) = do
|
||||
path <- getPathM t
|
||||
potentially $ do
|
||||
options <- getLiteralString arg1
|
||||
(T_WhileExpression _ _ body) <- findFirst whileLoop path
|
||||
caseCmd <- mapMaybe findCase body !!! 0
|
||||
return $ check (getId arg1) (map (:[]) $ filter (/= ':') options) caseCmd
|
||||
f _ = return ()
|
||||
|
||||
check :: Id -> [String] -> Token -> Analysis
|
||||
check optId opts (T_CaseExpression id _ list) = do
|
||||
unless (Nothing `Map.member` handledMap) $ do
|
||||
mapM_ (warnUnhandled optId id) $ catMaybes $ Map.keys notHandled
|
||||
|
||||
unless (any (`Map.member` handledMap) [Just "*",Just "?"]) $
|
||||
warn id 2220 "Invalid flags are not handled. Add a *) case."
|
||||
|
||||
mapM_ warnRedundant $ Map.toList notRequested
|
||||
|
||||
where
|
||||
handledMap = Map.fromList (concatMap getHandledStrings list)
|
||||
requestedMap = Map.fromList $ map (\x -> (Just x, ())) opts
|
||||
|
||||
notHandled = Map.difference requestedMap handledMap
|
||||
notRequested = Map.difference handledMap requestedMap
|
||||
|
||||
warnUnhandled optId caseId str =
|
||||
warn caseId 2213 $ "getopts specified -" ++ str ++ ", but it's not handled by this 'case'."
|
||||
|
||||
warnRedundant (key, expr) = potentially $ do
|
||||
str <- key
|
||||
guard $ str `notElem` ["*", ":", "?"]
|
||||
return $ warn (getId expr) 2214 "This case is not specified by getopts."
|
||||
|
||||
getHandledStrings (_, globs, _) =
|
||||
map (\x -> (literal x, x)) globs
|
||||
|
||||
literal :: Token -> Maybe String
|
||||
literal t = do
|
||||
getLiteralString t <> fromGlob t
|
||||
|
||||
fromGlob t =
|
||||
case t of
|
||||
T_Glob _ ('[':c:']':[]) -> return [c]
|
||||
T_Glob _ "*" -> return "*"
|
||||
T_Glob _ "?" -> return "?"
|
||||
_ -> Nothing
|
||||
|
||||
whileLoop t =
|
||||
case t of
|
||||
T_WhileExpression {} -> return True
|
||||
T_Script {} -> return False
|
||||
_ -> Nothing
|
||||
|
||||
findCase t =
|
||||
case t of
|
||||
T_Annotation _ _ x -> findCase x
|
||||
T_Pipeline _ _ [x] -> findCase x
|
||||
T_Redirecting _ _ x@(T_CaseExpression {}) -> return x
|
||||
_ -> Nothing
|
||||
|
||||
prop_checkCatastrophicRm1 = verify checkCatastrophicRm "rm -r $1/$2"
|
||||
prop_checkCatastrophicRm2 = verify checkCatastrophicRm "rm -r /home/$foo"
|
||||
prop_checkCatastrophicRm3 = verifyNot checkCatastrophicRm "rm -r /home/${USER:?}/*"
|
||||
prop_checkCatastrophicRm4 = verify checkCatastrophicRm "rm -fr /home/$(whoami)/*"
|
||||
prop_checkCatastrophicRm5 = verifyNot checkCatastrophicRm "rm -r /home/${USER:-thing}/*"
|
||||
prop_checkCatastrophicRm6 = verify checkCatastrophicRm "rm --recursive /etc/*$config*"
|
||||
prop_checkCatastrophicRm8 = verify checkCatastrophicRm "rm -rf /home"
|
||||
prop_checkCatastrophicRm10= verifyNot checkCatastrophicRm "rm -r \"${DIR}\"/{.gitignore,.gitattributes,ci}"
|
||||
prop_checkCatastrophicRm11= verify checkCatastrophicRm "rm -r /{bin,sbin}/$exec"
|
||||
prop_checkCatastrophicRm12= verify checkCatastrophicRm "rm -r /{{usr,},{bin,sbin}}/$exec"
|
||||
prop_checkCatastrophicRm13= verifyNot checkCatastrophicRm "rm -r /{{a,b},{c,d}}/$exec"
|
||||
prop_checkCatastrophicRmA = verify checkCatastrophicRm "rm -rf /usr /lib/nvidia-current/xorg/xorg"
|
||||
prop_checkCatastrophicRmB = verify checkCatastrophicRm "rm -rf \"$STEAMROOT/\"*"
|
||||
checkCatastrophicRm = CommandCheck (Basename "rm") $ \t ->
|
||||
when (isRecursive t) $
|
||||
mapM_ (mapM_ checkWord . braceExpand) $ arguments t
|
||||
where
|
||||
isRecursive = any (`elem` ["r", "R", "recursive"]) . map snd . getAllFlags
|
||||
|
||||
checkWord token =
|
||||
case getLiteralString token of
|
||||
Just str ->
|
||||
when (fixPath str `elem` importantPaths) $
|
||||
warn (getId token) 2114 "Warning: deletes a system directory."
|
||||
Nothing ->
|
||||
checkWord' token
|
||||
|
||||
checkWord' token = fromMaybe (return ()) $ do
|
||||
filename <- getPotentialPath token
|
||||
let path = fixPath filename
|
||||
return . when (path `elem` importantPaths) $
|
||||
warn (getId token) 2115 $ "Use \"${var:?}\" to ensure this never expands to " ++ path ++ " ."
|
||||
|
||||
fixPath filename =
|
||||
let normalized = skipRepeating '/' . skipRepeating '*' $ filename in
|
||||
if normalized == "/" then normalized else stripTrailing '/' normalized
|
||||
|
||||
getPotentialPath = getLiteralStringExt f
|
||||
where
|
||||
f (T_Glob _ str) = return str
|
||||
f (T_DollarBraced _ word) =
|
||||
let var = onlyLiteralString word in
|
||||
-- This shouldn't handle non-colon cases.
|
||||
if any (`isInfixOf` var) [":?", ":-", ":="]
|
||||
then Nothing
|
||||
else return ""
|
||||
f _ = return ""
|
||||
|
||||
stripTrailing c = reverse . dropWhile (== c) . reverse
|
||||
skipRepeating c (a:b:rest) | a == b && b == c = skipRepeating c (b:rest)
|
||||
skipRepeating c (a:r) = a:skipRepeating c r
|
||||
skipRepeating _ [] = []
|
||||
|
||||
paths = [
|
||||
"", "/bin", "/etc", "/home", "/mnt", "/usr", "/usr/share", "/usr/local",
|
||||
"/var", "/lib", "/dev", "/media", "/boot", "/lib64", "/usr/bin"
|
||||
]
|
||||
importantPaths = filter (not . null) $
|
||||
["", "/", "/*", "/*/*"] >>= (\x -> map (++x) paths)
|
||||
|
||||
|
||||
prop_checkLetUsage1 = verify checkLetUsage "let a=1"
|
||||
prop_checkLetUsage2 = verifyNot checkLetUsage "(( a=1 ))"
|
||||
checkLetUsage = CommandCheck (Exactly "let") f
|
||||
where
|
||||
f t = whenShell [Bash,Ksh] $ do
|
||||
style (getId t) 2219 $ "Instead of 'let expr', prefer (( expr )) ."
|
||||
|
||||
|
||||
missingDestination handler token = do
|
||||
case params of
|
||||
[single] -> do
|
||||
unless (hasTarget || mayBecomeMultipleArgs single) $
|
||||
handler token
|
||||
_ -> return ()
|
||||
where
|
||||
args = getAllFlags token
|
||||
params = map fst $ filter (\(_,x) -> x == "") args
|
||||
hasTarget =
|
||||
any (\x -> x /= "" && x `isPrefixOf` "target-directory") $
|
||||
map snd args
|
||||
|
||||
prop_checkMvArguments1 = verify checkMvArguments "mv 'foo bar'"
|
||||
prop_checkMvArguments2 = verifyNot checkMvArguments "mv foo bar"
|
||||
prop_checkMvArguments3 = verifyNot checkMvArguments "mv 'foo bar'{,bak}"
|
||||
prop_checkMvArguments4 = verifyNot checkMvArguments "mv \"$@\""
|
||||
prop_checkMvArguments5 = verifyNot checkMvArguments "mv -t foo bar"
|
||||
prop_checkMvArguments6 = verifyNot checkMvArguments "mv --target-directory=foo bar"
|
||||
prop_checkMvArguments7 = verifyNot checkMvArguments "mv --target-direc=foo bar"
|
||||
prop_checkMvArguments8 = verifyNot checkMvArguments "mv --version"
|
||||
prop_checkMvArguments9 = verifyNot checkMvArguments "mv \"${!var}\""
|
||||
checkMvArguments = CommandCheck (Basename "mv") $ missingDestination f
|
||||
where
|
||||
f t = err (getId t) 2224 "This mv has no destination. Check the arguments."
|
||||
|
||||
checkCpArguments = CommandCheck (Basename "cp") $ missingDestination f
|
||||
where
|
||||
f t = err (getId t) 2225 "This cp has no destination. Check the arguments."
|
||||
|
||||
checkLnArguments = CommandCheck (Basename "ln") $ missingDestination f
|
||||
where
|
||||
f t = warn (getId t) 2226 "This ln has no destination. Check the arguments, or specify '.' explicitly."
|
||||
|
||||
|
||||
prop_checkFindRedirections1 = verify checkFindRedirections "find . -exec echo {} > file \\;"
|
||||
prop_checkFindRedirections2 = verifyNot checkFindRedirections "find . -exec echo {} \\; > file"
|
||||
prop_checkFindRedirections3 = verifyNot checkFindRedirections "find . -execdir sh -c 'foo > file' \\;"
|
||||
checkFindRedirections = CommandCheck (Basename "find") f
|
||||
where
|
||||
f t = do
|
||||
redirecting <- getClosestCommandM t
|
||||
case redirecting of
|
||||
Just (T_Redirecting _ redirs@(_:_) (T_SimpleCommand _ _ args@(_:_:_))) -> do
|
||||
-- This assumes IDs are sequential, which is mostly but not always true.
|
||||
let minRedir = minimum $ map getId redirs
|
||||
let maxArg = maximum $ map getId args
|
||||
when (minRedir < maxArg) $
|
||||
warn minRedir 2227
|
||||
"Redirection applies to the find command itself. Rewrite to work per action (or move to end)."
|
||||
_ -> return ()
|
||||
|
||||
prop_checkWhich = verify checkWhich "which '.+'"
|
||||
checkWhich = CommandCheck (Basename "which") $
|
||||
\t -> info (getId t) 2230 "which is non-standard. Use builtin 'command -v' instead."
|
||||
|
||||
return []
|
||||
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
419
src/ShellCheck/Checks/ShellSupport.hs
Normal file
419
src/ShellCheck/Checks/ShellSupport.hs
Normal file
|
@ -0,0 +1,419 @@
|
|||
{-
|
||||
Copyright 2012-2016 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
module ShellCheck.Checks.ShellSupport (checker
|
||||
, ShellCheck.Checks.ShellSupport.runTests
|
||||
) where
|
||||
|
||||
import ShellCheck.AST
|
||||
import ShellCheck.ASTLib
|
||||
import ShellCheck.AnalyzerLib
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.Regex
|
||||
|
||||
import Control.Monad
|
||||
import Control.Monad.RWS
|
||||
import Data.Char
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import qualified Data.Map as Map
|
||||
import Test.QuickCheck.All (forAllProperties)
|
||||
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
|
||||
|
||||
data ForShell = ForShell [Shell] (Token -> Analysis)
|
||||
|
||||
getChecker params list = Checker {
|
||||
perScript = nullCheck,
|
||||
perToken = foldl composeAnalyzers nullCheck $ mapMaybe include list
|
||||
}
|
||||
where
|
||||
shell = shellType params
|
||||
include (ForShell list a) = do
|
||||
guard $ shell `elem` list
|
||||
return a
|
||||
|
||||
checker params = getChecker params checks
|
||||
|
||||
checks = [
|
||||
checkForDecimals
|
||||
,checkBashisms
|
||||
,checkEchoSed
|
||||
,checkBraceExpansionVars
|
||||
,checkMultiDimensionalArrays
|
||||
,checkPS1Assignments
|
||||
]
|
||||
|
||||
testChecker (ForShell _ t) =
|
||||
Checker {
|
||||
perScript = nullCheck,
|
||||
perToken = t
|
||||
}
|
||||
verify c s = producesComments (testChecker c) s == Just True
|
||||
verifyNot c s = producesComments (testChecker c) s == Just False
|
||||
|
||||
prop_checkForDecimals1 = verify checkForDecimals "((3.14*c))"
|
||||
prop_checkForDecimals2 = verify checkForDecimals "foo[1.2]=bar"
|
||||
prop_checkForDecimals3 = verifyNot checkForDecimals "declare -A foo; foo[1.2]=bar"
|
||||
checkForDecimals = ForShell [Sh, Dash, Bash] f
|
||||
where
|
||||
f t@(TA_Expansion id _) = potentially $ do
|
||||
str <- getLiteralString t
|
||||
first <- str !!! 0
|
||||
guard $ isDigit first && '.' `elem` str
|
||||
return $ err id 2079 "(( )) doesn't support decimals. Use bc or awk."
|
||||
f _ = return ()
|
||||
|
||||
|
||||
prop_checkBashisms = verify checkBashisms "while read a; do :; done < <(a)"
|
||||
prop_checkBashisms2 = verify checkBashisms "[ foo -nt bar ]"
|
||||
prop_checkBashisms3 = verify checkBashisms "echo $((i++))"
|
||||
prop_checkBashisms4 = verify checkBashisms "rm !(*.hs)"
|
||||
prop_checkBashisms5 = verify checkBashisms "source file"
|
||||
prop_checkBashisms6 = verify checkBashisms "[ \"$a\" == 42 ]"
|
||||
prop_checkBashisms7 = verify checkBashisms "echo ${var[1]}"
|
||||
prop_checkBashisms8 = verify checkBashisms "echo ${!var[@]}"
|
||||
prop_checkBashisms9 = verify checkBashisms "echo ${!var*}"
|
||||
prop_checkBashisms10= verify checkBashisms "echo ${var:4:12}"
|
||||
prop_checkBashisms11= verifyNot checkBashisms "echo ${var:-4}"
|
||||
prop_checkBashisms12= verify checkBashisms "echo ${var//foo/bar}"
|
||||
prop_checkBashisms13= verify checkBashisms "exec -c env"
|
||||
prop_checkBashisms14= verify checkBashisms "echo -n \"Foo: \""
|
||||
prop_checkBashisms15= verify checkBashisms "let n++"
|
||||
prop_checkBashisms16= verify checkBashisms "echo $RANDOM"
|
||||
prop_checkBashisms17= verify checkBashisms "echo $((RANDOM%6+1))"
|
||||
prop_checkBashisms18= verify checkBashisms "foo &> /dev/null"
|
||||
prop_checkBashisms19= verify checkBashisms "foo > file*.txt"
|
||||
prop_checkBashisms20= verify checkBashisms "read -ra foo"
|
||||
prop_checkBashisms21= verify checkBashisms "[ -a foo ]"
|
||||
prop_checkBashisms22= verifyNot checkBashisms "[ foo -a bar ]"
|
||||
prop_checkBashisms23= verify checkBashisms "trap mything ERR INT"
|
||||
prop_checkBashisms24= verifyNot checkBashisms "trap mything INT TERM"
|
||||
prop_checkBashisms25= verify checkBashisms "cat < /dev/tcp/host/123"
|
||||
prop_checkBashisms26= verify checkBashisms "trap mything ERR SIGTERM"
|
||||
prop_checkBashisms27= verify checkBashisms "echo *[^0-9]*"
|
||||
prop_checkBashisms28= verify checkBashisms "exec {n}>&2"
|
||||
prop_checkBashisms29= verify checkBashisms "echo ${!var}"
|
||||
prop_checkBashisms30= verify checkBashisms "printf -v '%s' \"$1\""
|
||||
prop_checkBashisms31= verify checkBashisms "printf '%q' \"$1\""
|
||||
prop_checkBashisms32= verifyNot checkBashisms "#!/bin/dash\n[ foo -nt bar ]"
|
||||
prop_checkBashisms33= verify checkBashisms "#!/bin/sh\necho -n foo"
|
||||
prop_checkBashisms34= verifyNot checkBashisms "#!/bin/dash\necho -n foo"
|
||||
prop_checkBashisms35= verifyNot checkBashisms "#!/bin/dash\nlocal foo"
|
||||
prop_checkBashisms36= verifyNot checkBashisms "#!/bin/dash\nread -p foo -r bar"
|
||||
prop_checkBashisms37= verifyNot checkBashisms "HOSTNAME=foo; echo $HOSTNAME"
|
||||
prop_checkBashisms38= verify checkBashisms "RANDOM=9; echo $RANDOM"
|
||||
prop_checkBashisms39= verify checkBashisms "foo-bar() { true; }"
|
||||
prop_checkBashisms40= verify checkBashisms "echo $(<file)"
|
||||
prop_checkBashisms41= verify checkBashisms "echo `<file`"
|
||||
prop_checkBashisms42= verify checkBashisms "trap foo int"
|
||||
prop_checkBashisms43= verify checkBashisms "trap foo sigint"
|
||||
prop_checkBashisms44= verifyNot checkBashisms "#!/bin/dash\ntrap foo int"
|
||||
prop_checkBashisms45= verifyNot checkBashisms "#!/bin/dash\ntrap foo INT"
|
||||
prop_checkBashisms46= verify checkBashisms "#!/bin/dash\ntrap foo SIGINT"
|
||||
prop_checkBashisms47= verify checkBashisms "#!/bin/dash\necho foo 42>/dev/null"
|
||||
prop_checkBashisms48= verifyNot checkBashisms "#!/bin/dash\necho $LINENO"
|
||||
prop_checkBashisms49= verify checkBashisms "#!/bin/dash\necho $MACHTYPE"
|
||||
prop_checkBashisms50= verify checkBashisms "#!/bin/sh\ncmd >& file"
|
||||
prop_checkBashisms51= verifyNot checkBashisms "#!/bin/sh\ncmd 2>&1"
|
||||
prop_checkBashisms52= verifyNot checkBashisms "#!/bin/sh\ncmd >&2"
|
||||
prop_checkBashisms53= verifyNot checkBashisms "#!/bin/sh\nprintf -- -f\n"
|
||||
prop_checkBashisms54= verify checkBashisms "#!/bin/sh\nfoo+=bar"
|
||||
checkBashisms = ForShell [Sh, Dash] $ \t -> do
|
||||
params <- ask
|
||||
kludge params t
|
||||
where
|
||||
-- This code was copy-pasted from Analytics where params was a variable
|
||||
kludge params = bashism
|
||||
where
|
||||
isDash = shellType params == Dash
|
||||
warnMsg id s =
|
||||
if isDash
|
||||
then warn id 2169 $ "In dash, " ++ s ++ " not supported."
|
||||
else warn id 2039 $ "In POSIX sh, " ++ s ++ " undefined."
|
||||
|
||||
bashism (T_ProcSub id _ _) = warnMsg id "process substitution is"
|
||||
bashism (T_Extglob id _ _) = warnMsg id "extglob is"
|
||||
bashism (T_DollarSingleQuoted id _) = warnMsg id "$'..' is"
|
||||
bashism (T_DollarDoubleQuoted id _) = warnMsg id "$\"..\" is"
|
||||
bashism (T_ForArithmetic id _ _ _ _) = warnMsg id "arithmetic for loops are"
|
||||
bashism (T_Arithmetic id _) = warnMsg id "standalone ((..)) is"
|
||||
bashism (T_DollarBracket id _) = warnMsg id "$[..] in place of $((..)) is"
|
||||
bashism (T_SelectIn id _ _ _) = warnMsg id "select loops are"
|
||||
bashism (T_BraceExpansion id _) = warnMsg id "brace expansion is"
|
||||
bashism (T_Condition id DoubleBracket _) = warnMsg id "[[ ]] is"
|
||||
bashism (T_HereString id _) = warnMsg id "here-strings are"
|
||||
bashism (TC_Binary id SingleBracket op _ _)
|
||||
| op `elem` [ "<", ">", "\\<", "\\>", "<=", ">=", "\\<=", "\\>="] =
|
||||
unless isDash $ warnMsg id $ "lexicographical " ++ op ++ " is"
|
||||
bashism (TC_Binary id SingleBracket op _ _)
|
||||
| op `elem` [ "-nt", "-ef" ] =
|
||||
unless isDash $ warnMsg id $ op ++ " is"
|
||||
bashism (TC_Binary id SingleBracket "==" _ _) =
|
||||
warnMsg id "== in place of = is"
|
||||
bashism (TC_Binary id SingleBracket "=~" _ _) =
|
||||
warnMsg id "=~ regex matching is"
|
||||
bashism (TC_Unary id _ "-a" _) =
|
||||
warnMsg id "unary -a in place of -e is"
|
||||
bashism (TA_Unary id op _)
|
||||
| op `elem` [ "|++", "|--", "++|", "--|"] =
|
||||
warnMsg id $ filter (/= '|') op ++ " is"
|
||||
bashism (TA_Binary id "**" _ _) = warnMsg id "exponentials are"
|
||||
bashism (T_FdRedirect id "&" (T_IoFile _ (T_Greater _) _)) = warnMsg id "&> is"
|
||||
bashism (T_FdRedirect id "" (T_IoFile _ (T_GREATAND _) _)) = warnMsg id ">& is"
|
||||
bashism (T_FdRedirect id ('{':_) _) = warnMsg id "named file descriptors are"
|
||||
bashism (T_FdRedirect id num _)
|
||||
| all isDigit num && length num > 1 = warnMsg id "FDs outside 0-9 are"
|
||||
bashism (T_Assignment id Append _ _ _) =
|
||||
warnMsg id "+= is"
|
||||
bashism (T_IoFile id _ word) | isNetworked =
|
||||
warnMsg id "/dev/{tcp,udp} is"
|
||||
where
|
||||
file = onlyLiteralString word
|
||||
isNetworked = any (`isPrefixOf` file) ["/dev/tcp", "/dev/udp"]
|
||||
bashism (T_Glob id str) | "[^" `isInfixOf` str =
|
||||
warnMsg id "^ in place of ! in glob bracket expressions is"
|
||||
|
||||
bashism t@(TA_Variable id str _) | isBashVariable str =
|
||||
warnMsg id $ str ++ " is"
|
||||
|
||||
bashism t@(T_DollarBraced id token) = do
|
||||
mapM_ check expansion
|
||||
when (isBashVariable var) $
|
||||
warnMsg id $ var ++ " is"
|
||||
where
|
||||
str = bracedString t
|
||||
var = getBracedReference str
|
||||
check (regex, feature) =
|
||||
when (isJust $ matchRegex regex str) $ warnMsg id feature
|
||||
|
||||
bashism t@(T_Pipe id "|&") =
|
||||
warnMsg id "|& in place of 2>&1 | is"
|
||||
bashism (T_Array id _) =
|
||||
warnMsg id "arrays are"
|
||||
bashism (T_IoFile id _ t) | isGlob t =
|
||||
warnMsg id "redirecting to/from globs is"
|
||||
bashism (T_CoProc id _ _) =
|
||||
warnMsg id "coproc is"
|
||||
|
||||
bashism (T_Function id _ _ str _) | not (isVariableName str) =
|
||||
warnMsg id "naming functions outside [a-zA-Z_][a-zA-Z0-9_]* is"
|
||||
|
||||
bashism (T_DollarExpansion id [x]) | isOnlyRedirection x =
|
||||
warnMsg id "$(<file) to read files is"
|
||||
bashism (T_Backticked id [x]) | isOnlyRedirection x =
|
||||
warnMsg id "`<file` to read files is"
|
||||
|
||||
bashism t@(T_SimpleCommand _ _ (cmd:arg:_))
|
||||
| t `isCommand` "echo" && "-" `isPrefixOf` argString =
|
||||
unless ("--" `isPrefixOf` argString) $ -- echo "-----"
|
||||
if isDash
|
||||
then
|
||||
when (argString /= "-n") $
|
||||
warnMsg (getId arg) "echo flags besides -n"
|
||||
else
|
||||
warnMsg (getId arg) "echo flags are"
|
||||
where argString = concat $ oversimplify arg
|
||||
bashism t@(T_SimpleCommand _ _ (cmd:arg:_))
|
||||
| t `isCommand` "exec" && "-" `isPrefixOf` concat (oversimplify arg) =
|
||||
warnMsg (getId arg) "exec flags are"
|
||||
bashism t@(T_SimpleCommand id _ _)
|
||||
| t `isCommand` "let" = warnMsg id "'let' is"
|
||||
|
||||
bashism t@(T_SimpleCommand id _ (cmd:rest)) =
|
||||
let name = fromMaybe "" $ getCommandName t
|
||||
flags = getLeadingFlags t
|
||||
in do
|
||||
when (name `elem` unsupportedCommands) $
|
||||
warnMsg id $ "'" ++ name ++ "' is"
|
||||
potentially $ do
|
||||
allowed <- Map.lookup name allowedFlags
|
||||
(word, flag) <- listToMaybe $
|
||||
filter (\x -> (not . null . snd $ x) && snd x `notElem` allowed) flags
|
||||
return . warnMsg (getId word) $ name ++ " -" ++ flag ++ " is"
|
||||
|
||||
when (name == "source") $ warnMsg id "'source' in place of '.' is"
|
||||
when (name == "trap") $
|
||||
let
|
||||
check token = potentially $ do
|
||||
str <- getLiteralString token
|
||||
let upper = map toUpper str
|
||||
return $ do
|
||||
when (upper `elem` ["ERR", "DEBUG", "RETURN"]) $
|
||||
warnMsg (getId token) $ "trapping " ++ str ++ " is"
|
||||
when ("SIG" `isPrefixOf` upper) $
|
||||
warnMsg (getId token)
|
||||
"prefixing signal names with 'SIG' is"
|
||||
when (not isDash && upper /= str) $
|
||||
warnMsg (getId token)
|
||||
"using lower/mixed case for signal names is"
|
||||
in
|
||||
mapM_ check (drop 1 rest)
|
||||
|
||||
when (name == "printf") $ potentially $ do
|
||||
format <- rest !!! 0 -- flags are covered by allowedFlags
|
||||
let literal = onlyLiteralString format
|
||||
guard $ "%q" `isInfixOf` literal
|
||||
return $ warnMsg (getId format) "printf %q is"
|
||||
where
|
||||
unsupportedCommands = [
|
||||
"let", "caller", "builtin", "complete", "compgen", "declare", "dirs", "disown",
|
||||
"enable", "mapfile", "readarray", "pushd", "popd", "shopt", "suspend",
|
||||
"typeset"
|
||||
] ++ if not isDash then ["local", "type"] else []
|
||||
allowedFlags = Map.fromList [
|
||||
("exec", []),
|
||||
("export", ["-p"]),
|
||||
("printf", []),
|
||||
("read", if isDash then ["r", "p"] else ["r"]),
|
||||
("ulimit", ["f"])
|
||||
]
|
||||
|
||||
bashism _ = return ()
|
||||
|
||||
varChars="_0-9a-zA-Z"
|
||||
expansion = let re = mkRegex in [
|
||||
(re $ "^![" ++ varChars ++ "]", "indirect expansion is"),
|
||||
(re $ "^[" ++ varChars ++ "]+\\[.*\\]$", "array references are"),
|
||||
(re $ "^![" ++ varChars ++ "]+\\[[*@]]$", "array key expansion is"),
|
||||
(re $ "^![" ++ varChars ++ "]+[*@]$", "name matching prefixes are"),
|
||||
(re $ "^[" ++ varChars ++ "]+:[^-=?+]", "string indexing is"),
|
||||
(re $ "^[" ++ varChars ++ "]+(\\[.*\\])?/", "string replacement is")
|
||||
]
|
||||
bashVars = [
|
||||
"LINENO", "OSTYPE", "MACHTYPE", "HOSTTYPE", "HOSTNAME",
|
||||
"DIRSTACK", "EUID", "UID", "SHLVL", "PIPESTATUS", "SHELLOPTS"
|
||||
]
|
||||
bashDynamicVars = [ "RANDOM", "SECONDS" ]
|
||||
dashVars = [ "LINENO" ]
|
||||
isBashVariable var =
|
||||
(var `elem` bashDynamicVars
|
||||
|| var `elem` bashVars && not (isAssigned var))
|
||||
&& not (isDash && var `elem` dashVars)
|
||||
isAssigned var = any f (variableFlow params)
|
||||
where
|
||||
f x = case x of
|
||||
Assignment (_, _, name, _) -> name == var
|
||||
_ -> False
|
||||
|
||||
prop_checkEchoSed1 = verify checkEchoSed "FOO=$(echo \"$cow\" | sed 's/foo/bar/g')"
|
||||
prop_checkEchoSed2 = verify checkEchoSed "rm $(echo $cow | sed -e 's,foo,bar,')"
|
||||
checkEchoSed = ForShell [Bash, Ksh] f
|
||||
where
|
||||
f (T_Pipeline id _ [a, b]) =
|
||||
when (acmd == ["echo", "${VAR}"]) $
|
||||
case bcmd of
|
||||
["sed", v] -> checkIn v
|
||||
["sed", "-e", v] -> checkIn v
|
||||
_ -> return ()
|
||||
where
|
||||
-- This should have used backreferences, but TDFA doesn't support them
|
||||
sedRe = mkRegex "^s(.)([^\n]*)g?$"
|
||||
isSimpleSed s = fromMaybe False $ do
|
||||
[first,rest] <- matchRegex sedRe s
|
||||
let delimiters = filter (== head first) rest
|
||||
guard $ length delimiters == 2
|
||||
return True
|
||||
|
||||
acmd = oversimplify a
|
||||
bcmd = oversimplify b
|
||||
checkIn s =
|
||||
when (isSimpleSed s) $
|
||||
style id 2001 "See if you can use ${variable//search/replace} instead."
|
||||
f _ = return ()
|
||||
|
||||
|
||||
prop_checkBraceExpansionVars1 = verify checkBraceExpansionVars "echo {1..$n}"
|
||||
prop_checkBraceExpansionVars2 = verifyNot checkBraceExpansionVars "echo {1,3,$n}"
|
||||
prop_checkBraceExpansionVars3 = verify checkBraceExpansionVars "eval echo DSC{0001..$n}.jpg"
|
||||
prop_checkBraceExpansionVars4 = verify checkBraceExpansionVars "echo {$i..100}"
|
||||
checkBraceExpansionVars = ForShell [Bash] f
|
||||
where
|
||||
f t@(T_BraceExpansion id list) = mapM_ check list
|
||||
where
|
||||
check element =
|
||||
when (any (`isInfixOf` toString element) ["$..", "..$"]) $ do
|
||||
c <- isEvaled element
|
||||
if c
|
||||
then style id 2175 "Quote this invalid brace expansion since it should be passed literally to eval."
|
||||
else warn id 2051 "Bash doesn't support variables in brace range expansions."
|
||||
f _ = return ()
|
||||
|
||||
literalExt t =
|
||||
case t of
|
||||
T_DollarBraced {} -> return "$"
|
||||
T_DollarExpansion {} -> return "$"
|
||||
T_DollarArithmetic {} -> return "$"
|
||||
otherwise -> return "-"
|
||||
toString t = fromJust $ getLiteralStringExt literalExt t
|
||||
isEvaled t = do
|
||||
cmd <- getClosestCommandM t
|
||||
return $ isJust cmd && fromJust cmd `isUnqualifiedCommand` "eval"
|
||||
|
||||
|
||||
prop_checkMultiDimensionalArrays1 = verify checkMultiDimensionalArrays "foo[a][b]=3"
|
||||
prop_checkMultiDimensionalArrays2 = verifyNot checkMultiDimensionalArrays "foo[a]=3"
|
||||
prop_checkMultiDimensionalArrays3 = verify checkMultiDimensionalArrays "foo=( [a][b]=c )"
|
||||
prop_checkMultiDimensionalArrays4 = verifyNot checkMultiDimensionalArrays "foo=( [a]=c )"
|
||||
prop_checkMultiDimensionalArrays5 = verify checkMultiDimensionalArrays "echo ${foo[bar][baz]}"
|
||||
prop_checkMultiDimensionalArrays6 = verifyNot checkMultiDimensionalArrays "echo ${foo[bar]}"
|
||||
checkMultiDimensionalArrays = ForShell [Bash] f
|
||||
where
|
||||
f token =
|
||||
case token of
|
||||
T_Assignment _ _ name (first:second:_) _ -> about second
|
||||
T_IndexedElement _ (first:second:_) _ -> about second
|
||||
T_DollarBraced {} ->
|
||||
when (isMultiDim token) $ about token
|
||||
_ -> return ()
|
||||
about t = warn (getId t) 2180 "Bash does not support multidimensional arrays. Use 1D or associative arrays."
|
||||
|
||||
re = mkRegex "^\\[.*\\]\\[.*\\]" -- Fixme, this matches ${foo:- [][]} and such as well
|
||||
isMultiDim t = getBracedModifier (bracedString t) `matches` re
|
||||
|
||||
prop_checkPS11 = verify checkPS1Assignments "PS1='\\033[1;35m\\$ '"
|
||||
prop_checkPS11a= verify checkPS1Assignments "export PS1='\\033[1;35m\\$ '"
|
||||
prop_checkPSf2 = verify checkPS1Assignments "PS1='\\h \\e[0m\\$ '"
|
||||
prop_checkPS13 = verify checkPS1Assignments "PS1=$'\\x1b[c '"
|
||||
prop_checkPS14 = verify checkPS1Assignments "PS1=$'\\e[3m; '"
|
||||
prop_checkPS14a= verify checkPS1Assignments "export PS1=$'\\e[3m; '"
|
||||
prop_checkPS15 = verifyNot checkPS1Assignments "PS1='\\[\\033[1;35m\\]\\$ '"
|
||||
prop_checkPS16 = verifyNot checkPS1Assignments "PS1='\\[\\e1m\\e[1m\\]\\$ '"
|
||||
prop_checkPS17 = verifyNot checkPS1Assignments "PS1='e033x1B'"
|
||||
prop_checkPS18 = verifyNot checkPS1Assignments "PS1='\\[\\e\\]'"
|
||||
checkPS1Assignments = ForShell [Bash] f
|
||||
where
|
||||
f token = case token of
|
||||
(T_Assignment _ _ "PS1" _ word) -> warnFor word
|
||||
_ -> return ()
|
||||
|
||||
warnFor word =
|
||||
let contents = concat $ oversimplify word in
|
||||
when (containsUnescaped contents) $
|
||||
info (getId word) 2025 "Make sure all escape sequences are enclosed in \\[..\\] to prevent line wrapping issues"
|
||||
containsUnescaped s =
|
||||
let unenclosed = subRegex enclosedRegex s "" in
|
||||
isJust $ matchRegex escapeRegex unenclosed
|
||||
enclosedRegex = mkRegex "\\\\\\[.*\\\\\\]" -- FIXME: shouldn't be eager
|
||||
escapeRegex = mkRegex "\\\\x1[Bb]|\\\\e|\x1B|\\\\033"
|
||||
|
||||
|
||||
return []
|
||||
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
117
src/ShellCheck/Data.hs
Normal file
117
src/ShellCheck/Data.hs
Normal file
|
@ -0,0 +1,117 @@
|
|||
module ShellCheck.Data where
|
||||
|
||||
import ShellCheck.Interface
|
||||
import Data.Version (showVersion)
|
||||
import Paths_ShellCheck (version)
|
||||
|
||||
shellcheckVersion = showVersion version
|
||||
|
||||
internalVariables = [
|
||||
-- Generic
|
||||
"", "_", "rest", "REST",
|
||||
|
||||
-- Bash
|
||||
"BASH", "BASHOPTS", "BASHPID", "BASH_ALIASES", "BASH_ARGC",
|
||||
"BASH_ARGV", "BASH_CMDS", "BASH_COMMAND", "BASH_EXECUTION_STRING",
|
||||
"BASH_LINENO", "BASH_REMATCH", "BASH_SOURCE", "BASH_SUBSHELL",
|
||||
"BASH_VERSINFO", "BASH_VERSION", "COMP_CWORD", "COMP_KEY",
|
||||
"COMP_LINE", "COMP_POINT", "COMP_TYPE", "COMP_WORDBREAKS",
|
||||
"COMP_WORDS", "COPROC", "DIRSTACK", "EUID", "FUNCNAME", "GROUPS",
|
||||
"HISTCMD", "HOSTNAME", "HOSTTYPE", "LINENO", "MACHTYPE", "MAPFILE",
|
||||
"OLDPWD", "OPTARG", "OPTIND", "OSTYPE", "PIPESTATUS", "PPID", "PWD",
|
||||
"RANDOM", "READLINE_LINE", "READLINE_POINT", "REPLY", "SECONDS",
|
||||
"SHELLOPTS", "SHLVL", "UID", "BASH_ENV", "BASH_XTRACEFD", "CDPATH",
|
||||
"COLUMNS", "COMPREPLY", "EMACS", "ENV", "FCEDIT", "FIGNORE",
|
||||
"FUNCNEST", "GLOBIGNORE", "HISTCONTROL", "HISTFILE", "HISTFILESIZE",
|
||||
"HISTIGNORE", "HISTSIZE", "HISTTIMEFORMAT", "HOME", "HOSTFILE", "IFS",
|
||||
"IGNOREEOF", "INPUTRC", "LANG", "LC_ALL", "LC_COLLATE", "LC_CTYPE",
|
||||
"LC_MESSAGES", "LC_MONETARY", "LC_NUMERIC", "LC_TIME", "LINES", "MAIL",
|
||||
"MAILCHECK", "MAILPATH", "OPTERR", "PATH", "POSIXLY_CORRECT",
|
||||
"PROMPT_COMMAND", "PROMPT_DIRTRIM", "PS1", "PS2", "PS3", "PS4", "SHELL",
|
||||
"TIMEFORMAT", "TMOUT", "TMPDIR", "auto_resume", "histchars", "COPROC",
|
||||
|
||||
-- Other
|
||||
"USER", "TZ", "TERM", "LOGNAME", "LD_LIBRARY_PATH", "LANGUAGE", "DISPLAY",
|
||||
"HOSTNAME", "KRB5CCNAME", "XAUTHORITY"
|
||||
|
||||
-- Ksh
|
||||
, ".sh.version"
|
||||
]
|
||||
|
||||
variablesWithoutSpaces = [
|
||||
"$", "-", "?", "!",
|
||||
"BASHPID", "BASH_ARGC", "BASH_LINENO", "BASH_SUBSHELL", "EUID", "LINENO",
|
||||
"OPTIND", "PPID", "RANDOM", "SECONDS", "SHELLOPTS", "SHLVL", "UID",
|
||||
"COLUMNS", "HISTFILESIZE", "HISTSIZE", "LINES"
|
||||
]
|
||||
|
||||
arrayVariables = [
|
||||
"BASH_ALIASES", "BASH_ARGC", "BASH_ARGV", "BASH_CMDS", "BASH_LINENO",
|
||||
"BASH_REMATCH", "BASH_SOURCE", "BASH_VERSINFO", "COMP_WORDS", "COPROC",
|
||||
"DIRSTACK", "FUNCNAME", "GROUPS", "MAPFILE", "PIPESTATUS", "COMPREPLY"
|
||||
]
|
||||
|
||||
commonCommands = [
|
||||
"admin", "alias", "ar", "asa", "at", "awk", "basename", "batch",
|
||||
"bc", "bg", "break", "c99", "cal", "cat", "cd", "cflow", "chgrp",
|
||||
"chmod", "chown", "cksum", "cmp", "colon", "comm", "command",
|
||||
"compress", "continue", "cp", "crontab", "csplit", "ctags", "cut",
|
||||
"cxref", "date", "dd", "delta", "df", "diff", "dirname", "dot",
|
||||
"du", "echo", "ed", "env", "eval", "ex", "exec", "exit", "expand",
|
||||
"export", "expr", "fc", "fg", "file", "find", "fold", "fort77",
|
||||
"fuser", "gencat", "get", "getconf", "getopts", "grep", "hash",
|
||||
"head", "iconv", "ipcrm", "ipcs", "jobs", "join", "kill", "lex",
|
||||
"link", "ln", "locale", "localedef", "logger", "logname", "lp",
|
||||
"ls", "m4", "mailx", "make", "man", "mesg", "mkdir", "mkfifo",
|
||||
"more", "mv", "newgrp", "nice", "nl", "nm", "nohup", "od", "paste",
|
||||
"patch", "pathchk", "pax", "pr", "printf", "prs", "ps", "pwd",
|
||||
"qalter", "qdel", "qhold", "qmove", "qmsg", "qrerun", "qrls",
|
||||
"qselect", "qsig", "qstat", "qsub", "read", "readonly", "renice",
|
||||
"return", "rm", "rmdel", "rmdir", "sact", "sccs", "sed", "set",
|
||||
"sh", "shift", "sleep", "sort", "split", "strings", "strip", "stty",
|
||||
"tabs", "tail", "talk", "tee", "test", "time", "times", "touch",
|
||||
"tput", "tr", "trap", "tsort", "tty", "type", "ulimit", "umask",
|
||||
"unalias", "uname", "uncompress", "unexpand", "unget", "uniq",
|
||||
"unlink", "unset", "uucp", "uudecode", "uuencode", "uustat", "uux",
|
||||
"val", "vi", "wait", "wc", "what", "who", "write", "xargs", "yacc",
|
||||
"zcat"
|
||||
]
|
||||
|
||||
nonReadingCommands = [
|
||||
"alias", "basename", "bg", "cal", "cd", "chgrp", "chmod", "chown",
|
||||
"cp", "du", "echo", "export", "false", "fg", "fuser", "getconf",
|
||||
"getopt", "getopts", "ipcrm", "ipcs", "jobs", "kill", "ln", "ls",
|
||||
"locale", "mv", "nice", "printf", "ps", "pwd", "renice", "rm", "rmdir",
|
||||
"set", "sleep", "touch", "trap", "true", "ulimit", "unalias", "uname"
|
||||
]
|
||||
|
||||
sampleWords = [
|
||||
"alpha", "bravo", "charlie", "delta", "echo", "foxtrot",
|
||||
"golf", "hotel", "india", "juliett", "kilo", "lima", "mike",
|
||||
"november", "oscar", "papa", "quebec", "romeo", "sierra",
|
||||
"tango", "uniform", "victor", "whiskey", "xray", "yankee",
|
||||
"zulu"
|
||||
]
|
||||
|
||||
binaryTestOps = [
|
||||
"-nt", "-ot", "-ef", "==", "!=", "<=", ">=", "-eq", "-ne", "-lt", "-le",
|
||||
"-gt", "-ge", "=~", ">", "<", "=", "\\<", "\\>", "\\<=", "\\>="
|
||||
]
|
||||
|
||||
unaryTestOps = [
|
||||
"!", "-a", "-b", "-c", "-d", "-e", "-f", "-g", "-h", "-L", "-k", "-p",
|
||||
"-r", "-s", "-S", "-t", "-u", "-w", "-x", "-O", "-G", "-N", "-z", "-n",
|
||||
"-o", "-v", "-R"
|
||||
]
|
||||
|
||||
shellForExecutable :: String -> Maybe Shell
|
||||
shellForExecutable name =
|
||||
case name of
|
||||
"sh" -> return Sh
|
||||
"bash" -> return Bash
|
||||
"dash" -> return Dash
|
||||
"ash" -> return Dash -- There's also a warning for this.
|
||||
"ksh" -> return Ksh
|
||||
"ksh88" -> return Ksh
|
||||
"ksh93" -> return Ksh
|
||||
otherwise -> Nothing
|
95
src/ShellCheck/Formatter/CheckStyle.hs
Normal file
95
src/ShellCheck/Formatter/CheckStyle.hs
Normal file
|
@ -0,0 +1,95 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
module ShellCheck.Formatter.CheckStyle (format) where
|
||||
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.Formatter.Format
|
||||
|
||||
import Data.Char
|
||||
import Data.List
|
||||
import GHC.Exts
|
||||
import System.IO
|
||||
|
||||
format :: IO Formatter
|
||||
format = return Formatter {
|
||||
header = do
|
||||
putStrLn "<?xml version='1.0' encoding='UTF-8'?>"
|
||||
putStrLn "<checkstyle version='4.3'>",
|
||||
|
||||
onFailure = outputError,
|
||||
onResult = outputResults,
|
||||
|
||||
footer = putStrLn "</checkstyle>"
|
||||
}
|
||||
|
||||
outputResults cr sys =
|
||||
if null comments
|
||||
then outputFile (crFilename cr) "" []
|
||||
else mapM_ outputGroup fileGroups
|
||||
where
|
||||
comments = crComments cr
|
||||
fileGroups = groupWith sourceFile comments
|
||||
outputGroup group = do
|
||||
let filename = sourceFile (head group)
|
||||
result <- (siReadFile sys) filename
|
||||
let contents = either (const "") id result
|
||||
outputFile filename contents group
|
||||
|
||||
outputFile filename contents warnings = do
|
||||
let comments = makeNonVirtual warnings contents
|
||||
putStrLn . formatFile filename $ comments
|
||||
|
||||
formatFile name comments = concat [
|
||||
"<file ", attr "name" name, ">\n",
|
||||
concatMap formatComment comments,
|
||||
"</file>"
|
||||
]
|
||||
|
||||
formatComment c = concat [
|
||||
"<error ",
|
||||
attr "line" $ show . lineNo $ c,
|
||||
attr "column" $ show . colNo $ c,
|
||||
attr "severity" . severity $ severityText c,
|
||||
attr "message" $ messageText c,
|
||||
attr "source" $ "ShellCheck.SC" ++ show (codeNo c),
|
||||
"/>\n"
|
||||
]
|
||||
|
||||
outputError file error = putStrLn $ concat [
|
||||
"<file ", attr "name" file, ">\n",
|
||||
"<error ",
|
||||
attr "line" "1",
|
||||
attr "column" "1",
|
||||
attr "severity" "error",
|
||||
attr "message" error,
|
||||
attr "source" "ShellCheck",
|
||||
"/>\n",
|
||||
"</file>"
|
||||
]
|
||||
|
||||
|
||||
attr s v = concat [ s, "='", escape v, "' " ]
|
||||
escape = concatMap escape'
|
||||
escape' c = if isOk c then [c] else "&#" ++ show (ord c) ++ ";"
|
||||
isOk x = any ($x) [isAsciiUpper, isAsciiLower, isDigit, (`elem` " ./")]
|
||||
|
||||
severity "error" = "error"
|
||||
severity "warning" = "warning"
|
||||
severity _ = "info"
|
67
src/ShellCheck/Formatter/Format.hs
Normal file
67
src/ShellCheck/Formatter/Format.hs
Normal file
|
@ -0,0 +1,67 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
module ShellCheck.Formatter.Format where
|
||||
|
||||
import ShellCheck.Data
|
||||
import ShellCheck.Interface
|
||||
|
||||
-- A formatter that carries along an arbitrary piece of data
|
||||
data Formatter = Formatter {
|
||||
header :: IO (),
|
||||
onResult :: CheckResult -> SystemInterface IO -> IO (),
|
||||
onFailure :: FilePath -> ErrorMessage -> IO (),
|
||||
footer :: IO ()
|
||||
}
|
||||
|
||||
sourceFile (PositionedComment pos _ _) = posFile pos
|
||||
lineNo (PositionedComment pos _ _) = posLine pos
|
||||
endLineNo (PositionedComment _ end _) = posLine end
|
||||
colNo (PositionedComment pos _ _) = posColumn pos
|
||||
endColNo (PositionedComment _ end _) = posColumn end
|
||||
codeNo (PositionedComment _ _ (Comment _ code _)) = code
|
||||
messageText (PositionedComment _ _ (Comment _ _ t)) = t
|
||||
|
||||
severityText :: PositionedComment -> String
|
||||
severityText (PositionedComment _ _ (Comment c _ _)) =
|
||||
case c of
|
||||
ErrorC -> "error"
|
||||
WarningC -> "warning"
|
||||
InfoC -> "info"
|
||||
StyleC -> "style"
|
||||
|
||||
-- Realign comments from a tabstop of 8 to 1
|
||||
makeNonVirtual comments contents =
|
||||
map fix comments
|
||||
where
|
||||
ls = lines contents
|
||||
fix c@(PositionedComment start end comment) = PositionedComment start {
|
||||
posColumn = realignColumn lineNo colNo c
|
||||
} end {
|
||||
posColumn = realignColumn endLineNo endColNo c
|
||||
} comment
|
||||
realignColumn lineNo colNo c =
|
||||
if lineNo c > 0 && lineNo c <= fromIntegral (length ls)
|
||||
then real (ls !! fromIntegral (lineNo c - 1)) 0 0 (colNo c)
|
||||
else colNo c
|
||||
real _ r v target | target <= v = r
|
||||
real [] r v _ = r -- should never happen
|
||||
real ('\t':rest) r v target =
|
||||
real rest (r+1) (v + 8 - (v `mod` 8)) target
|
||||
real (_:rest) r v target = real rest (r+1) (v+1) target
|
65
src/ShellCheck/Formatter/GCC.hs
Normal file
65
src/ShellCheck/Formatter/GCC.hs
Normal file
|
@ -0,0 +1,65 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
module ShellCheck.Formatter.GCC (format) where
|
||||
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.Formatter.Format
|
||||
|
||||
import Data.List
|
||||
import GHC.Exts
|
||||
import System.IO
|
||||
|
||||
format :: IO Formatter
|
||||
format = return Formatter {
|
||||
header = return (),
|
||||
footer = return (),
|
||||
onFailure = outputError,
|
||||
onResult = outputAll
|
||||
}
|
||||
|
||||
outputError file error = hPutStrLn stderr $ file ++ ": " ++ error
|
||||
|
||||
outputAll cr sys = mapM_ f groups
|
||||
where
|
||||
comments = crComments cr
|
||||
groups = groupWith sourceFile comments
|
||||
f :: [PositionedComment] -> IO ()
|
||||
f group = do
|
||||
let filename = sourceFile (head group)
|
||||
result <- (siReadFile sys) filename
|
||||
let contents = either (const "") id result
|
||||
outputResult filename contents group
|
||||
|
||||
outputResult filename contents warnings = do
|
||||
let comments = makeNonVirtual warnings contents
|
||||
mapM_ (putStrLn . formatComment filename) comments
|
||||
|
||||
formatComment filename c = concat [
|
||||
filename, ":",
|
||||
show $ lineNo c, ":",
|
||||
show $ colNo c, ": ",
|
||||
case severityText c of
|
||||
"error" -> "error"
|
||||
"warning" -> "warning"
|
||||
_ -> "note",
|
||||
": ",
|
||||
concat . lines $ messageText c,
|
||||
" [SC", show $ codeNo c, "]"
|
||||
]
|
60
src/ShellCheck/Formatter/JSON.hs
Normal file
60
src/ShellCheck/Formatter/JSON.hs
Normal file
|
@ -0,0 +1,60 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
module ShellCheck.Formatter.JSON (format) where
|
||||
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.Formatter.Format
|
||||
|
||||
import Data.IORef
|
||||
import GHC.Exts
|
||||
import System.IO
|
||||
import Text.JSON
|
||||
|
||||
format = do
|
||||
ref <- newIORef []
|
||||
return Formatter {
|
||||
header = return (),
|
||||
onResult = collectResult ref,
|
||||
onFailure = outputError,
|
||||
footer = finish ref
|
||||
}
|
||||
|
||||
instance JSON (PositionedComment) where
|
||||
showJSON comment@(PositionedComment start end (Comment level code string)) = makeObj [
|
||||
("file", showJSON $ posFile start),
|
||||
("line", showJSON $ posLine start),
|
||||
("endLine", showJSON $ posLine end),
|
||||
("column", showJSON $ posColumn start),
|
||||
("endColumn", showJSON $ posColumn end),
|
||||
("level", showJSON $ severityText comment),
|
||||
("code", showJSON code),
|
||||
("message", showJSON string)
|
||||
]
|
||||
|
||||
readJSON = undefined
|
||||
|
||||
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
||||
collectResult ref result _ =
|
||||
modifyIORef ref (\x -> crComments result ++ x)
|
||||
|
||||
finish ref = do
|
||||
list <- readIORef ref
|
||||
putStrLn $ encodeStrict list
|
||||
|
98
src/ShellCheck/Formatter/TTY.hs
Normal file
98
src/ShellCheck/Formatter/TTY.hs
Normal file
|
@ -0,0 +1,98 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
module ShellCheck.Formatter.TTY (format) where
|
||||
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.Formatter.Format
|
||||
|
||||
import Data.List
|
||||
import GHC.Exts
|
||||
import System.Info
|
||||
import System.IO
|
||||
|
||||
format :: FormatterOptions -> IO Formatter
|
||||
format options = return Formatter {
|
||||
header = return (),
|
||||
footer = return (),
|
||||
onFailure = outputError options,
|
||||
onResult = outputResult options
|
||||
}
|
||||
|
||||
colorForLevel level =
|
||||
case level of
|
||||
"error" -> 31 -- red
|
||||
"warning" -> 33 -- yellow
|
||||
"info" -> 32 -- green
|
||||
"style" -> 32 -- green
|
||||
"message" -> 1 -- bold
|
||||
"source" -> 0 -- none
|
||||
_ -> 0 -- none
|
||||
|
||||
outputError options file error = do
|
||||
color <- getColorFunc $ foColorOption options
|
||||
hPutStrLn stderr $ color "error" $ file ++ ": " ++ error
|
||||
|
||||
outputResult options result sys = do
|
||||
color <- getColorFunc $ foColorOption options
|
||||
let comments = crComments result
|
||||
let fileGroups = groupWith sourceFile comments
|
||||
mapM_ (outputForFile color sys) fileGroups
|
||||
|
||||
outputForFile color sys comments = do
|
||||
let fileName = sourceFile (head comments)
|
||||
result <- (siReadFile sys) fileName
|
||||
let contents = either (const "") id result
|
||||
let fileLines = lines contents
|
||||
let lineCount = fromIntegral $ length fileLines
|
||||
let groups = groupWith lineNo comments
|
||||
mapM_ (\x -> do
|
||||
let lineNum = lineNo (head x)
|
||||
let line = if lineNum < 1 || lineNum > lineCount
|
||||
then ""
|
||||
else fileLines !! fromIntegral (lineNum - 1)
|
||||
putStrLn ""
|
||||
putStrLn $ color "message" $
|
||||
"In " ++ fileName ++" line " ++ show lineNum ++ ":"
|
||||
putStrLn (color "source" line)
|
||||
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) x
|
||||
putStrLn ""
|
||||
) groups
|
||||
|
||||
cuteIndent :: PositionedComment -> String
|
||||
cuteIndent comment =
|
||||
replicate (fromIntegral $ colNo comment - 1) ' ' ++
|
||||
"^-- " ++ code (codeNo comment) ++ ": " ++ messageText comment
|
||||
|
||||
code code = "SC" ++ show code
|
||||
|
||||
getColorFunc colorOption = do
|
||||
term <- hIsTerminalDevice stdout
|
||||
let windows = "mingw" `isPrefixOf` os
|
||||
let isUsableTty = term && not windows
|
||||
let useColor = case colorOption of
|
||||
ColorAlways -> True
|
||||
ColorNever -> False
|
||||
ColorAuto -> isUsableTty
|
||||
return $ if useColor then colorComment else const id
|
||||
where
|
||||
colorComment level comment =
|
||||
ansi (colorForLevel level) ++ comment ++ clear
|
||||
clear = ansi 0
|
||||
ansi n = "\x1B[" ++ show n ++ "m"
|
121
src/ShellCheck/Interface.hs
Normal file
121
src/ShellCheck/Interface.hs
Normal file
|
@ -0,0 +1,121 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
module ShellCheck.Interface where
|
||||
|
||||
import ShellCheck.AST
|
||||
import Control.Monad.Identity
|
||||
import qualified Data.Map as Map
|
||||
|
||||
|
||||
newtype SystemInterface m = SystemInterface {
|
||||
-- Read a file by filename, or return an error
|
||||
siReadFile :: String -> m (Either ErrorMessage String)
|
||||
}
|
||||
|
||||
-- ShellCheck input and output
|
||||
data CheckSpec = CheckSpec {
|
||||
csFilename :: String,
|
||||
csScript :: String,
|
||||
csCheckSourced :: Bool,
|
||||
csExcludedWarnings :: [Integer],
|
||||
csShellTypeOverride :: Maybe Shell
|
||||
} deriving (Show, Eq)
|
||||
|
||||
data CheckResult = CheckResult {
|
||||
crFilename :: String,
|
||||
crComments :: [PositionedComment]
|
||||
} deriving (Show, Eq)
|
||||
|
||||
emptyCheckSpec :: CheckSpec
|
||||
emptyCheckSpec = CheckSpec {
|
||||
csFilename = "",
|
||||
csScript = "",
|
||||
csCheckSourced = False,
|
||||
csExcludedWarnings = [],
|
||||
csShellTypeOverride = Nothing
|
||||
}
|
||||
|
||||
-- Parser input and output
|
||||
data ParseSpec = ParseSpec {
|
||||
psFilename :: String,
|
||||
psScript :: String,
|
||||
psCheckSourced :: Bool
|
||||
} deriving (Show, Eq)
|
||||
|
||||
data ParseResult = ParseResult {
|
||||
prComments :: [PositionedComment],
|
||||
prTokenPositions :: Map.Map Id Position,
|
||||
prRoot :: Maybe Token
|
||||
} deriving (Show, Eq)
|
||||
|
||||
-- Analyzer input and output
|
||||
data AnalysisSpec = AnalysisSpec {
|
||||
asScript :: Token,
|
||||
asShellType :: Maybe Shell,
|
||||
asExecutionMode :: ExecutionMode,
|
||||
asCheckSourced :: Bool
|
||||
}
|
||||
|
||||
newtype AnalysisResult = AnalysisResult {
|
||||
arComments :: [TokenComment]
|
||||
}
|
||||
|
||||
|
||||
-- Formatter options
|
||||
newtype FormatterOptions = FormatterOptions {
|
||||
foColorOption :: ColorOption
|
||||
}
|
||||
|
||||
|
||||
-- Supporting data types
|
||||
data Shell = Ksh | Sh | Bash | Dash deriving (Show, Eq)
|
||||
data ExecutionMode = Executed | Sourced deriving (Show, Eq)
|
||||
|
||||
type ErrorMessage = String
|
||||
type Code = Integer
|
||||
|
||||
data Severity = ErrorC | WarningC | InfoC | StyleC deriving (Show, Eq, Ord)
|
||||
data Position = Position {
|
||||
posFile :: String, -- Filename
|
||||
posLine :: Integer, -- 1 based source line
|
||||
posColumn :: Integer -- 1 based source column, where tabs are 8
|
||||
} deriving (Show, Eq)
|
||||
|
||||
data Comment = Comment Severity Code String deriving (Show, Eq)
|
||||
data PositionedComment = PositionedComment Position Position Comment deriving (Show, Eq)
|
||||
data TokenComment = TokenComment Id Comment deriving (Show, Eq)
|
||||
|
||||
data ColorOption =
|
||||
ColorAuto
|
||||
| ColorAlways
|
||||
| ColorNever
|
||||
deriving (Ord, Eq, Show)
|
||||
|
||||
-- For testing
|
||||
mockedSystemInterface :: [(String, String)] -> SystemInterface Identity
|
||||
mockedSystemInterface files = SystemInterface {
|
||||
siReadFile = rf
|
||||
}
|
||||
where
|
||||
rf file =
|
||||
case filter ((== file) . fst) files of
|
||||
[] -> return $ Left "File not included in mock."
|
||||
[(_, contents)] -> return $ Right contents
|
||||
|
3060
src/ShellCheck/Parser.hs
Normal file
3060
src/ShellCheck/Parser.hs
Normal file
File diff suppressed because it is too large
Load diff
80
src/ShellCheck/Regex.hs
Normal file
80
src/ShellCheck/Regex.hs
Normal file
|
@ -0,0 +1,80 @@
|
|||
{-
|
||||
Copyright 2012-2015 Vidar Holen
|
||||
|
||||
This file is part of ShellCheck.
|
||||
https://www.shellcheck.net
|
||||
|
||||
ShellCheck is free software: you can redistribute it and/or modify
|
||||
it under the terms of the GNU 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 General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||
-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
|
||||
-- Basically Text.Regex based on regex-tdfa instead of the buggy regex-posix.
|
||||
module ShellCheck.Regex where
|
||||
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Control.Monad
|
||||
import Text.Regex.TDFA
|
||||
|
||||
-- Precompile the regex
|
||||
mkRegex :: String -> Regex
|
||||
mkRegex str =
|
||||
let make :: RegexMaker Regex CompOption ExecOption String => String -> Regex
|
||||
make = makeRegex
|
||||
in
|
||||
make str
|
||||
|
||||
-- Does the regex match?
|
||||
matches :: String -> Regex -> Bool
|
||||
matches = flip match
|
||||
|
||||
-- Get all subgroups of the first match
|
||||
matchRegex :: Regex -> String -> Maybe [String]
|
||||
matchRegex re str = do
|
||||
(_, _, _, groups) <- matchM re str :: Maybe (String,String,String,[String])
|
||||
return groups
|
||||
|
||||
-- Get all full matches
|
||||
matchAllStrings :: Regex -> String -> [String]
|
||||
matchAllStrings re = unfoldr f
|
||||
where
|
||||
f :: String -> Maybe (String, String)
|
||||
f str = do
|
||||
(_, match, rest, _) <- matchM re str :: Maybe (String, String, String, [String])
|
||||
return (match, rest)
|
||||
|
||||
-- Get all subgroups from all matches
|
||||
matchAllSubgroups :: Regex -> String -> [[String]]
|
||||
matchAllSubgroups re = unfoldr f
|
||||
where
|
||||
f :: String -> Maybe ([String], String)
|
||||
f str = do
|
||||
(_, _, rest, groups) <- matchM re str :: Maybe (String, String, String, [String])
|
||||
return (groups, rest)
|
||||
|
||||
-- Replace regex in input with string
|
||||
subRegex :: Regex -> String -> String -> String
|
||||
subRegex re input replacement = f input
|
||||
where
|
||||
f str = fromMaybe str $ do
|
||||
(before, match, after) <- matchM re str :: Maybe (String, String, String)
|
||||
when (null match) $ error ("Internal error: substituted empty in " ++ str)
|
||||
return $ before ++ replacement ++ f after
|
||||
|
||||
-- Split a string based on a regex.
|
||||
splitOn :: String -> Regex -> [String]
|
||||
splitOn input re =
|
||||
case matchM re input :: Maybe (String, String, String) of
|
||||
Just (before, match, after) -> before : after `splitOn` re
|
||||
Nothing -> [input]
|
Loading…
Add table
Add a link
Reference in a new issue