Replaced parser error for 'function' with shell-aware check.
This commit is contained in:
parent
6a4a5a815e
commit
075d58ee90
|
@ -26,6 +26,8 @@ data Id = Id Int deriving (Show, Eq, Ord)
|
||||||
data Quoted = Quoted | Unquoted deriving (Show, Eq)
|
data Quoted = Quoted | Unquoted deriving (Show, Eq)
|
||||||
data Dashed = Dashed | Undashed deriving (Show, Eq)
|
data Dashed = Dashed | Undashed deriving (Show, Eq)
|
||||||
data AssignmentMode = Assign | Append deriving (Show, Eq)
|
data AssignmentMode = Assign | Append deriving (Show, Eq)
|
||||||
|
data FunctionKeyword = FunctionKeyword Bool deriving (Show, Eq)
|
||||||
|
data FunctionParentheses = FunctionParentheses Bool deriving (Show, Eq)
|
||||||
|
|
||||||
data Token =
|
data Token =
|
||||||
TA_Base Id String Token
|
TA_Base Id String Token
|
||||||
|
@ -80,7 +82,7 @@ data Token =
|
||||||
| T_For Id
|
| T_For Id
|
||||||
| T_ForArithmetic Id Token Token Token [Token]
|
| T_ForArithmetic Id Token Token Token [Token]
|
||||||
| T_ForIn Id String [Token] [Token]
|
| T_ForIn Id String [Token] [Token]
|
||||||
| T_Function Id String Token
|
| T_Function Id FunctionKeyword FunctionParentheses String Token
|
||||||
| T_GREATAND Id
|
| T_GREATAND Id
|
||||||
| T_Glob Id String
|
| T_Glob Id String
|
||||||
| T_Greater Id
|
| T_Greater Id
|
||||||
|
@ -218,7 +220,7 @@ analyze f g i t =
|
||||||
return $ T_ForArithmetic id x y z list
|
return $ T_ForArithmetic id x y z list
|
||||||
|
|
||||||
delve (T_Script id s l) = dl l $ T_Script id s
|
delve (T_Script id s l) = dl l $ T_Script id s
|
||||||
delve (T_Function id name body) = d1 body $ T_Function id name
|
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_Condition id typ token) = d1 token $ T_Condition id typ
|
||||||
delve (T_Extglob id str l) = dl l $ T_Extglob id str
|
delve (T_Extglob id str l) = dl l $ T_Extglob id str
|
||||||
delve (T_DollarBraced id op) = d1 op $ T_DollarBraced id
|
delve (T_DollarBraced id op) = d1 op $ T_DollarBraced id
|
||||||
|
@ -308,7 +310,7 @@ getId t = case t of
|
||||||
T_ForIn id _ _ _ -> id
|
T_ForIn id _ _ _ -> id
|
||||||
T_SelectIn id _ _ _ -> id
|
T_SelectIn id _ _ _ -> id
|
||||||
T_CaseExpression id _ _ -> id
|
T_CaseExpression id _ _ -> id
|
||||||
T_Function id _ _ -> id
|
T_Function id _ _ _ _ -> id
|
||||||
T_Arithmetic id _ -> id
|
T_Arithmetic id _ -> id
|
||||||
T_Script id _ _ -> id
|
T_Script id _ _ -> id
|
||||||
T_Condition id _ _ -> id
|
T_Condition id _ _ -> id
|
||||||
|
|
|
@ -172,6 +172,7 @@ nodeChecks = [
|
||||||
,checkCdAndBack
|
,checkCdAndBack
|
||||||
,checkWrongArithmeticAssignment
|
,checkWrongArithmeticAssignment
|
||||||
,checkConditionalAndOrs
|
,checkConditionalAndOrs
|
||||||
|
,checkFunctionDeclarations
|
||||||
]
|
]
|
||||||
|
|
||||||
|
|
||||||
|
@ -1884,7 +1885,7 @@ checkFunctionsUsedExternally params t =
|
||||||
|
|
||||||
analyse f t = snd $ runState (doAnalysis f t) []
|
analyse f t = snd $ runState (doAnalysis f t) []
|
||||||
functions = Map.fromList $ analyse findFunctions t
|
functions = Map.fromList $ analyse findFunctions t
|
||||||
findFunctions (T_Function id name _) = modify ((name, id):)
|
findFunctions (T_Function id _ _ name _) = modify ((name, id):)
|
||||||
findFunctions t@(T_SimpleCommand id _ (_:args))
|
findFunctions t@(T_SimpleCommand id _ (_:args))
|
||||||
| t `isUnqualifiedCommand` "alias" = mapM_ getAlias args
|
| t `isUnqualifiedCommand` "alias" = mapM_ getAlias args
|
||||||
findFunctions _ = return ()
|
findFunctions _ = return ()
|
||||||
|
@ -2090,6 +2091,25 @@ checkLoopKeywordScope params t |
|
||||||
subshellType t = case leadType (shellType params) (parentMap params) t of
|
subshellType t = case leadType (shellType params) (parentMap params) t of
|
||||||
NoneScope -> Nothing
|
NoneScope -> Nothing
|
||||||
SubshellScope str -> return str
|
SubshellScope str -> return str
|
||||||
isFunction t = case t of T_Function _ _ _ -> True; _ -> False
|
isFunction t = case t of T_Function _ _ _ _ _ -> True; _ -> False
|
||||||
relevant t = isLoop t || isFunction t || isJust (subshellType t)
|
relevant t = isLoop t || isFunction t || isJust (subshellType t)
|
||||||
checkLoopKeywordScope _ _ = return ()
|
checkLoopKeywordScope _ _ = return ()
|
||||||
|
|
||||||
|
|
||||||
|
prop_checkFunctionDeclarations1 = verify checkFunctionDeclarations "#!/bin/ksh\nfunction foo() { command foo --lol \"$@\"; }"
|
||||||
|
prop_checkFunctionDeclarations2 = verify checkFunctionDeclarations "#!/bin/dash\nfunction foo { lol; }"
|
||||||
|
prop_checkFunctionDeclarations3 = verifyNot checkFunctionDeclarations "foo() { echo bar; }"
|
||||||
|
checkFunctionDeclarations params
|
||||||
|
(T_Function id (FunctionKeyword hasKeyword) (FunctionParentheses hasParens) _ _) =
|
||||||
|
case (shellType params) of
|
||||||
|
Bash -> return ()
|
||||||
|
Zsh -> return ()
|
||||||
|
Ksh -> do
|
||||||
|
when (hasKeyword && hasParens) $
|
||||||
|
err id 2111 "ksh does not allow 'function' keyword and '()' at the same time."
|
||||||
|
Sh -> do
|
||||||
|
when (hasKeyword && hasParens) $
|
||||||
|
warn id 2112 "'function' keyword is non-standard. Delete it."
|
||||||
|
when (hasKeyword && not hasParens) $
|
||||||
|
warn id 2113 "'function' keyword is non-standard. Use 'foo()' instead of 'function foo'."
|
||||||
|
checkFunctionDeclarations _ _ = return ()
|
||||||
|
|
|
@ -1580,61 +1580,52 @@ readCaseItem = called "case item" $ do
|
||||||
|
|
||||||
prop_readFunctionDefinition = isOk readFunctionDefinition "foo() { command foo --lol \"$@\"; }"
|
prop_readFunctionDefinition = isOk readFunctionDefinition "foo() { command foo --lol \"$@\"; }"
|
||||||
prop_readFunctionDefinition1 = isOk readFunctionDefinition "foo (){ command foo --lol \"$@\"; }"
|
prop_readFunctionDefinition1 = isOk readFunctionDefinition "foo (){ command foo --lol \"$@\"; }"
|
||||||
prop_readFunctionDefinition2 = isWarning readFunctionDefinition "function foo() { command foo --lol \"$@\"; }"
|
|
||||||
prop_readFunctionDefinition3 = isWarning readFunctionDefinition "function foo { lol; }"
|
|
||||||
prop_readFunctionDefinition4 = isWarning readFunctionDefinition "foo(a, b) { true; }"
|
prop_readFunctionDefinition4 = isWarning readFunctionDefinition "foo(a, b) { true; }"
|
||||||
prop_readFunctionDefinition5 = isOk readFunctionDefinition ":(){ :|:;}"
|
prop_readFunctionDefinition5 = isOk readFunctionDefinition ":(){ :|:;}"
|
||||||
prop_readFunctionDefinition6 = isOk readFunctionDefinition "?(){ foo; }"
|
prop_readFunctionDefinition6 = isOk readFunctionDefinition "?(){ foo; }"
|
||||||
prop_readFunctionDefinition7 = isOk readFunctionDefinition "..(){ cd ..; }"
|
prop_readFunctionDefinition7 = isOk readFunctionDefinition "..(){ cd ..; }"
|
||||||
prop_readFunctionDefinition8 = isOk readFunctionDefinition "foo() (ls)"
|
prop_readFunctionDefinition8 = isOk readFunctionDefinition "foo() (ls)"
|
||||||
readFunctionDefinition = called "function" $ do
|
readFunctionDefinition = called "function" $ do
|
||||||
id <- getNextId
|
functionSignature <- try readFunctionSignature
|
||||||
name <- try readFunctionSignature
|
|
||||||
allspacing
|
allspacing
|
||||||
(disregard (lookAhead $ oneOf "{(") <|> parseProblem ErrorC 1064 "Expected a { to open the function definition.")
|
(disregard (lookAhead $ oneOf "{(") <|> parseProblem ErrorC 1064 "Expected a { to open the function definition.")
|
||||||
group <- readBraceGroup <|> readSubshell
|
group <- readBraceGroup <|> readSubshell
|
||||||
return $ T_Function id name group
|
return $ functionSignature group
|
||||||
|
|
||||||
|
|
||||||
readFunctionSignature = do
|
|
||||||
readWithFunction <|> readWithoutFunction
|
|
||||||
where
|
where
|
||||||
readWithFunction = do
|
readFunctionSignature = do
|
||||||
pos <- getPosition
|
readWithFunction <|> readWithoutFunction
|
||||||
try $ do
|
where
|
||||||
string "function"
|
readWithFunction = do
|
||||||
whitespace
|
id <- getNextId
|
||||||
parseProblemAt pos InfoC 1005 "Drop the keyword 'function'. It's optional in Bash but invalid in other shells."
|
try $ do
|
||||||
spacing
|
string "function"
|
||||||
name <- readFunctionName
|
whitespace
|
||||||
optional spacing
|
spacing
|
||||||
pos <- getPosition
|
name <- readFunctionName
|
||||||
readParens <|> do
|
optional spacing
|
||||||
parseProblemAt pos InfoC 1006 "Include '()' after the function name (in addition to dropping 'function')."
|
hasParens <- wasIncluded readParens
|
||||||
return name
|
return $ T_Function id (FunctionKeyword True) (FunctionParentheses hasParens) name
|
||||||
|
|
||||||
readWithoutFunction = try $ do
|
readWithoutFunction = try $ do
|
||||||
name <- readFunctionName
|
id <- getNextId
|
||||||
optional spacing
|
name <- readFunctionName
|
||||||
readParens
|
optional spacing
|
||||||
return name
|
readParens
|
||||||
|
return $ T_Function id (FunctionKeyword False) (FunctionParentheses True) name
|
||||||
readParens = do
|
|
||||||
g_Lparen
|
|
||||||
optional spacing
|
|
||||||
g_Rparen <|> do
|
|
||||||
parseProblem ErrorC 1065 "Trying to declare parameters? Don't. Use () and refer to params as $1, $2.."
|
|
||||||
many $ noneOf "\n){"
|
|
||||||
g_Rparen
|
|
||||||
return ()
|
|
||||||
|
|
||||||
readFunctionName = many1 functionChars
|
|
||||||
|
|
||||||
|
readParens = do
|
||||||
|
g_Lparen
|
||||||
|
optional spacing
|
||||||
|
g_Rparen <|> do
|
||||||
|
parseProblem ErrorC 1065 "Trying to declare parameters? Don't. Use () and refer to params as $1, $2.."
|
||||||
|
many $ noneOf "\n){"
|
||||||
|
g_Rparen
|
||||||
|
return ()
|
||||||
|
|
||||||
|
readFunctionName = many1 functionChars
|
||||||
|
|
||||||
readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing)
|
readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing)
|
||||||
|
|
||||||
|
|
||||||
prop_readCompoundCommand = isOk readCompoundCommand "{ echo foo; }>/dev/null"
|
prop_readCompoundCommand = isOk readCompoundCommand "{ echo foo; }>/dev/null"
|
||||||
readCompoundCommand = do
|
readCompoundCommand = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
|
|
Loading…
Reference in New Issue