Added recursive parsing support for `..`

This commit is contained in:
Vidar Holen 2013-06-26 21:04:39 -07:00
parent 25ee7e20f4
commit f820298b6e
3 changed files with 55 additions and 12 deletions

View File

@ -23,7 +23,7 @@ import qualified Text.Regex as Re
data Id = Id Int deriving (Show, Eq, Ord)
data Token = T_AND_IF Id | T_OR_IF Id | T_DSEMI Id | T_Semi Id | T_DLESS Id | T_DGREAT Id | T_LESSAND Id | T_GREATAND Id | T_LESSGREAT Id | T_DLESSDASH Id | T_CLOBBER Id | T_If Id | T_Then Id | T_Else Id | T_Elif Id | T_Fi Id | T_Do Id | T_Done Id | T_Case Id | T_Esac Id | T_While Id | T_Until Id | T_For Id | T_Select Id | T_Lbrace Id | T_Rbrace Id | T_Lparen Id | T_Rparen Id | T_Bang Id | T_In Id | T_NEWLINE Id | T_EOF Id | T_Less Id | T_Greater Id | T_SingleQuoted Id String | T_Literal Id String | T_NormalWord Id [Token] | T_DoubleQuoted Id [Token] | T_DollarExpansion Id [Token] | T_DollarBraced Id Token | T_DollarArithmetic Id Token | T_BraceExpansion Id String | T_IoFile Id Token Token | T_HereDoc Id Bool Bool String | T_HereString Id Token | T_FdRedirect Id String Token | T_Assignment Id String Token | T_Array Id [Token] | T_Redirecting Id [Token] Token | T_SimpleCommand Id [Token] [Token] | T_Pipeline Id [Token] | T_Banged Id Token | T_AndIf Id (Token) (Token) | T_OrIf Id (Token) (Token) | T_Backgrounded Id Token | T_IfExpression Id [([Token],[Token])] [Token] | T_Subshell Id [Token] | T_BraceGroup Id [Token] | T_WhileExpression Id [Token] [Token] | T_UntilExpression Id [Token] [Token] | T_ForIn Id String [Token] [Token] | T_SelectIn Id String [Token] [Token] | T_CaseExpression Id Token [([Token],[Token])] | T_Function Id String Token | T_Arithmetic Id Token | T_Script Id String [Token] | T_Condition Id ConditionType Token | T_Extglob Id String [Token] | TC_And Id ConditionType String Token Token | TC_Or Id ConditionType String Token Token | TC_Group Id ConditionType Token | TC_Binary Id ConditionType String Token Token | TC_Unary Id ConditionType String Token | TC_Noary Id ConditionType Token | TA_Binary Id String Token Token | TA_Unary Id String Token | TA_Sequence Id [Token] | TA_Variable Id String | TA_Trinary Id Token Token Token | TA_Expansion Id Token | TA_Literal Id String | T_Backticked Id String | T_ProcSub Id String [Token] | T_Glob Id String | T_ForArithmetic Id Token Token Token [Token] | T_DollarSingleQuoted Id String | T_DollarDoubleQuoted Id [Token] | TA_Base Id String Token
data Token = T_AND_IF Id | T_OR_IF Id | T_DSEMI Id | T_Semi Id | T_DLESS Id | T_DGREAT Id | T_LESSAND Id | T_GREATAND Id | T_LESSGREAT Id | T_DLESSDASH Id | T_CLOBBER Id | T_If Id | T_Then Id | T_Else Id | T_Elif Id | T_Fi Id | T_Do Id | T_Done Id | T_Case Id | T_Esac Id | T_While Id | T_Until Id | T_For Id | T_Select Id | T_Lbrace Id | T_Rbrace Id | T_Lparen Id | T_Rparen Id | T_Bang Id | T_In Id | T_NEWLINE Id | T_EOF Id | T_Less Id | T_Greater Id | T_SingleQuoted Id String | T_Literal Id String | T_NormalWord Id [Token] | T_DoubleQuoted Id [Token] | T_DollarExpansion Id [Token] | T_DollarBraced Id Token | T_DollarArithmetic Id Token | T_BraceExpansion Id String | T_IoFile Id Token Token | T_HereDoc Id Bool Bool String | T_HereString Id Token | T_FdRedirect Id String Token | T_Assignment Id String Token | T_Array Id [Token] | T_Redirecting Id [Token] Token | T_SimpleCommand Id [Token] [Token] | T_Pipeline Id [Token] | T_Banged Id Token | T_AndIf Id (Token) (Token) | T_OrIf Id (Token) (Token) | T_Backgrounded Id Token | T_IfExpression Id [([Token],[Token])] [Token] | T_Subshell Id [Token] | T_BraceGroup Id [Token] | T_WhileExpression Id [Token] [Token] | T_UntilExpression Id [Token] [Token] | T_ForIn Id String [Token] [Token] | T_SelectIn Id String [Token] [Token] | T_CaseExpression Id Token [([Token],[Token])] | T_Function Id String Token | T_Arithmetic Id Token | T_Script Id String [Token] | T_Condition Id ConditionType Token | T_Extglob Id String [Token] | TC_And Id ConditionType String Token Token | TC_Or Id ConditionType String Token Token | TC_Group Id ConditionType Token | TC_Binary Id ConditionType String Token Token | TC_Unary Id ConditionType String Token | TC_Noary Id ConditionType Token | TA_Binary Id String Token Token | TA_Unary Id String Token | TA_Sequence Id [Token] | TA_Variable Id String | TA_Trinary Id Token Token Token | TA_Expansion Id Token | TA_Literal Id String | T_Backticked Id [Token] | T_ProcSub Id String [Token] | T_Glob Id String | T_ForArithmetic Id Token Token Token [Token] | T_DollarSingleQuoted Id String | T_DollarDoubleQuoted Id [Token] | TA_Base Id String Token
deriving (Show)
@ -65,6 +65,7 @@ analyze f g i t =
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_Backticked id list) = dl list $ T_Backticked id
delve (T_DollarArithmetic id c) = d1 c $ T_DollarArithmetic id
delve (T_IoFile id op file) = d2 op file $ T_IoFile id
delve (T_HereString id word) = d1 word $ T_HereString id

View File

@ -119,6 +119,7 @@ basicChecks = [
,checkIndirectExpansion
,checkSudoRedirect
,checkPS1Assignments
,checkBackticks
]
treeChecks = [
checkUnquotedExpansions
@ -364,23 +365,36 @@ checkForInQuoted (T_ForIn _ f [T_NormalWord _ [T_Literal id s]] _) =
checkForInQuoted _ = return ()
prop_checkForInCat1 = verify checkForInCat "for f in $(cat foo); do stuff; done"
prop_checkForInCat1a= verify checkForInCat "for f in `cat foo`; do stuff; done"
prop_checkForInCat2 = verify checkForInCat "for f in $(cat foo | grep lol); do stuff; done"
prop_checkForInCat2a= verify checkForInCat "for f in `cat foo | grep lol`; do stuff; done"
prop_checkForInCat3 = verifyNot checkForInCat "for f in $(cat foo | grep bar | wc -l); do stuff; done"
checkForInCat (T_ForIn _ f [T_NormalWord _ w] _) = mapM_ checkF w
where
checkF (T_DollarExpansion id [T_Pipeline _ r])
| all isLineBased r =
info id $ "To read lines rather than words, pipe/redirect to a 'while read' loop."
checkF (T_Backticked id cmds) = checkF (T_DollarExpansion id cmds)
checkF _ = return ()
isLineBased cmd = any (cmd `isCommand`) ["grep", "sed", "cat"]
checkForInCat _ = return ()
prop_checkForInLs = verify checkForInLs "for f in $(ls *.mp3); do mplayer \"$f\"; done"
checkForInLs (T_ForIn _ f [T_NormalWord _ [T_DollarExpansion id [x]]] _) =
case deadSimple x of ("ls":n) -> let args = (if n == [] then ["*"] else n) in
err id $ "Don't use 'for "++f++" in $(ls " ++ (intercalate " " n) ++ ")'. Use 'for "++f++" in "++ (intercalate " " args) ++ "'."
_ -> return ()
checkForInLs _ = return ()
prop_checkForInLs2 = verify checkForInLs "for f in `ls *.mp3`; do mplayer \"$f\"; done"
checkForInLs t = try t
where
try (T_ForIn _ f [T_NormalWord _ [T_DollarExpansion id [x]]] _) =
check id f x
try (T_ForIn _ f [T_NormalWord _ [T_Backticked id [x]]] _) =
check id f x
try _ = return ()
check id f x =
case deadSimple x of
("ls":n) ->
let args = (if n == [] then ["*"] else n) in
err id $ "Don't use 'for "++f++" in $(ls " ++ (intercalate " " n)
++ ")'. Use 'for "++f++" in "++ (intercalate " " args) ++ "'."
_ -> return ()
prop_checkFindExec1 = verify checkFindExec "find / -name '*.php' -exec rm {};"
@ -425,6 +439,7 @@ checkFindExec _ = return ()
prop_checkUnquotedExpansions1 = verifyTree checkUnquotedExpansions "rm $(ls)"
prop_checkUnquotedExpansions1a= verifyTree checkUnquotedExpansions "rm `ls`"
prop_checkUnquotedExpansions2 = verifyTree checkUnquotedExpansions "rm foo$(date)"
prop_checkUnquotedExpansions3 = verifyTree checkUnquotedExpansions "[ $(foo) == cow ]"
prop_checkUnquotedExpansions3a= verifyTree checkUnquotedExpansions "[ ! $(foo) ]"
@ -438,6 +453,7 @@ checkUnquotedExpansions t tree =
check _ = return ()
check' t@(T_DollarExpansion id _) = unless (inUnquotableContext tree t) $ msg id
check' t@(T_Backticked id _) = unless (inUnquotableContext tree t) $ msg id
check' _ = return ()
prop_checkRedirectToSame = verify checkRedirectToSame "cat foo > foo"
@ -820,12 +836,16 @@ checkPrintfVar = checkUnqualifiedCommand "printf" f where
else return ()
prop_checkUuoe1 = verify checkUuoe "echo $(date)"
prop_checkUuoe1a= verify checkUuoe "echo `date`"
prop_checkUuoe2 = verify checkUuoe "echo \"$(date)\""
prop_checkUuoe2a= verify checkUuoe "echo \"`date`\""
prop_checkUuoe3 = verifyNot checkUuoe "echo \"The time is $(date)\""
checkUuoe = checkUnqualifiedCommand "echo" f where
msg id = style id "Useless echo? Instead of 'echo $(cmd)', just use 'cmd'."
f [T_NormalWord id [(T_DollarExpansion _ _)]] = msg id
f [T_NormalWord id [T_DoubleQuoted _ [(T_DollarExpansion _ _)]]] = msg id
f [T_NormalWord id [(T_Backticked _ _)]] = msg id
f [T_NormalWord id [T_DoubleQuoted _ [(T_Backticked _ _)]]] = msg id
f _ = return ()
prop_checkTr1 = verify checkTr "tr [a-f] [A-F]"
@ -907,6 +927,7 @@ checkGrepRe = checkCommand "grep" f where
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 = checkCommand "trap" f where
@ -916,6 +937,7 @@ checkTrapQuotes = checkCommand "trap" f where
checkTrap _ = return ()
warning id = warn id $ "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 ()
@ -989,10 +1011,17 @@ checkPS1Assignments t =
enclosedRegex = mkRegex "\\\\\\[.*\\\\\\]" -- FIXME: shouldn't be eager
escapeRegex = mkRegex "\\x1[Bb]|\\e|\x1B|\\033"
prop_checkBackticks1 = verify checkBackticks "echo `foo`"
prop_checkBackticks2 = verifyNot checkBackticks "echo $(foo)"
checkBackticks (T_Backticked id _) =
style id "Use $(..) instead of deprecated `..`"
checkBackticks _ = return ()
prop_checkIndirectExpansion1 = verify checkIndirectExpansion "${foo$n}"
prop_checkIndirectExpansion2 = verifyNot checkIndirectExpansion "${foo//$n/lol}"
checkIndirectExpansion (T_DollarBraced id (T_NormalWord _ ((T_Literal _ s):attempt:_))) =
case attempt of T_DollarExpansion _ _ -> doit
T_Backticked _ _ -> doit
T_DollarBraced _ _ -> doit
T_DollarArithmetic _ _ -> doit
_ -> return ()
@ -1038,6 +1067,7 @@ data VariableState = Dead Token String | Alive deriving (Show, Eq)
leadType t =
case t of
T_DollarExpansion _ _ -> SubshellScope "$(..) expansion"
T_Backticked _ _ -> SubshellScope "`..` expansion"
T_Backgrounded _ _ -> SubshellScope "backgrounding &"
T_Subshell _ _ -> SubshellScope "(..) group"
-- This considers the whole pipeline one subshell. Consider fixing.
@ -1227,7 +1257,8 @@ checkSpacefulness t =
isSpaceful :: (String -> Bool) -> Token -> Bool
isSpaceful spacefulF x =
case x of
T_DollarExpansion _ _ -> True
T_DollarExpansion _ _ -> True
T_Backticked _ _ -> True
T_Glob _ _ -> True
T_Extglob _ _ _ -> True
T_Literal _ s -> s `containsAny` globspace

View File

@ -656,16 +656,27 @@ readSingleQuotedPart =
readSingleEscaped
<|> anyChar `reluctantlyTill1` (singleQuote <|> backslash)
prop_readBackTicked = isWarning readBackTicked "`ls *.mp3`"
prop_readBackTicked = isOk readBackTicked "`ls *.mp3`"
readBackTicked = called "backtick expansion" $ do
id <- getNextId
parseNote WarningC "Use $(..) instead of deprecated `..` backtick expansion."
pos <- getPosition
char '`'
f <- readGenericLiteral (char '`')
subStart <- getPosition
subString <- readGenericLiteral (char '`')
char '`'
return $ T_Backticked id f
result <- subParse subStart readCompoundList subString
return $ T_Backticked id result
where
-- Position may be off due to escapes
subParse pos parser input = do
lastPosition <- getPosition
lastInput <- getInput
setPosition pos
setInput input
result <- parser
setInput lastInput
setPosition lastPosition
return result
prop_readDoubleQuoted = isOk readDoubleQuoted "\"Hello $FOO\""
readDoubleQuoted = called "double quoted string" $ do