Let annotations take effect earlier (fixes #2534)
This commit is contained in:
parent
d0dd81e1fa
commit
c76b8d9a32
|
@ -496,6 +496,17 @@ prop_fileCannotEnableExternalSources2 = result == [1144]
|
|||
csCheckSourced = True
|
||||
}
|
||||
|
||||
prop_rcCanSuppressEarlyProblems1 = null result
|
||||
where
|
||||
result = checkWithRc "disable=1071" emptyCheckSpec {
|
||||
csScript = "#!/bin/zsh\necho $1"
|
||||
}
|
||||
|
||||
prop_rcCanSuppressEarlyProblems2 = null result
|
||||
where
|
||||
result = checkWithRc "disable=1104" emptyCheckSpec {
|
||||
csScript = "!/bin/bash\necho 'hello world'"
|
||||
}
|
||||
|
||||
return []
|
||||
runTests = $quickCheckAll
|
||||
|
|
|
@ -38,7 +38,6 @@ import Data.Functor
|
|||
import Data.List (isPrefixOf, isInfixOf, isSuffixOf, partition, sortBy, intercalate, nub, find)
|
||||
import Data.Maybe
|
||||
import Data.Monoid
|
||||
import Debug.Trace -- STRIP
|
||||
import GHC.Exts (sortWith)
|
||||
import Prelude hiding (readList)
|
||||
import System.IO
|
||||
|
@ -458,8 +457,8 @@ called s p = do
|
|||
pos <- getPosition
|
||||
withContext (ContextName pos s) p
|
||||
|
||||
withAnnotations anns =
|
||||
withContext (ContextAnnotation anns)
|
||||
withAnnotations anns p =
|
||||
if null anns then p else withContext (ContextAnnotation anns) p
|
||||
|
||||
readConditionContents single =
|
||||
readCondContents `attempting` lookAhead (do
|
||||
|
@ -3258,23 +3257,30 @@ prop_readScript3 = isWarning readScript "#!/bin/bash\necho hello\xA0world"
|
|||
prop_readScript4 = isWarning readScript "#!/usr/bin/perl\nfoo=("
|
||||
prop_readScript5 = isOk readScript "#!/bin/bash\n#This is an empty script\n\n"
|
||||
prop_readScript6 = isOk readScript "#!/usr/bin/env -S X=FOO bash\n#This is an empty script\n\n"
|
||||
prop_readScript7 = isOk readScript "#!/bin/zsh\n# shellcheck disable=SC1071\nfor f (a b); echo $f\n"
|
||||
readScriptFile sourced = do
|
||||
start <- startSpan
|
||||
pos <- getPosition
|
||||
optional $ do
|
||||
readUtf8Bom
|
||||
parseProblem ErrorC 1082
|
||||
"This file has a UTF-8 BOM. Remove it with: LC_CTYPE=C sed '1s/^...//' < yourscript ."
|
||||
shebang <- readShebang <|> readEmptyLiteral
|
||||
let (T_Literal _ shebangString) = shebang
|
||||
allspacing
|
||||
annotationStart <- startSpan
|
||||
fileAnnotations <- readAnnotations
|
||||
rcAnnotations <- if sourced
|
||||
then return []
|
||||
else do
|
||||
filename <- Mr.asks currentFilename
|
||||
readConfigFile filename
|
||||
|
||||
-- Put the rc annotations on the stack so that one can ignore e.g. SC1084 in .shellcheckrc
|
||||
withAnnotations rcAnnotations $ do
|
||||
hasBom <- wasIncluded readUtf8Bom
|
||||
shebang <- readShebang <|> readEmptyLiteral
|
||||
let (T_Literal _ shebangString) = shebang
|
||||
allspacing
|
||||
annotationStart <- startSpan
|
||||
fileAnnotations <- readAnnotations
|
||||
|
||||
-- Similarly put the filewide annotations on the stack to allow earlier suppression
|
||||
withAnnotations fileAnnotations $ do
|
||||
when (hasBom) $
|
||||
parseProblemAt pos ErrorC 1082
|
||||
"This file has a UTF-8 BOM. Remove it with: LC_CTYPE=C sed '1s/^...//' < yourscript ."
|
||||
let annotations = fileAnnotations ++ rcAnnotations
|
||||
annotationId <- endSpan annotationStart
|
||||
let shellAnnotationSpecified =
|
||||
|
@ -3286,7 +3292,7 @@ readScriptFile sourced = do
|
|||
verifyShebang pos (executableFromShebang shebangString)
|
||||
if ignoreShebang || isValidShell (executableFromShebang shebangString) /= Just False
|
||||
then do
|
||||
commands <- withAnnotations annotations readCompoundListOrEmpty
|
||||
commands <- readCompoundListOrEmpty
|
||||
id <- endSpan start
|
||||
verifyEof
|
||||
let script = T_Annotation annotationId annotations $
|
||||
|
@ -3388,16 +3394,6 @@ parsesCleanly parser string = runIdentity $ do
|
|||
return $ Just . null $ parseNotes userState ++ parseProblems systemState
|
||||
(Left _, _) -> return Nothing
|
||||
|
||||
-- For printf debugging: print the value of an expression
|
||||
-- Example: return $ dump $ T_Literal id [c]
|
||||
dump :: Show a => a -> a -- STRIP
|
||||
dump x = trace (show x) x -- STRIP
|
||||
|
||||
-- Like above, but print a specific expression:
|
||||
-- Example: return $ dumps ("Returning: " ++ [c]) $ T_Literal id [c]
|
||||
dumps :: Show x => x -> a -> a -- STRIP
|
||||
dumps t = trace (show t) -- STRIP
|
||||
|
||||
parseWithNotes parser = do
|
||||
item <- parser
|
||||
state <- getState
|
||||
|
|
Loading…
Reference in New Issue