mirror of
https://github.com/koalaman/shellcheck
synced 2025-08-20 13:23:55 -07:00
Add support for ${| ..} expansion (fixes #3243)
This commit is contained in:
parent
6a758d5dc7
commit
23097320a4
5 changed files with 21 additions and 15 deletions
|
@ -31,6 +31,7 @@ newtype Id = Id Int deriving (Show, Eq, Ord, Generic, NFData)
|
|||
|
||||
data Quoted = Quoted | Unquoted deriving (Show, Eq)
|
||||
data Dashed = Dashed | Undashed deriving (Show, Eq)
|
||||
data Piped = Piped | Unpiped deriving (Show, Eq)
|
||||
data AssignmentMode = Assign | Append deriving (Show, Eq)
|
||||
newtype FunctionKeyword = FunctionKeyword Bool deriving (Show, Eq)
|
||||
newtype FunctionParentheses = FunctionParentheses Bool deriving (Show, Eq)
|
||||
|
@ -84,7 +85,7 @@ data InnerToken t =
|
|||
| Inner_T_DollarDoubleQuoted [t]
|
||||
| Inner_T_DollarExpansion [t]
|
||||
| Inner_T_DollarSingleQuoted String
|
||||
| Inner_T_DollarBraceCommandExpansion [t]
|
||||
| Inner_T_DollarBraceCommandExpansion Piped [t]
|
||||
| Inner_T_Done
|
||||
| Inner_T_DoubleQuoted [t]
|
||||
| Inner_T_EOF
|
||||
|
@ -228,7 +229,7 @@ pattern T_CoProc id var body = OuterToken id (Inner_T_CoProc var body)
|
|||
pattern TC_Or id typ str t1 t2 = OuterToken id (Inner_TC_Or typ str t1 t2)
|
||||
pattern TC_Unary id typ op token = OuterToken id (Inner_TC_Unary typ op token)
|
||||
pattern T_DollarArithmetic id c = OuterToken id (Inner_T_DollarArithmetic c)
|
||||
pattern T_DollarBraceCommandExpansion id list = OuterToken id (Inner_T_DollarBraceCommandExpansion list)
|
||||
pattern T_DollarBraceCommandExpansion id pipe list = OuterToken id (Inner_T_DollarBraceCommandExpansion pipe list)
|
||||
pattern T_DollarBraced id braced op = OuterToken id (Inner_T_DollarBraced braced op)
|
||||
pattern T_DollarBracket id c = OuterToken id (Inner_T_DollarBracket c)
|
||||
pattern T_DollarDoubleQuoted id list = OuterToken id (Inner_T_DollarDoubleQuoted list)
|
||||
|
|
|
@ -561,7 +561,7 @@ getCommandNameFromExpansion t =
|
|||
case t of
|
||||
T_DollarExpansion _ [c] -> extract c
|
||||
T_Backticked _ [c] -> extract c
|
||||
T_DollarBraceCommandExpansion _ [c] -> extract c
|
||||
T_DollarBraceCommandExpansion _ _ [c] -> extract c
|
||||
_ -> Nothing
|
||||
where
|
||||
extract (T_Pipeline _ _ [cmd]) = getCommandName cmd
|
||||
|
@ -616,7 +616,7 @@ getCommandSequences t =
|
|||
T_Annotation _ _ t -> getCommandSequences t
|
||||
|
||||
T_DollarExpansion _ cmds -> [cmds]
|
||||
T_DollarBraceCommandExpansion _ cmds -> [cmds]
|
||||
T_DollarBraceCommandExpansion _ _ cmds -> [cmds]
|
||||
T_Backticked _ cmds -> [cmds]
|
||||
_ -> []
|
||||
|
||||
|
|
|
@ -800,7 +800,7 @@ checkUnquotedExpansions params =
|
|||
where
|
||||
check t@(T_DollarExpansion _ c) = examine t c
|
||||
check t@(T_Backticked _ c) = examine t c
|
||||
check t@(T_DollarBraceCommandExpansion _ c) = examine t c
|
||||
check t@(T_DollarBraceCommandExpansion _ _ c) = examine t c
|
||||
check _ = return ()
|
||||
tree = parentMap params
|
||||
examine t contents =
|
||||
|
@ -3012,7 +3012,8 @@ checkTildeInPath _ _ = return ()
|
|||
|
||||
prop_checkUnsupported3 = verify checkUnsupported "#!/bin/sh\ncase foo in bar) baz ;& esac"
|
||||
prop_checkUnsupported4 = verify checkUnsupported "#!/bin/ksh\ncase foo in bar) baz ;;& esac"
|
||||
prop_checkUnsupported5 = verify checkUnsupported "#!/bin/bash\necho \"${ ls; }\""
|
||||
prop_checkUnsupported5 = verifyNot checkUnsupported "#!/bin/bash\necho \"${ ls; }\""
|
||||
prop_checkUnsupported6 = verify checkUnsupported "#!/bin/ash\necho \"${ ls; }\""
|
||||
checkUnsupported params t =
|
||||
unless (null support || (shellType params `elem` support)) $
|
||||
report name
|
||||
|
@ -3026,7 +3027,7 @@ checkUnsupported params t =
|
|||
shellSupport t =
|
||||
case t of
|
||||
T_CaseExpression _ _ list -> forCase (map (\(a,_,_) -> a) list)
|
||||
T_DollarBraceCommandExpansion {} -> ("${ ..; } command expansion", [Ksh])
|
||||
T_DollarBraceCommandExpansion {} -> ("${ ..; } command expansion", [Bash, Ksh])
|
||||
_ -> ("", [])
|
||||
where
|
||||
forCase seps | CaseContinue `elem` seps = ("cases with ;;&", [Bash])
|
||||
|
@ -3606,7 +3607,7 @@ checkSplittingInArrays params t =
|
|||
_ -> return ()
|
||||
checkPart part = case part of
|
||||
T_DollarExpansion id _ -> forCommand id
|
||||
T_DollarBraceCommandExpansion id _ -> forCommand id
|
||||
T_DollarBraceCommandExpansion id _ _ -> forCommand id
|
||||
T_Backticked id _ -> forCommand id
|
||||
T_DollarBraced id _ str |
|
||||
not (isCountingReference part)
|
||||
|
@ -5161,7 +5162,7 @@ checkExpansionWithRedirection params t =
|
|||
case t of
|
||||
T_DollarExpansion id [cmd] -> check id cmd
|
||||
T_Backticked id [cmd] -> check id cmd
|
||||
T_DollarBraceCommandExpansion id [cmd] -> check id cmd
|
||||
T_DollarBraceCommandExpansion id _ [cmd] -> check id cmd
|
||||
_ -> return ()
|
||||
where
|
||||
check id pipe =
|
||||
|
|
|
@ -716,6 +716,9 @@ build t = do
|
|||
linkRange totalRead result
|
||||
else return totalRead
|
||||
|
||||
T_DollarBraceCommandExpansion id _ body ->
|
||||
sequentially body
|
||||
|
||||
T_DoubleQuoted _ list -> sequentially list
|
||||
|
||||
T_DollarExpansion id body ->
|
||||
|
|
|
@ -1695,16 +1695,17 @@ readAmbiguous prefix expected alternative warner = do
|
|||
|
||||
prop_readDollarBraceCommandExpansion1 = isOk readDollarBraceCommandExpansion "${ ls; }"
|
||||
prop_readDollarBraceCommandExpansion2 = isOk readDollarBraceCommandExpansion "${\nls\n}"
|
||||
readDollarBraceCommandExpansion = called "ksh ${ ..; } command expansion" $ do
|
||||
prop_readDollarBraceCommandExpansion3 = isOk readDollarBraceCommandExpansion "${| REPLY=42; }"
|
||||
readDollarBraceCommandExpansion = called "ksh-style ${ ..; } command expansion" $ do
|
||||
start <- startSpan
|
||||
try $ do
|
||||
string "${"
|
||||
whitespace
|
||||
c <- try $ do
|
||||
string "${"
|
||||
char '|' <|> whitespace
|
||||
allspacing
|
||||
term <- readTerm
|
||||
char '}' <|> fail "Expected } to end the ksh ${ ..; } command expansion"
|
||||
char '}' <|> fail "Expected } to end the ksh-style ${ ..; } command expansion"
|
||||
id <- endSpan start
|
||||
return $ T_DollarBraceCommandExpansion id term
|
||||
return $ T_DollarBraceCommandExpansion id (if c == '|' then Piped else Unpiped) term
|
||||
|
||||
prop_readDollarBraced1 = isOk readDollarBraced "${foo//bar/baz}"
|
||||
prop_readDollarBraced2 = isOk readDollarBraced "${foo/'{cow}'}"
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue