mirror of
https://github.com/koalaman/shellcheck
synced 2025-07-07 05:21:34 -07:00
Preliminary support for sourced files.
This commit is contained in:
parent
0dd61b65d8
commit
f31c8bd3a3
5 changed files with 203 additions and 28 deletions
|
@ -125,6 +125,7 @@ data Token =
|
|||
| T_Pipe Id String
|
||||
| T_CoProc Id (Maybe String) Token
|
||||
| T_CoProcBody Id Token
|
||||
| T_Include Id Token Token -- . & source: SimpleCommand T_Script
|
||||
deriving (Show)
|
||||
|
||||
data Annotation = DisableComment Integer deriving (Show, Eq)
|
||||
|
@ -255,6 +256,7 @@ analyze f g i =
|
|||
delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns
|
||||
delve (T_CoProc id var body) = d1 body $ T_CoProc id var
|
||||
delve (T_CoProcBody id t) = d1 t $ T_CoProcBody id
|
||||
delve (T_Include id includer script) = d2 includer script $ T_Include id
|
||||
delve t = return t
|
||||
|
||||
getId t = case t of
|
||||
|
@ -350,6 +352,7 @@ getId t = case t of
|
|||
T_Pipe id _ -> id
|
||||
T_CoProc id _ _ -> id
|
||||
T_CoProcBody id _ -> id
|
||||
T_Include id _ _ -> id
|
||||
|
||||
blank :: Monad m => Token -> m ()
|
||||
blank = const $ return ()
|
||||
|
|
|
@ -224,6 +224,7 @@ filterByAnnotation token =
|
|||
any hasNum anns
|
||||
where
|
||||
hasNum (DisableComment ts) = num == ts
|
||||
shouldIgnoreFor _ (T_Include {}) = True -- Ignore included files
|
||||
shouldIgnoreFor _ _ = False
|
||||
parents = getParentTree token
|
||||
|
||||
|
|
|
@ -81,7 +81,7 @@ checkScript sys spec = do
|
|||
}
|
||||
|
||||
getErrors sys spec =
|
||||
map getCode . crComments $
|
||||
sort . map getCode . crComments $
|
||||
runIdentity (checkScript sys spec)
|
||||
where
|
||||
getCode (PositionedComment _ (Comment _ code _)) = code
|
||||
|
@ -124,5 +124,45 @@ prop_optionDisablesIssue2 =
|
|||
csExcludedWarnings = [2148, 1037]
|
||||
}
|
||||
|
||||
prop_failsWhenNotSourcing =
|
||||
[1091, 2154] == getErrors
|
||||
(mockedSystemInterface [])
|
||||
emptyCheckSpec {
|
||||
csScript = "source lob; echo \"$bar\"",
|
||||
csExcludedWarnings = [2148]
|
||||
}
|
||||
|
||||
prop_worksWhenSourcing =
|
||||
null $ getErrors
|
||||
(mockedSystemInterface [("lib", "bar=1")])
|
||||
emptyCheckSpec {
|
||||
csScript = "source lib; echo \"$bar\"",
|
||||
csExcludedWarnings = [2148]
|
||||
}
|
||||
|
||||
prop_worksWhenDotting =
|
||||
null $ getErrors
|
||||
(mockedSystemInterface [("lib", "bar=1")])
|
||||
emptyCheckSpec {
|
||||
csScript = ". lib; echo \"$bar\"",
|
||||
csExcludedWarnings = [2148]
|
||||
}
|
||||
|
||||
prop_noInfiniteSourcing =
|
||||
[] == getErrors
|
||||
(mockedSystemInterface [("lib", "source lib")])
|
||||
emptyCheckSpec {
|
||||
csScript = "source lib",
|
||||
csExcludedWarnings = [2148]
|
||||
}
|
||||
|
||||
prop_canSourceBadSyntax =
|
||||
[1094, 2086] == getErrors
|
||||
(mockedSystemInterface [("lib", "for f; do")])
|
||||
emptyCheckSpec {
|
||||
csScript = "source lib; echo $1",
|
||||
csExcludedWarnings = [2148]
|
||||
}
|
||||
|
||||
return []
|
||||
runTests = $quickCheckAll
|
||||
|
|
|
@ -21,23 +21,28 @@
|
|||
module ShellCheck.Parser (parseScript, runTests) where
|
||||
|
||||
import ShellCheck.AST
|
||||
import ShellCheck.ASTLib
|
||||
import ShellCheck.Data
|
||||
import ShellCheck.Interface
|
||||
import Text.Parsec hiding (runParser)
|
||||
import Debug.Trace
|
||||
|
||||
import Control.Monad
|
||||
import Control.Monad.Identity
|
||||
import Control.Monad.Trans
|
||||
import Data.Char
|
||||
import Data.Functor
|
||||
import Data.List (isPrefixOf, isInfixOf, isSuffixOf, partition, sortBy, intercalate, nub)
|
||||
import qualified Data.Map as Map
|
||||
import qualified Control.Monad.State as Ms
|
||||
import qualified Control.Monad.Reader as Mr
|
||||
import Data.Maybe
|
||||
import Debug.Trace
|
||||
import GHC.Exts (sortWith)
|
||||
import Prelude hiding (readList)
|
||||
import System.IO
|
||||
import Text.Parsec hiding (runParser)
|
||||
import Text.Parsec.Error
|
||||
import GHC.Exts (sortWith)
|
||||
import Text.Parsec.Pos
|
||||
import qualified Control.Monad.Reader as Mr
|
||||
import qualified Control.Monad.State as Ms
|
||||
import qualified Data.Map as Map
|
||||
|
||||
import Test.QuickCheck.All (quickCheckAll)
|
||||
|
||||
type SCBase m = Mr.ReaderT (SystemInterface m) (Ms.StateT SystemState m)
|
||||
|
@ -125,7 +130,11 @@ almostSpace =
|
|||
--------- Message/position annotation on top of user state
|
||||
data Note = Note Id Severity Code String deriving (Show, Eq)
|
||||
data ParseNote = ParseNote SourcePos Severity Code String deriving (Show, Eq)
|
||||
data Context = ContextName SourcePos String | ContextAnnotation [Annotation] deriving (Show)
|
||||
data Context =
|
||||
ContextName SourcePos String
|
||||
| ContextAnnotation [Annotation]
|
||||
| ContextSource String
|
||||
deriving (Show)
|
||||
|
||||
data UserState = UserState {
|
||||
lastId :: Id,
|
||||
|
@ -179,9 +188,27 @@ shouldIgnoreCode code = do
|
|||
where
|
||||
disabling (ContextAnnotation list) =
|
||||
any disabling' list
|
||||
disabling (ContextSource _) = True -- Don't add messages for sourced files
|
||||
disabling _ = False
|
||||
disabling' (DisableComment n) = code == n
|
||||
|
||||
shouldFollow file = do
|
||||
context <- getCurrentContexts
|
||||
if any isThisFile context
|
||||
then return False
|
||||
else
|
||||
if length (filter isSource context) >= 100
|
||||
then do
|
||||
parseProblem ErrorC 1092 "Stopping at 100 'source' frames :O"
|
||||
return False
|
||||
else
|
||||
return True
|
||||
where
|
||||
isSource (ContextSource _) = True
|
||||
isSource _ = False
|
||||
isThisFile (ContextSource name) | name == file = True
|
||||
isThisFile _= False
|
||||
|
||||
-- Store potential parse problems outside of parsec
|
||||
|
||||
data SystemState = SystemState {
|
||||
|
@ -900,6 +927,18 @@ subParse pos parser input = do
|
|||
setPosition lastPosition
|
||||
return result
|
||||
|
||||
inSeparateContext parser = do
|
||||
context <- Ms.get
|
||||
success context <|> failure context
|
||||
where
|
||||
success c = do
|
||||
res <- try parser
|
||||
Ms.put c
|
||||
return res
|
||||
failure c = do
|
||||
Ms.put c
|
||||
fail ""
|
||||
|
||||
prop_readDoubleQuoted = isOk readDoubleQuoted "\"Hello $FOO\""
|
||||
prop_readDoubleQuoted2 = isOk readDoubleQuoted "\"$'\""
|
||||
prop_readDoubleQuoted3 = isWarning readDoubleQuoted "\x201Chello\x201D"
|
||||
|
@ -1403,7 +1442,6 @@ makeSimpleCommand id1 id2 prefix cmd suffix =
|
|||
redirection (T_FdRedirect {}) = True
|
||||
redirection _ = False
|
||||
|
||||
|
||||
prop_readSimpleCommand = isOk readSimpleCommand "echo test > file"
|
||||
prop_readSimpleCommand2 = isOk readSimpleCommand "cmd &> file"
|
||||
prop_readSimpleCommand3 = isOk readSimpleCommand "export foo=(bar baz)"
|
||||
|
@ -1411,6 +1449,7 @@ prop_readSimpleCommand4 = isOk readSimpleCommand "typeset -a foo=(lol)"
|
|||
prop_readSimpleCommand5 = isOk readSimpleCommand "time if true; then echo foo; fi"
|
||||
prop_readSimpleCommand6 = isOk readSimpleCommand "time -p ( ls -l; )"
|
||||
readSimpleCommand = called "simple command" $ do
|
||||
pos <- getPosition
|
||||
id1 <- getNextId
|
||||
id2 <- getNextId
|
||||
prefix <- option [] readCmdPrefix
|
||||
|
@ -1424,7 +1463,11 @@ readSimpleCommand = called "simple command" $ do
|
|||
(["time"], readTimeSuffix),
|
||||
(["let"], readLetSuffix)
|
||||
]
|
||||
return $ makeSimpleCommand id1 id2 prefix [cmd] suffix
|
||||
|
||||
let result = makeSimpleCommand id1 id2 prefix [cmd] suffix
|
||||
if isCommand ["source", "."] cmd
|
||||
then readSource pos result
|
||||
else return result
|
||||
where
|
||||
isCommand strings (T_NormalWord _ [T_Literal _ s]) = s `elem` strings
|
||||
isCommand _ _ = False
|
||||
|
@ -1434,6 +1477,51 @@ readSimpleCommand = called "simple command" $ do
|
|||
then action
|
||||
else getParser def cmd rest
|
||||
|
||||
|
||||
readSource :: Monad m => SourcePos -> Token -> SCParser m Token
|
||||
readSource pos t@(T_Redirecting _ _ (T_SimpleCommand _ _ (cmd:file:_))) = do
|
||||
let literalFile = getLiteralString file
|
||||
case literalFile of
|
||||
Nothing -> do
|
||||
parseNoteAt pos InfoC 1090
|
||||
"This source will be skipped since it's not constant."
|
||||
return t
|
||||
Just filename -> do
|
||||
proceed <- shouldFollow filename
|
||||
if not proceed
|
||||
then do
|
||||
parseNoteAt pos InfoC 1093
|
||||
"This file appears to be recursively sourced. Ignoring."
|
||||
return t
|
||||
else do
|
||||
sys <- Mr.ask
|
||||
input <- system $ siReadFile sys filename
|
||||
case input of
|
||||
Left err -> do
|
||||
parseNoteAt pos InfoC 1091 $
|
||||
"Not following: " ++ err
|
||||
return t
|
||||
Right script -> do
|
||||
id <- getNextIdAt pos
|
||||
|
||||
let included = do
|
||||
src <- subRead filename script
|
||||
return $ T_Include id t src
|
||||
|
||||
let failed = do
|
||||
parseNoteAt pos WarningC 1094
|
||||
"Parsing of sourced file failed. Ignoring it."
|
||||
return t
|
||||
|
||||
included <|> failed
|
||||
where
|
||||
subRead name script =
|
||||
withContext (ContextSource name) $
|
||||
inSeparateContext $
|
||||
subParse (initialPos name) readScript script
|
||||
readSource _ t = return t
|
||||
|
||||
|
||||
prop_readPipeline = isOk readPipeline "! cat /etc/issue | grep -i ubuntu"
|
||||
prop_readPipeline2 = isWarning readPipeline "!cat /etc/issue | grep -i ubuntu"
|
||||
prop_readPipeline3 = isOk readPipeline "for f; do :; done|cat"
|
||||
|
@ -2222,6 +2310,7 @@ runParser sys p filename contents =
|
|||
(runParserT p initialUserState filename contents)
|
||||
sys)
|
||||
initialSystemState
|
||||
system = lift . lift . lift
|
||||
|
||||
parseShell sys name contents = do
|
||||
(result, state) <- runParser sys (parseWithNotes readScript) name contents
|
||||
|
|
|
@ -38,6 +38,7 @@ import Data.Maybe
|
|||
import Data.Monoid
|
||||
import Prelude hiding (catch)
|
||||
import System.Console.GetOpt
|
||||
import System.Directory
|
||||
import System.Environment
|
||||
import System.Exit
|
||||
import System.IO
|
||||
|
@ -56,6 +57,16 @@ instance Monoid Status where
|
|||
mempty = NoProblems
|
||||
mappend = max
|
||||
|
||||
data Options = Options {
|
||||
checkSpec :: CheckSpec,
|
||||
externalSources :: Bool
|
||||
}
|
||||
|
||||
defaultOptions = Options {
|
||||
checkSpec = emptyCheckSpec,
|
||||
externalSources = False
|
||||
}
|
||||
|
||||
usageHeader = "Usage: shellcheck [OPTIONS...] FILES..."
|
||||
options = [
|
||||
Option "e" ["exclude"]
|
||||
|
@ -64,6 +75,8 @@ options = [
|
|||
(ReqArg (Flag "format") "FORMAT") "output format",
|
||||
Option "s" ["shell"]
|
||||
(ReqArg (Flag "shell") "SHELLNAME") "Specify dialect (bash,sh,ksh)",
|
||||
Option "x" ["external-sources"]
|
||||
(NoArg $ Flag "externals" "true") "Allow 'source' outside of FILES.",
|
||||
Option "V" ["version"]
|
||||
(NoArg $ Flag "version" "true") "Print version information"
|
||||
]
|
||||
|
@ -128,7 +141,7 @@ statusToCode status =
|
|||
|
||||
process :: [Flag] -> [FilePath] -> ExceptT Status IO Status
|
||||
process flags files = do
|
||||
options <- foldM (flip parseOption) emptyCheckSpec flags
|
||||
options <- foldM (flip parseOption) defaultOptions flags
|
||||
verifyFiles files
|
||||
let format = fromMaybe "tty" $ getOption flags "format"
|
||||
formatter <-
|
||||
|
@ -140,12 +153,12 @@ process flags files = do
|
|||
throwError SupportFailure
|
||||
where write s = " " ++ s
|
||||
Just f -> ExceptT $ fmap Right f
|
||||
let sys = ioInterface (const False)
|
||||
sys <- lift $ ioInterface options files
|
||||
lift $ runFormatter sys formatter options files
|
||||
|
||||
runFormatter :: SystemInterface IO -> Formatter -> CheckSpec -> [FilePath]
|
||||
runFormatter :: SystemInterface IO -> Formatter -> Options -> [FilePath]
|
||||
-> IO Status
|
||||
runFormatter sys format spec files = do
|
||||
runFormatter sys format options files = do
|
||||
header format
|
||||
result <- foldM f NoProblems files
|
||||
footer format
|
||||
|
@ -163,7 +176,7 @@ runFormatter sys format spec files = do
|
|||
process :: FilePath -> IO Status
|
||||
process filename = do
|
||||
contents <- inputFile filename
|
||||
let checkspec = spec {
|
||||
let checkspec = (checkSpec options) {
|
||||
csFilename = filename,
|
||||
csScript = contents
|
||||
}
|
||||
|
@ -179,17 +192,30 @@ parseOption flag options =
|
|||
Flag "shell" str ->
|
||||
fromMaybe (die $ "Unknown shell: " ++ str) $ do
|
||||
shell <- shellForExecutable str
|
||||
return $ return options { csShellTypeOverride = Just shell }
|
||||
return $ return options {
|
||||
checkSpec = (checkSpec options) {
|
||||
csShellTypeOverride = Just shell
|
||||
}
|
||||
}
|
||||
|
||||
Flag "exclude" str -> do
|
||||
new <- mapM parseNum $ split ',' str
|
||||
let old = csExcludedWarnings options
|
||||
return options { csExcludedWarnings = new ++ old }
|
||||
let old = csExcludedWarnings . checkSpec $ options
|
||||
return options {
|
||||
checkSpec = (checkSpec options) {
|
||||
csExcludedWarnings = new ++ old
|
||||
}
|
||||
}
|
||||
|
||||
Flag "version" _ -> do
|
||||
liftIO printVersion
|
||||
throwError NoProblems
|
||||
|
||||
Flag "externals" _ -> do
|
||||
return options {
|
||||
externalSources = True
|
||||
}
|
||||
|
||||
_ -> return options
|
||||
where
|
||||
die s = do
|
||||
|
@ -202,19 +228,35 @@ parseOption flag options =
|
|||
throwError SyntaxFailure
|
||||
return (Prelude.read num :: Integer)
|
||||
|
||||
ioInterface filter =
|
||||
SystemInterface {
|
||||
siReadFile = get
|
||||
ioInterface options files = do
|
||||
inputs <- mapM normalize files
|
||||
return SystemInterface {
|
||||
siReadFile = get inputs
|
||||
}
|
||||
where
|
||||
get file =
|
||||
if filter file
|
||||
get inputs file = do
|
||||
ok <- allowable inputs file
|
||||
if ok
|
||||
then (Right <$> inputFile file) `catch` handler
|
||||
else return $ Left (file ++ " was not specified as input.")
|
||||
else return $ Left (file ++ " was not specified as input (see shellcheck -x).")
|
||||
|
||||
where
|
||||
handler :: IOException -> IO (Either ErrorMessage String)
|
||||
handler ex = return . Left $ show ex
|
||||
|
||||
allowable inputs x =
|
||||
if externalSources options
|
||||
then return True
|
||||
else do
|
||||
path <- normalize x
|
||||
return $ path `elem` inputs
|
||||
|
||||
normalize x =
|
||||
canonicalizePath x `catch` fallback x
|
||||
where
|
||||
fallback :: FilePath -> IOException -> IO FilePath
|
||||
fallback path _ = return path
|
||||
|
||||
inputFile file = do
|
||||
contents <-
|
||||
if file == "-"
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue