Support ;& and ;;& in case statements
This commit is contained in:
parent
61531cbb10
commit
3dd592a02a
|
@ -29,6 +29,7 @@ data AssignmentMode = Assign | Append deriving (Show, Eq)
|
|||
data FunctionKeyword = FunctionKeyword Bool deriving (Show, Eq)
|
||||
data FunctionParentheses = FunctionParentheses Bool deriving (Show, Eq)
|
||||
data ForInType = NormalForIn | ShortForIn deriving (Show, Eq)
|
||||
data CaseType = CaseBreak | CaseFallThrough | CaseContinue deriving (Show, Eq)
|
||||
|
||||
data Token =
|
||||
TA_Base Id String Token
|
||||
|
@ -58,7 +59,7 @@ data Token =
|
|||
| T_BraceGroup Id [Token]
|
||||
| T_CLOBBER Id
|
||||
| T_Case Id
|
||||
| T_CaseExpression Id Token [([Token],[Token])]
|
||||
| T_CaseExpression Id Token [(CaseType, [Token], [Token])]
|
||||
| T_Condition Id ConditionType Token
|
||||
| T_DGREAT Id
|
||||
| T_DLESS Id
|
||||
|
@ -207,10 +208,10 @@ analyze f g i =
|
|||
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 (\(c, t) -> do
|
||||
newCases <- mapM (\(o, c, t) -> do
|
||||
x <- mapM round c
|
||||
y <- mapM round t
|
||||
return (x,y)
|
||||
return (o, x,y)
|
||||
) cases
|
||||
return $ T_CaseExpression id newWord newCases
|
||||
|
||||
|
|
|
@ -643,7 +643,7 @@ checkBashisms _ = bashism
|
|||
bashism (T_Array id _) =
|
||||
warnMsg id "arrays are"
|
||||
|
||||
bashism _ = return()
|
||||
bashism _ = return ()
|
||||
|
||||
varChars="_0-9a-zA-Z"
|
||||
expansion = let re = mkRegex in [
|
||||
|
@ -2663,8 +2663,10 @@ checkOverridingPath _ _ = return ()
|
|||
|
||||
prop_checkUnsupported1 = verifyNot checkUnsupported "#!/bin/zsh\nfunction { echo cow; }"
|
||||
prop_checkUnsupported2 = verify checkUnsupported "#!/bin/sh\nfunction { echo cow; }"
|
||||
prop_checkUnsupported3 = verify checkUnsupported "#!/bin/sh\ncase foo in bar) baz ;& esac"
|
||||
prop_checkUnsupported4 = verify checkUnsupported "#!/bin/ksh\ncase foo in bar) baz ;;& esac"
|
||||
checkUnsupported params t =
|
||||
when (shellType params `notElem` support) $
|
||||
when ((not $ null support) && (shellType params `notElem` support)) $
|
||||
report name
|
||||
where
|
||||
(name, support) = shellSupport t
|
||||
|
@ -2679,7 +2681,13 @@ shellSupport t =
|
|||
T_ForIn _ _ (_:_:_) _ _ -> ("multi-index for loops", [Zsh])
|
||||
T_ForIn _ ShortForIn _ _ _ -> ("short form for loops", [Zsh])
|
||||
T_ProcSub _ "=" _ -> ("=(..) process substitution", [Zsh])
|
||||
otherwise -> ("", [Bash, Ksh, Sh, Zsh])
|
||||
T_CaseExpression _ _ list -> forCase (map (\(a,_,_) -> a) list)
|
||||
otherwise -> ("", [])
|
||||
where
|
||||
forCase seps | any (== CaseContinue) seps = ("cases with ;;&", [Bash])
|
||||
forCase seps | any (== CaseFallThrough) seps = ("cases with ;&", [Bash, Ksh, Zsh])
|
||||
forCase _ = ("", [])
|
||||
|
||||
|
||||
getCommandSequences (T_Script _ _ cmds) = [cmds]
|
||||
getCommandSequences (T_BraceGroup _ cmds) = [cmds]
|
||||
|
|
|
@ -1305,7 +1305,7 @@ readLineBreak = optional readNewlineList
|
|||
prop_readSeparator1 = isWarning readScript "a &; b"
|
||||
prop_readSeparator2 = isOk readScript "a & b"
|
||||
readSeparatorOp = do
|
||||
notFollowedBy2 (g_AND_IF <|> g_DSEMI)
|
||||
notFollowedBy2 (void g_AND_IF <|> void readCaseSeparator)
|
||||
notFollowedBy2 (string "&>")
|
||||
f <- try (do
|
||||
char '&'
|
||||
|
@ -1687,6 +1687,8 @@ readInClause = do
|
|||
prop_readCaseClause = isOk readCaseClause "case foo in a ) lol; cow;; b|d) fooo; esac"
|
||||
prop_readCaseClause2 = isOk readCaseClause "case foo\n in * ) echo bar;; esac"
|
||||
prop_readCaseClause3 = isOk readCaseClause "case foo\n in * ) echo bar & ;; esac"
|
||||
prop_readCaseClause4 = isOk readCaseClause "case foo\n in *) echo bar ;& bar) foo; esac"
|
||||
prop_readCaseClause5 = isOk readCaseClause "case foo\n in *) echo bar;;& foo) baz;; esac"
|
||||
readCaseClause = called "case expression" $ do
|
||||
id <- getNextId
|
||||
g_Case
|
||||
|
@ -1707,14 +1709,21 @@ readCaseItem = called "case item" $ do
|
|||
pattern <- readPattern
|
||||
g_Rparen
|
||||
readLineBreak
|
||||
list <- (lookAhead g_DSEMI >> return []) <|> readCompoundList
|
||||
(g_DSEMI <|> lookAhead (readLineBreak >> g_Esac)) `attempting` do
|
||||
list <- (lookAhead readCaseSeparator >> return []) <|> readCompoundList
|
||||
separator <- readCaseSeparator `attempting` do
|
||||
pos <- getPosition
|
||||
lookAhead g_Rparen
|
||||
parseProblemAt pos ErrorC 1074
|
||||
"Did you forget the ;; after the previous case item?"
|
||||
readLineBreak
|
||||
return (pattern, list)
|
||||
return (separator, pattern, list)
|
||||
|
||||
readCaseSeparator = choice [
|
||||
tryToken ";;&" (const ()) >> return CaseContinue,
|
||||
tryToken ";&" (const ()) >> return CaseFallThrough,
|
||||
g_DSEMI >> return CaseBreak,
|
||||
lookAhead (readLineBreak >> g_Esac) >> return CaseBreak
|
||||
]
|
||||
|
||||
prop_readFunctionDefinition = isOk readFunctionDefinition "foo() { command foo --lol \"$@\"; }"
|
||||
prop_readFunctionDefinition1 = isOk readFunctionDefinition "foo (){ command foo --lol \"$@\"; }"
|
||||
|
|
Loading…
Reference in New Issue