Fix error spans for shebang warnings (fixes #1620)

This commit is contained in:
Vidar Holen 2019-06-23 13:47:35 -07:00
parent 7e77bfae49
commit 5242e384a1
4 changed files with 19 additions and 15 deletions

View File

@ -121,7 +121,7 @@ data Token =
| T_Rbrace Id | T_Rbrace Id
| T_Redirecting Id [Token] Token | T_Redirecting Id [Token] Token
| T_Rparen Id | T_Rparen Id
| T_Script Id String [Token] | T_Script Id Token [Token] -- Shebang T_Literal, followed by script.
| T_Select Id | T_Select Id
| T_SelectIn Id String [Token] [Token] | T_SelectIn Id String [Token] [Token]
| T_Semi Id | T_Semi Id

View File

@ -534,7 +534,7 @@ indexOfSublists sub = f 0
prop_checkShebangParameters1 = verifyTree checkShebangParameters "#!/usr/bin/env bash -x\necho cow" prop_checkShebangParameters1 = verifyTree checkShebangParameters "#!/usr/bin/env bash -x\necho cow"
prop_checkShebangParameters2 = verifyNotTree checkShebangParameters "#! /bin/sh -l " prop_checkShebangParameters2 = verifyNotTree checkShebangParameters "#! /bin/sh -l "
checkShebangParameters p (T_Annotation _ _ t) = checkShebangParameters p t checkShebangParameters p (T_Annotation _ _ t) = checkShebangParameters p t
checkShebangParameters _ (T_Script id sb _) = checkShebangParameters _ (T_Script _ (T_Literal id sb) _) =
[makeComment ErrorC id 2096 "On most OS, shebangs can only specify a single parameter." | length (words sb) > 2] [makeComment ErrorC id 2096 "On most OS, shebangs can only specify a single parameter." | length (words sb) > 2]
prop_checkShebang1 = verifyNotTree checkShebang "#!/usr/bin/env bash -x\necho cow" prop_checkShebang1 = verifyNotTree checkShebang "#!/usr/bin/env bash -x\necho cow"
@ -554,7 +554,7 @@ checkShebang params (T_Annotation _ list t) =
where where
isOverride (ShellOverride _) = True isOverride (ShellOverride _) = True
isOverride _ = False isOverride _ = False
checkShebang params (T_Script id sb _) = execWriter $ do checkShebang params (T_Script _ (T_Literal id sb) _) = execWriter $ do
unless (shellTypeSpecified params) $ do unless (shellTypeSpecified params) $ do
when (sb == "") $ when (sb == "") $
err id 2148 "Tips depend on target shell and yours is unknown. Add a shebang." err id 2148 "Tips depend on target shell and yours is unknown. Add a shebang."

View File

@ -206,7 +206,7 @@ containsSetE root = isNothing $ doAnalysis (guard . not . isSetE) root
where where
isSetE t = isSetE t =
case t of case t of
T_Script _ str _ -> str `matches` re T_Script _ (T_Literal _ str) _ -> str `matches` re
T_SimpleCommand {} -> T_SimpleCommand {} ->
t `isUnqualifiedCommand` "set" && t `isUnqualifiedCommand` "set" &&
("errexit" `elem` oversimplify t || ("errexit" `elem` oversimplify t ||
@ -252,7 +252,7 @@ determineShell fallbackShell t = fromMaybe Bash $ do
getCandidates (T_Annotation _ annotations s) = getCandidates (T_Annotation _ annotations s) =
map forAnnotation annotations ++ map forAnnotation annotations ++
[Just $ fromShebang s] [Just $ fromShebang s]
fromShebang (T_Script _ s t) = executableFromShebang s fromShebang (T_Script _ (T_Literal _ s) _) = executableFromShebang s
-- Given a string like "/bin/bash" or "/usr/bin/env dash", -- Given a string like "/bin/bash" or "/usr/bin/env dash",
-- return the shell basename like "bash" or "dash" -- return the shell basename like "bash" or "dash"

View File

@ -2790,6 +2790,7 @@ readAssignmentWordExt lenient = try $ do
string "=" >> return Assign string "=" >> return Assign
] ]
readEmptyLiteral = do readEmptyLiteral = do
start <- startSpan start <- startSpan
id <- endSpan start id <- endSpan start
@ -2941,12 +2942,14 @@ prop_readShebang5 = isWarning readShebang "\n#!/bin/sh"
prop_readShebang6 = isWarning readShebang " # Copyright \n!#/bin/bash" prop_readShebang6 = isWarning readShebang " # Copyright \n!#/bin/bash"
prop_readShebang7 = isNotOk readShebang "# Copyright \nfoo\n#!/bin/bash" prop_readShebang7 = isNotOk readShebang "# Copyright \nfoo\n#!/bin/bash"
readShebang = do readShebang = do
start <- startSpan
anyShebang <|> try readMissingBang <|> withHeader anyShebang <|> try readMissingBang <|> withHeader
many linewhitespace many linewhitespace
str <- many $ noneOf "\r\n" str <- many $ noneOf "\r\n"
id <- endSpan start
optional carriageReturn optional carriageReturn
optional linefeed optional linefeed
return str return $ T_Literal id str
where where
anyShebang = choice $ map try [ anyShebang = choice $ map try [
readCorrect, readCorrect,
@ -3077,7 +3080,8 @@ readScriptFile sourced = do
readUtf8Bom readUtf8Bom
parseProblem ErrorC 1082 parseProblem ErrorC 1082
"This file has a UTF-8 BOM. Remove it with: LC_CTYPE=C sed '1s/^...//' < yourscript ." "This file has a UTF-8 BOM. Remove it with: LC_CTYPE=C sed '1s/^...//' < yourscript ."
sb <- option "" readShebang shebang <- readShebang <|> readEmptyLiteral
let (T_Literal _ shebangString) = shebang
allspacing allspacing
annotationStart <- startSpan annotationStart <- startSpan
fileAnnotations <- readAnnotations fileAnnotations <- readAnnotations
@ -3094,19 +3098,19 @@ readScriptFile sourced = do
let ignoreShebang = shellAnnotationSpecified || shellFlagSpecified let ignoreShebang = shellAnnotationSpecified || shellFlagSpecified
unless ignoreShebang $ unless ignoreShebang $
verifyShebang pos (getShell sb) verifyShebang pos (getShell shebangString)
if ignoreShebang || isValidShell (getShell sb) /= Just False if ignoreShebang || isValidShell (getShell shebangString) /= Just False
then do then do
commands <- withAnnotations annotations readCompoundListOrEmpty commands <- withAnnotations annotations readCompoundListOrEmpty
id <- endSpan start id <- endSpan start
verifyEof verifyEof
let script = T_Annotation annotationId annotations $ let script = T_Annotation annotationId annotations $
T_Script id sb commands T_Script id shebang commands
reparseIndices script reparseIndices script
else do else do
many anyChar many anyChar
id <- endSpan start id <- endSpan start
return $ T_Script id sb [] return $ T_Script id shebang []
where where
basename s = reverse . takeWhile (/= '/') . reverse $ s basename s = reverse . takeWhile (/= '/') . reverse $ s