mirror of
https://github.com/koalaman/shellcheck.git
synced 2025-09-30 00:39:19 +08:00
Compare commits
11 Commits
dependabot
...
ebuild
Author | SHA1 | Date | |
---|---|---|---|
|
c9b8ad3439 | ||
|
e59fbfebda | ||
|
ce3414eeea | ||
|
feebbbb096 | ||
|
87ef5ae18a | ||
|
0138a6fafc | ||
|
dfa920c5d2 | ||
|
fc9b63fb5e | ||
|
272ef819b9 | ||
|
08ae7ef836 | ||
|
e3d8483e49 |
@@ -93,6 +93,7 @@ library
|
||||
ShellCheck.Formatter.Quiet
|
||||
ShellCheck.Interface
|
||||
ShellCheck.Parser
|
||||
ShellCheck.PortageVariables
|
||||
ShellCheck.Prelude
|
||||
ShellCheck.Regex
|
||||
other-modules:
|
||||
|
@@ -87,8 +87,9 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
|
||||
|
||||
: Specify Bourne shell dialect. Valid values are *sh*, *bash*, *dash* and *ksh*.
|
||||
The default is to deduce the shell from the file's `shell` directive,
|
||||
shebang, or `.bash/.bats/.dash/.ksh` extension, in that order. *sh* refers to
|
||||
POSIX `sh` (not the system's), and will warn of portability issues.
|
||||
shebang, or `.bash/.bats/.dash/.ksh/.ebuild/.eclass` extension, in that
|
||||
order. *sh* refers to POSIX `sh` (not the system's), and will warn of
|
||||
portability issues.
|
||||
|
||||
**-S**\ *SEVERITY*,\ **--severity=***severity*
|
||||
|
||||
|
@@ -21,6 +21,7 @@ import qualified ShellCheck.Analyzer
|
||||
import ShellCheck.Checker
|
||||
import ShellCheck.Data
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.PortageVariables
|
||||
import ShellCheck.Regex
|
||||
|
||||
import qualified ShellCheck.Formatter.CheckStyle
|
||||
@@ -396,10 +397,12 @@ ioInterface options files = do
|
||||
inputs <- mapM normalize files
|
||||
cache <- newIORef emptyCache
|
||||
configCache <- newIORef ("", Nothing)
|
||||
portageVars <- newIORef Nothing
|
||||
return (newSystemInterface :: SystemInterface IO) {
|
||||
siReadFile = get cache inputs,
|
||||
siFindSource = findSourceFile inputs (sourcePaths options),
|
||||
siGetConfig = getConfig configCache
|
||||
siGetConfig = getConfig configCache,
|
||||
siGetPortageVariables = getOrLoadPortage portageVars
|
||||
}
|
||||
where
|
||||
emptyCache :: Map.Map FilePath String
|
||||
@@ -523,6 +526,21 @@ ioInterface options files = do
|
||||
("SCRIPTDIR":rest) -> joinPath (scriptdir:rest)
|
||||
_ -> str
|
||||
|
||||
getOrLoadPortage cache = do
|
||||
x <- readIORef cache
|
||||
case x of
|
||||
Just m -> do
|
||||
return m
|
||||
Nothing -> do
|
||||
vars <- readPortageVariables `catch` handler
|
||||
writeIORef cache $ Just vars
|
||||
return vars
|
||||
where
|
||||
handler :: IOException -> IO (Map.Map String [String])
|
||||
handler e = do
|
||||
hPutStrLn stderr $ "Error finding portage repos, eclass definitions will be ignored: " ++ show e
|
||||
return $ Map.empty
|
||||
|
||||
inputFile file = do
|
||||
(handle, shouldCache) <-
|
||||
if file == "-"
|
||||
|
@@ -36,8 +36,6 @@ import Numeric (showHex)
|
||||
|
||||
import Test.QuickCheck
|
||||
|
||||
arguments (T_SimpleCommand _ _ (cmd:args)) = args
|
||||
|
||||
-- Is this a type of loop?
|
||||
isLoop t = case t of
|
||||
T_WhileExpression {} -> True
|
||||
@@ -546,17 +544,16 @@ getCommandNameAndToken direct t = fromMaybe (Nothing, t) $ do
|
||||
return t
|
||||
_ -> fail ""
|
||||
|
||||
-- If a command substitution is a single command, get its name.
|
||||
-- $(date +%s) = Just "date"
|
||||
getCommandNameFromExpansion :: Token -> Maybe String
|
||||
getCommandNameFromExpansion t =
|
||||
-- If a command substitution is a single SimpleCommand, return it.
|
||||
getSimpleCommandFromExpansion :: Token -> Maybe Token
|
||||
getSimpleCommandFromExpansion t =
|
||||
case t of
|
||||
T_DollarExpansion _ [c] -> extract c
|
||||
T_Backticked _ [c] -> extract c
|
||||
T_DollarBraceCommandExpansion _ [c] -> extract c
|
||||
_ -> Nothing
|
||||
where
|
||||
extract (T_Pipeline _ _ [cmd]) = getCommandName cmd
|
||||
extract (T_Pipeline _ _ [c]) = getCommand c
|
||||
extract _ = Nothing
|
||||
|
||||
-- Get the basename of a token representing a command
|
||||
@@ -564,6 +561,10 @@ getCommandBasename = fmap basename . getCommandName
|
||||
|
||||
basename = reverse . takeWhile (/= '/') . reverse
|
||||
|
||||
-- Get the arguments to a command
|
||||
arguments (T_SimpleCommand _ _ (cmd:args)) = args
|
||||
arguments t = maybe [] arguments (getCommand t)
|
||||
|
||||
isAssignment t =
|
||||
case t of
|
||||
T_Redirecting _ _ w -> isAssignment w
|
||||
@@ -912,5 +913,20 @@ getEnableDirectives root =
|
||||
T_Annotation _ list _ -> [s | EnableComment s <- list]
|
||||
_ -> []
|
||||
|
||||
|
||||
commandExpansionShouldBeSplit t = do
|
||||
cmd <- getSimpleCommandFromExpansion t
|
||||
name <- getCommandName cmd
|
||||
case () of
|
||||
-- Should probably be split
|
||||
_ | name `elem` ["seq", "pgrep"] -> return True
|
||||
-- Portage macros that return a single word or nothing
|
||||
_ | name `elem` ["usev", "use_with", "use_enable"] -> return True
|
||||
-- Portage macros that are fine as long as the arguments have no spaces
|
||||
_ | name `elem` ["usex", "meson_use", "meson_feature"] -> do
|
||||
return . not $ any (' ' `elem`) $ map (getLiteralStringDef " ") $ arguments cmd
|
||||
_ -> Nothing
|
||||
|
||||
|
||||
return []
|
||||
runTests = $quickCheckAll
|
||||
|
@@ -314,7 +314,7 @@ runAndGetComments f s = do
|
||||
let pr = pScript s
|
||||
root <- prRoot pr
|
||||
let spec = defaultSpec pr
|
||||
let params = makeParameters spec
|
||||
let params = runIdentity $ makeParameters (mockedSystemInterface []) spec
|
||||
return $
|
||||
filterByAnnotation spec params $
|
||||
f params root
|
||||
@@ -792,6 +792,11 @@ prop_checkUnquotedExpansions8 = verifyNot checkUnquotedExpansions "set -- $(seq
|
||||
prop_checkUnquotedExpansions9 = verifyNot checkUnquotedExpansions "echo foo `# inline comment`"
|
||||
prop_checkUnquotedExpansions10 = verify checkUnquotedExpansions "#!/bin/sh\nexport var=$(val)"
|
||||
prop_checkUnquotedExpansions11 = verifyNot checkUnquotedExpansions "ps -p $(pgrep foo)"
|
||||
prop_checkUnquotedExpansions12 = verify checkUnquotedExpansions "#!/bin/sh\nexport var=$(val)"
|
||||
prop_checkUnquotedExpansions13 = verifyNot checkUnquotedExpansions "echo $(usev X)"
|
||||
prop_checkUnquotedExpansions14 = verifyNot checkUnquotedExpansions "echo $(usex X \"\" Y)"
|
||||
prop_checkUnquotedExpansions15 = verify checkUnquotedExpansions "echo $(usex X \"Y Z\" W)"
|
||||
|
||||
checkUnquotedExpansions params =
|
||||
check
|
||||
where
|
||||
@@ -801,12 +806,9 @@ checkUnquotedExpansions params =
|
||||
check _ = return ()
|
||||
tree = parentMap params
|
||||
examine t contents =
|
||||
unless (null contents || shouldBeSplit t || isQuoteFree (shellType params) tree t || usedAsCommandName tree t) $
|
||||
unless (null contents || commandExpansionShouldBeSplit t == Just True || isQuoteFree (shellType params) tree t || usedAsCommandName tree t) $
|
||||
warn (getId t) 2046 "Quote this to prevent word splitting."
|
||||
|
||||
shouldBeSplit t =
|
||||
getCommandNameFromExpansion t `elem` [Just "seq", Just "pgrep"]
|
||||
|
||||
|
||||
prop_checkRedirectToSame = verify checkRedirectToSame "cat foo > foo"
|
||||
prop_checkRedirectToSame2 = verify checkRedirectToSame "cat lol | sed -e 's/a/b/g' > lol"
|
||||
@@ -1037,9 +1039,6 @@ checkStderrRedirect params redir@(T_Redirecting _ [
|
||||
|
||||
checkStderrRedirect _ _ = return ()
|
||||
|
||||
lt x = trace ("Tracing " ++ show x) x -- STRIP
|
||||
ltt t = trace ("Tracing " ++ show t) -- STRIP
|
||||
|
||||
|
||||
prop_checkSingleQuotedVariables = verify checkSingleQuotedVariables "echo '$foo'"
|
||||
prop_checkSingleQuotedVariables2 = verify checkSingleQuotedVariables "echo 'lol$1.jpg'"
|
||||
@@ -1070,6 +1069,10 @@ prop_checkSingleQuotedVariables22 = verifyNot checkSingleQuotedVariables "jq '$_
|
||||
prop_checkSingleQuotedVariables23 = verifyNot checkSingleQuotedVariables "command jq '$__loc__'"
|
||||
prop_checkSingleQuotedVariables24 = verifyNot checkSingleQuotedVariables "exec jq '$__loc__'"
|
||||
prop_checkSingleQuotedVariables25 = verifyNot checkSingleQuotedVariables "exec -c -a foo jq '$__loc__'"
|
||||
prop_checkSingleQuotedVariablesCros1 = verifyNot checkSingleQuotedVariables "python_gen_any_dep 'dev-python/pyyaml[${PYTHON_USEDEP}]'"
|
||||
prop_checkSingleQuotedVariablesCros2 = verifyNot checkSingleQuotedVariables "python_gen_cond_dep 'dev-python/unittest2[${PYTHON_USEDEP}]' python2_7 pypy"
|
||||
prop_checkSingleQuotedVariablesCros3 = verifyNot checkSingleQuotedVariables "version_format_string '${PN}_source_$1_$2-$3_$4'"
|
||||
|
||||
|
||||
|
||||
checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
|
||||
@@ -1109,6 +1112,9 @@ checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
|
||||
,"git filter-branch"
|
||||
,"mumps -run %XCMD"
|
||||
,"mumps -run LOOP%XCMD"
|
||||
,"python_gen_any_dep"
|
||||
,"python_gen_cond_dep"
|
||||
,"version_format_string"
|
||||
]
|
||||
|| "awk" `isSuffixOf` commandName
|
||||
|| "perl" `isPrefixOf` commandName
|
||||
@@ -2392,7 +2398,7 @@ checkUnusedAssignments params t = execWriter (mapM_ warnFor unused)
|
||||
name ++ " appears unused. Verify use (or export if used externally)."
|
||||
|
||||
stripSuffix = takeWhile isVariableChar
|
||||
defaultMap = Map.fromList $ zip internalVariables $ repeat ()
|
||||
defaultMap = Map.fromList $ zip (internalVariables ++ additionalKnownVariables params) $ repeat ()
|
||||
|
||||
prop_checkUnassignedReferences1 = verifyTree checkUnassignedReferences "echo $foo"
|
||||
prop_checkUnassignedReferences2 = verifyNotTree checkUnassignedReferences "foo=hello; echo $foo"
|
||||
@@ -2451,7 +2457,7 @@ checkUnassignedReferences = checkUnassignedReferences' False
|
||||
checkUnassignedReferences' includeGlobals params t = warnings
|
||||
where
|
||||
(readMap, writeMap) = execState (mapM tally $ variableFlow params) (Map.empty, Map.empty)
|
||||
defaultAssigned = Map.fromList $ map (\a -> (a, ())) $ filter (not . null) internalVariables
|
||||
defaultAssigned = Map.fromList $ map (\a -> (a, ())) $ filter (not . null) (internalVariables ++ additionalKnownVariables params)
|
||||
|
||||
tally (Assignment (_, _, name, _)) =
|
||||
modify (\(read, written) -> (read, Map.insert name () written))
|
||||
@@ -3509,6 +3515,7 @@ prop_checkSplittingInArrays5 = verifyNot checkSplittingInArrays "a=( $! $$ $# )"
|
||||
prop_checkSplittingInArrays6 = verifyNot checkSplittingInArrays "a=( ${#arr[@]} )"
|
||||
prop_checkSplittingInArrays7 = verifyNot checkSplittingInArrays "a=( foo{1,2} )"
|
||||
prop_checkSplittingInArrays8 = verifyNot checkSplittingInArrays "a=( * )"
|
||||
prop_checkSplittingInArrays9 = verifyNot checkSplittingInArrays "a=( $(use_enable foo) )"
|
||||
checkSplittingInArrays params t =
|
||||
case t of
|
||||
T_Array _ elements -> mapM_ check elements
|
||||
@@ -3518,6 +3525,7 @@ checkSplittingInArrays params t =
|
||||
T_NormalWord _ parts -> mapM_ checkPart parts
|
||||
_ -> return ()
|
||||
checkPart part = case part of
|
||||
_ | commandExpansionShouldBeSplit part == Just True -> return ()
|
||||
T_DollarExpansion id _ -> forCommand id
|
||||
T_DollarBraceCommandExpansion id _ -> forCommand id
|
||||
T_Backticked id _ -> forCommand id
|
||||
|
@@ -31,14 +31,14 @@ import qualified ShellCheck.Checks.ShellSupport
|
||||
|
||||
|
||||
-- TODO: Clean up the cruft this is layered on
|
||||
analyzeScript :: AnalysisSpec -> AnalysisResult
|
||||
analyzeScript spec = newAnalysisResult {
|
||||
analyzeScript :: Monad m => SystemInterface m -> AnalysisSpec -> m AnalysisResult
|
||||
analyzeScript sys spec = do
|
||||
params <- makeParameters sys spec
|
||||
return $ newAnalysisResult {
|
||||
arComments =
|
||||
filterByAnnotation spec params . nub $
|
||||
runChecker params (checkers spec params)
|
||||
}
|
||||
where
|
||||
params = makeParameters spec
|
||||
|
||||
checkers spec params = mconcat $ map ($ params) [
|
||||
ShellCheck.Analytics.checker spec,
|
||||
|
@@ -88,6 +88,8 @@ data Parameters = Parameters {
|
||||
hasSetE :: Bool,
|
||||
-- Whether this script has 'set -o pipefail' anywhere.
|
||||
hasPipefail :: Bool,
|
||||
-- Whether this script is an Ebuild file.
|
||||
isPortage :: Bool,
|
||||
-- A linear (bad) analysis of data flow
|
||||
variableFlow :: [StackData],
|
||||
-- A map from Id to Token
|
||||
@@ -103,9 +105,12 @@ data Parameters = Parameters {
|
||||
-- map from token id to start and end position
|
||||
tokenPositions :: Map.Map Id (Position, Position),
|
||||
-- Result from Control Flow Graph analysis (including data flow analysis)
|
||||
cfgAnalysis :: CF.CFGAnalysis
|
||||
cfgAnalysis :: CF.CFGAnalysis,
|
||||
-- A set of additional variables known to be set (TODO: make this more general?)
|
||||
additionalKnownVariables :: [String]
|
||||
} deriving (Show)
|
||||
|
||||
|
||||
-- TODO: Cache results of common AST ops here
|
||||
data Cache = Cache {}
|
||||
|
||||
@@ -152,7 +157,7 @@ producesComments c s = do
|
||||
let pr = pScript s
|
||||
prRoot pr
|
||||
let spec = defaultSpec pr
|
||||
let params = makeParameters spec
|
||||
let params = runIdentity $ makeParameters (mockedSystemInterface []) spec
|
||||
return . not . null $ filterByAnnotation spec params $ runChecker params c
|
||||
|
||||
makeComment :: Severity -> Id -> Code -> String -> TokenComment
|
||||
@@ -196,11 +201,25 @@ makeCommentWithFix severity id code str fix =
|
||||
}
|
||||
in force withFix
|
||||
|
||||
makeParameters spec = params
|
||||
makeParameters :: Monad m => SystemInterface m -> AnalysisSpec -> m Parameters
|
||||
makeParameters sys spec = do
|
||||
extraVars <-
|
||||
if asIsPortage spec
|
||||
then do
|
||||
vars <- siGetPortageVariables sys
|
||||
let classes = getInheritedEclasses root
|
||||
return $ concatMap (\c -> Map.findWithDefault [] c vars) classes
|
||||
else
|
||||
return []
|
||||
|
||||
return $ makeParams extraVars
|
||||
where
|
||||
shell = fromMaybe (determineShell (asFallbackShell spec) root) $ asShellType spec
|
||||
makeParams extraVars = params
|
||||
where
|
||||
params = Parameters {
|
||||
rootNode = root,
|
||||
shellType = fromMaybe (determineShell (asFallbackShell spec) root) $ asShellType spec,
|
||||
shellType = shell,
|
||||
hasSetE = containsSetE root,
|
||||
hasLastpipe =
|
||||
case shellType params of
|
||||
@@ -221,15 +240,18 @@ makeParameters spec = params
|
||||
Sh -> True
|
||||
Ksh -> isOptionSet "pipefail" root,
|
||||
shellTypeSpecified = isJust (asShellType spec) || isJust (asFallbackShell spec),
|
||||
isPortage = asIsPortage spec,
|
||||
idMap = getTokenMap root,
|
||||
parentMap = getParentTree root,
|
||||
variableFlow = getVariableFlow params root,
|
||||
tokenPositions = asTokenPositions spec,
|
||||
cfgAnalysis = CF.analyzeControlFlow cfParams root
|
||||
cfgAnalysis = CF.analyzeControlFlow cfParams root,
|
||||
additionalKnownVariables = extraVars
|
||||
}
|
||||
cfParams = CF.CFGParameters {
|
||||
CF.cfLastpipe = hasLastpipe params,
|
||||
CF.cfPipefail = hasPipefail params
|
||||
CF.cfPipefail = hasPipefail params,
|
||||
CF.cfAdditionalInitialVariables = additionalKnownVariables params
|
||||
}
|
||||
root = asScript spec
|
||||
|
||||
@@ -582,6 +604,17 @@ getReferencedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Litera
|
||||
head:_ -> map (\x -> (base, head, x)) $ getVariablesFromLiteralToken head
|
||||
_ -> []
|
||||
"alias" -> [(base, token, name) | token <- rest, name <- getVariablesFromLiteralToken token]
|
||||
|
||||
-- tc-export makes a list of toolchain variables available, similar to export.
|
||||
-- Usage tc-export CC CXX
|
||||
"tc-export" -> concatMap getReference rest
|
||||
|
||||
-- tc-export_build_env exports the listed variables plus a bunch of BUILD_XX variables.
|
||||
-- Usage tc-export_build_env BUILD_CC
|
||||
"tc-export_build_env" ->
|
||||
concatMap getReference rest
|
||||
++ [ (base, base, v) | v <- portageBuildEnvVariables ]
|
||||
|
||||
_ -> []
|
||||
where
|
||||
forDeclare =
|
||||
@@ -653,6 +686,16 @@ getModifiedVariableCommand base@(T_SimpleCommand id cmdPrefix (T_NormalWord _ (T
|
||||
"DEFINE_integer" -> maybeToList $ getFlagVariable rest
|
||||
"DEFINE_string" -> maybeToList $ getFlagVariable rest
|
||||
|
||||
"tc-export" -> concatMap getModifierParamString rest
|
||||
|
||||
-- tc-export_build_env exports the listed variables plus a bunch of BUILD_XX variables.
|
||||
-- Usage tc-export_build_env BUILD_CC
|
||||
"tc-export_build_env" ->
|
||||
concatMap getModifierParamString rest
|
||||
++ [ (base, base, var, DataString $ SourceExternal) |
|
||||
var <- ["BUILD_" ++ x, x ++ "_FOR_BUILD" ],
|
||||
x <- portageBuildEnvVariables ]
|
||||
|
||||
_ -> []
|
||||
where
|
||||
flags = map snd $ getAllFlags base
|
||||
@@ -918,6 +961,13 @@ modifiesVariable params token name =
|
||||
Assignment (_, _, n, source) -> isTrueAssignmentSource source && n == name
|
||||
_ -> False
|
||||
|
||||
-- Ebuild files inherit eclasses using 'inherit myclass1 myclass2'
|
||||
getInheritedEclasses :: Token -> [String]
|
||||
getInheritedEclasses root = execWriter $ doAnalysis findInheritedEclasses root
|
||||
where
|
||||
findInheritedEclasses cmd
|
||||
| cmd `isCommand` "inherit" = tell $ catMaybes $ getLiteralString <$> (arguments cmd)
|
||||
findInheritedEclasses _ = return ()
|
||||
|
||||
return []
|
||||
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
||||
|
@@ -167,7 +167,9 @@ data CFGParameters = CFGParameters {
|
||||
-- Whether the last element in a pipeline runs in the current shell
|
||||
cfLastpipe :: Bool,
|
||||
-- Whether all elements in a pipeline count towards the exit status
|
||||
cfPipefail :: Bool
|
||||
cfPipefail :: Bool,
|
||||
-- Additional variables to consider defined
|
||||
cfAdditionalInitialVariables :: [String]
|
||||
}
|
||||
|
||||
data CFGResult = CFGResult {
|
||||
|
@@ -197,12 +197,13 @@ unreachableState = modified newInternalState {
|
||||
}
|
||||
|
||||
-- The default state we assume we get from the environment
|
||||
createEnvironmentState :: InternalState
|
||||
createEnvironmentState = do
|
||||
createEnvironmentState :: CFGParameters -> InternalState
|
||||
createEnvironmentState params = do
|
||||
foldl' (flip ($)) newInternalState $ concat [
|
||||
addVars Data.internalVariables unknownVariableState,
|
||||
addVars Data.variablesWithoutSpaces spacelessVariableState,
|
||||
addVars Data.specialIntegerVariables integerVariableState
|
||||
addVars Data.specialIntegerVariables integerVariableState,
|
||||
addVars (cfAdditionalInitialVariables params) unknownVariableState
|
||||
]
|
||||
where
|
||||
addVars names val = map (\name -> insertGlobal name val) names
|
||||
@@ -1344,7 +1345,7 @@ analyzeControlFlow params t =
|
||||
runST $ f cfg entry exit
|
||||
where
|
||||
f cfg entry exit = do
|
||||
let env = createEnvironmentState
|
||||
let env = createEnvironmentState params
|
||||
ctx <- newCtx $ cfGraph cfg
|
||||
-- Do a dataflow analysis starting on the root node
|
||||
exitState <- runRoot ctx env entry exit
|
||||
|
@@ -25,6 +25,7 @@ import ShellCheck.ASTLib
|
||||
import ShellCheck.Interface
|
||||
import ShellCheck.Parser
|
||||
|
||||
import Data.Char
|
||||
import Data.Either
|
||||
import Data.Functor
|
||||
import Data.List
|
||||
@@ -54,6 +55,8 @@ shellFromFilename filename = listToMaybe candidates
|
||||
shellExtensions = [(".ksh", Ksh)
|
||||
,(".bash", Bash)
|
||||
,(".bats", Bash)
|
||||
,(".ebuild", Bash)
|
||||
,(".eclass", Bash)
|
||||
,(".dash", Dash)]
|
||||
-- The `.sh` is too generic to determine the shell:
|
||||
-- We fallback to Bash in this case and emit SC2148 if there is no shebang
|
||||
@@ -84,18 +87,24 @@ checkScript sys spec = do
|
||||
asShellType = csShellTypeOverride spec,
|
||||
asFallbackShell = shellFromFilename $ csFilename spec,
|
||||
asCheckSourced = csCheckSourced spec,
|
||||
asIsPortage = isPortage $ csFilename spec,
|
||||
asExecutionMode = Executed,
|
||||
asTokenPositions = tokenPositions,
|
||||
asOptionalChecks = getEnableDirectives root ++ csOptionalChecks spec
|
||||
} where as = newAnalysisSpec root
|
||||
let analysisMessages =
|
||||
maybe []
|
||||
(arComments . analyzeScript . analysisSpec)
|
||||
$ prRoot result
|
||||
let getAnalysisMessages =
|
||||
case prRoot result of
|
||||
Just root -> arComments <$> (analyzeScript sys $ analysisSpec root)
|
||||
Nothing -> return []
|
||||
let translator = tokenToPosition tokenPositions
|
||||
analysisMessages <- getAnalysisMessages
|
||||
return . nub . sortMessages . filter shouldInclude $
|
||||
(parseMessages ++ map translator analysisMessages)
|
||||
|
||||
isPortage filename =
|
||||
let f = map toLower filename in
|
||||
".ebuild" `isSuffixOf` f || ".eclass" `isSuffixOf` f
|
||||
|
||||
shouldInclude pc =
|
||||
severity <= csMinSeverity spec &&
|
||||
case csIncludedWarnings spec of
|
||||
|
@@ -62,8 +62,92 @@ internalVariables = [
|
||||
, "FLAGS_ARGC", "FLAGS_ARGV", "FLAGS_ERROR", "FLAGS_FALSE", "FLAGS_HELP",
|
||||
"FLAGS_PARENT", "FLAGS_RESERVED", "FLAGS_TRUE", "FLAGS_VERSION",
|
||||
"flags_error", "flags_return"
|
||||
] ++ portageManualInternalVariables
|
||||
|
||||
|
||||
portageManualInternalVariables = [
|
||||
-- toolchain settings
|
||||
"CFLAGS", "CXXFLAGS", "CPPFLAGS", "LDFLAGS", "FFLAGS", "FCFLAGS",
|
||||
"CBUILD", "CHOST", "MAKEOPTS",
|
||||
-- TODO: Delete these if we can handle `tc-export CC` implicit export.
|
||||
"CC", "CPP", "CXX",
|
||||
|
||||
-- portage internals
|
||||
"EBUILD_PHASE", "EBUILD_SH_ARGS", "EMERGE_FROM", "FILESDIR",
|
||||
"MERGE_TYPE", "PM_EBUILD_HOOK_DIR", "PORTAGE_ACTUAL_DISTDIR",
|
||||
"PORTAGE_ARCHLIST", "PORTAGE_BASHRC", "PORTAGE_BINPKG_FILE",
|
||||
"PORTAGE_BINPKG_TAR_OPTS", "PORTAGE_BINPKG_TMPFILE", "PORTAGE_BIN_PATH",
|
||||
"PORTAGE_BUILDDIR", "PORTAGE_BUILD_GROUP", "PORTAGE_BUILD_USER",
|
||||
"PORTAGE_BUNZIP2_COMMAND", "PORTAGE_BZIP2_COMMAND", "PORTAGE_COLORMAP",
|
||||
"PORTAGE_CONFIGROOT", "PORTAGE_DEBUG", "PORTAGE_DEPCACHEDIR",
|
||||
"PORTAGE_EBUILD_EXIT_FILE", "PORTAGE_ECLASS_LOCATIONS", "PORTAGE_GID",
|
||||
"PORTAGE_GRPNAME", "PORTAGE_INST_GID", "PORTAGE_INST_UID",
|
||||
"PORTAGE_INTERNAL_CALLER", "PORTAGE_IPC_DAEMON", "PORTAGE_IUSE",
|
||||
"PORTAGE_LOG_FILE", "PORTAGE_MUTABLE_FILTERED_VARS",
|
||||
"PORTAGE_OVERRIDE_EPREFIX", "PORTAGE_PYM_PATH", "PORTAGE_PYTHON",
|
||||
"PORTAGE_PYTHONPATH", "PORTAGE_READONLY_METADATA", "PORTAGE_READONLY_VARS",
|
||||
"PORTAGE_REPO_NAME", "PORTAGE_REPOSITORIES", "PORTAGE_RESTRICT",
|
||||
"PORTAGE_SAVED_READONLY_VARS", "PORTAGE_SIGPIPE_STATUS", "PORTAGE_TMPDIR",
|
||||
"PORTAGE_UPDATE_ENV", "PORTAGE_USERNAME", "PORTAGE_VERBOSE",
|
||||
"PORTAGE_WORKDIR_MODE", "PORTAGE_XATTR_EXCLUDE", "REPLACING_VERSIONS",
|
||||
"REPLACED_BY_VERSION", "__PORTAGE_HELPER", "__PORTAGE_TEST_HARDLINK_LOCKS",
|
||||
|
||||
-- generic ebuilds
|
||||
"A", "ARCH", "BDEPEND", "BOARD_USE", "BROOT", "CATEGORY", "D",
|
||||
"DEFINED_PHASES", "DEPEND", "DESCRIPTION", "DISTDIR", "DOCS", "EAPI",
|
||||
"ECLASS", "ED", "EPREFIX", "EROOT", "ESYSROOT", "EXTRA_ECONF",
|
||||
"EXTRA_EINSTALL", "EXTRA_MAKE", "FEATURES", "FILESDIR", "HOME", "HOMEPAGE",
|
||||
"HTML_DOCS", "INHERITED", "IUSE", "KEYWORDS", "LICENSE", "P", "PATCHES",
|
||||
"PDEPEND", "PF", "PKG_INSTALL_MASK", "PKGUSE", "PN", "PR", "PROPERTIES",
|
||||
"PROVIDES_EXCLUDE", "PV", "PVR", "QA_AM_MAINTAINER_MODE",
|
||||
"QA_CONFIGURE_OPTIONS", "QA_DESKTOP_FILE", "QA_DT_NEEDED", "QA_EXECSTACK",
|
||||
"QA_FLAGS_IGNORED", "QA_MULTILIB_PATHS", "QA_PREBUILT", "QA_PRESTRIPPED",
|
||||
"QA_SONAME", "QA_SONAME_NO_SYMLINK", "QA_TEXTRELS", "QA_WX_LOAD", "RDEPEND",
|
||||
"REPOSITORY", "REQUIRED_USE", "REQUIRES_EXCLUDE", "RESTRICT", "ROOT", "S",
|
||||
"SLOT", "SRC_TEST", "SRC_URI", "STRIP_MASK", "SUBSLOT", "SYSROOT", "T",
|
||||
"WORKDIR",
|
||||
|
||||
-- autotest.eclass declared incorrectly
|
||||
"AUTOTEST_CLIENT_TESTS", "AUTOTEST_CLIENT_SITE_TESTS",
|
||||
"AUTOTEST_SERVER_TESTS", "AUTOTEST_SERVER_SITE_TESTS", "AUTOTEST_CONFIG",
|
||||
"AUTOTEST_DEPS", "AUTOTEST_PROFILERS", "AUTOTEST_CONFIG_LIST",
|
||||
"AUTOTEST_DEPS_LIST", "AUTOTEST_PROFILERS_LIST",
|
||||
|
||||
-- cros-board.eclass declared incorrectly
|
||||
"CROS_BOARDS",
|
||||
|
||||
-- Undeclared cros-kernel2 vars
|
||||
"AFDO_PROFILE_VERSION",
|
||||
|
||||
-- haskell-cabal.eclass declared incorrectly
|
||||
"CABAL_FEATURES",
|
||||
|
||||
-- Undeclared haskell-cabal.eclass vars
|
||||
"CABAL_CORE_LIB_GHC_PV",
|
||||
|
||||
-- Undeclared readme.gentoo.eclass vars
|
||||
"DOC_CONTENTS",
|
||||
|
||||
-- Backwards compatibility perl-module.eclass vars
|
||||
"MODULE_AUTHOR", "MODULE_VERSION",
|
||||
|
||||
-- Undeclared perl-module.eclass vars
|
||||
"mydoc",
|
||||
|
||||
-- python-utils-r1.eclass declared incorrectly
|
||||
"RESTRICT_PYTHON_ABIS", "PYTHON_MODNAME",
|
||||
|
||||
-- ABI variables
|
||||
"ABI", "DEFAULT_ABI",
|
||||
|
||||
-- AFDO variables
|
||||
"AFDO_LOCATION",
|
||||
|
||||
-- Linguas
|
||||
"LINGUAS"
|
||||
]
|
||||
|
||||
|
||||
specialIntegerVariables = [
|
||||
"$", "?", "!", "#"
|
||||
]
|
||||
@@ -90,7 +174,9 @@ unbracedVariables = specialVariables ++ [
|
||||
arrayVariables = [
|
||||
"BASH_ALIASES", "BASH_ARGC", "BASH_ARGV", "BASH_CMDS", "BASH_LINENO",
|
||||
"BASH_REMATCH", "BASH_SOURCE", "BASH_VERSINFO", "COMP_WORDS", "COPROC",
|
||||
"DIRSTACK", "FUNCNAME", "GROUPS", "MAPFILE", "PIPESTATUS", "COMPREPLY"
|
||||
"DIRSTACK", "FUNCNAME", "GROUPS", "MAPFILE", "PIPESTATUS", "COMPREPLY",
|
||||
-- For Portage
|
||||
"PATCHES"
|
||||
]
|
||||
|
||||
commonCommands = [
|
||||
@@ -150,6 +236,11 @@ unaryTestOps = [
|
||||
"-o", "-v", "-R"
|
||||
]
|
||||
|
||||
-- Variables inspected by Portage tc-export_build_env
|
||||
portageBuildEnvVariables = [
|
||||
"CFLAGS", "CXXFLAGS", "CPPFLAGS", "LDFLAGS"
|
||||
]
|
||||
|
||||
shellForExecutable :: String -> Maybe Shell
|
||||
shellForExecutable name =
|
||||
case name of
|
||||
|
@@ -117,7 +117,8 @@ dummySystemInterface = mockedSystemInterface [
|
||||
cfgParams :: CFGParameters
|
||||
cfgParams = CFGParameters {
|
||||
cfLastpipe = False,
|
||||
cfPipefail = False
|
||||
cfPipefail = False,
|
||||
cfAdditionalInitialVariables = []
|
||||
}
|
||||
|
||||
-- An example script to play with
|
||||
|
@@ -25,7 +25,7 @@ module ShellCheck.Interface
|
||||
, CheckResult(crFilename, crComments)
|
||||
, ParseSpec(psFilename, psScript, psCheckSourced, psIgnoreRC, psShellTypeOverride)
|
||||
, ParseResult(prComments, prTokenPositions, prRoot)
|
||||
, AnalysisSpec(asScript, asShellType, asFallbackShell, asExecutionMode, asCheckSourced, asTokenPositions, asOptionalChecks)
|
||||
, AnalysisSpec(..)
|
||||
, AnalysisResult(arComments)
|
||||
, FormatterOptions(foColorOption, foWikiLinkCount)
|
||||
, Shell(Ksh, Sh, Bash, Dash)
|
||||
@@ -87,7 +87,9 @@ data SystemInterface m = SystemInterface {
|
||||
-- find the sourced file
|
||||
siFindSource :: String -> Maybe Bool -> [String] -> String -> m FilePath,
|
||||
-- | Get the configuration file (name, contents) for a filename
|
||||
siGetConfig :: String -> m (Maybe (FilePath, String))
|
||||
siGetConfig :: String -> m (Maybe (FilePath, String)),
|
||||
-- | Look up Portage Eclass variables
|
||||
siGetPortageVariables :: m (Map.Map String [String])
|
||||
}
|
||||
|
||||
-- ShellCheck input and output
|
||||
@@ -141,7 +143,8 @@ newSystemInterface =
|
||||
SystemInterface {
|
||||
siReadFile = \_ _ -> return $ Left "Not implemented",
|
||||
siFindSource = \_ _ _ name -> return name,
|
||||
siGetConfig = \_ -> return Nothing
|
||||
siGetConfig = \_ -> return Nothing,
|
||||
siGetPortageVariables = return Map.empty
|
||||
}
|
||||
|
||||
-- Parser input and output
|
||||
@@ -173,6 +176,7 @@ data AnalysisSpec = AnalysisSpec {
|
||||
asFallbackShell :: Maybe Shell,
|
||||
asExecutionMode :: ExecutionMode,
|
||||
asCheckSourced :: Bool,
|
||||
asIsPortage :: Bool,
|
||||
asOptionalChecks :: [String],
|
||||
asTokenPositions :: Map.Map Id (Position, Position)
|
||||
}
|
||||
@@ -183,6 +187,7 @@ newAnalysisSpec token = AnalysisSpec {
|
||||
asFallbackShell = Nothing,
|
||||
asExecutionMode = Executed,
|
||||
asCheckSourced = False,
|
||||
asIsPortage = False,
|
||||
asOptionalChecks = [],
|
||||
asTokenPositions = Map.empty
|
||||
}
|
||||
|
138
src/ShellCheck/PortageVariables.hs
Normal file
138
src/ShellCheck/PortageVariables.hs
Normal file
@@ -0,0 +1,138 @@
|
||||
{-# LANGUAGE ApplicativeDo #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
|
||||
module ShellCheck.PortageVariables (
|
||||
readPortageVariables
|
||||
) where
|
||||
|
||||
import ShellCheck.Regex
|
||||
|
||||
import Control.Exception
|
||||
import Control.Monad
|
||||
import Data.Maybe
|
||||
import System.Directory (listDirectory)
|
||||
import System.Exit (ExitCode(..))
|
||||
import System.FilePath
|
||||
import System.IO
|
||||
import System.Process
|
||||
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.Map as M
|
||||
|
||||
type RepoName = String
|
||||
type RepoPath = String
|
||||
type EclassName = String
|
||||
type EclassVar = String
|
||||
|
||||
-- | This is used for looking up what eclass variables are inherited,
|
||||
-- keyed by the name of the eclass.
|
||||
type EclassMap = M.Map EclassName [EclassVar]
|
||||
|
||||
data Repository = Repository
|
||||
{ repositoryName :: RepoName
|
||||
, repositoryLocation :: RepoPath
|
||||
, repositoryEclasses :: [Eclass]
|
||||
} deriving (Show, Eq, Ord)
|
||||
|
||||
data Eclass = Eclass
|
||||
{ eclassName :: EclassName
|
||||
, eclassVars :: [EclassVar]
|
||||
} deriving (Show, Eq, Ord)
|
||||
|
||||
readPortageVariables :: IO (M.Map String [String])
|
||||
readPortageVariables = portageVariables <$> scanRepos
|
||||
|
||||
-- | Map from eclass names to a list of eclass variables
|
||||
portageVariables :: [Repository] -> EclassMap
|
||||
portageVariables = foldMap $ foldMap go . repositoryEclasses
|
||||
where
|
||||
go e = M.singleton (eclassName e) (eclassVars e)
|
||||
|
||||
-- | Run @portageq@ to gather a list of repo names and paths, then scan each
|
||||
-- one for eclasses and ultimately eclass metadata.
|
||||
scanRepos :: IO [Repository]
|
||||
scanRepos = do
|
||||
let cmd = "portageq"
|
||||
let args = ["repos_config", "/"]
|
||||
out <- runOrDie cmd args
|
||||
forM (reposParser $ lines out) $ \(n,p) -> Repository n p <$> getEclasses p
|
||||
|
||||
-- | Get the name of the repo and its path from blocks outputted by
|
||||
-- @portageq@. If the path doesn't exist, this will return @Nothing@.
|
||||
reposParser :: [String] -> [(RepoName, RepoPath)]
|
||||
reposParser = f ""
|
||||
where
|
||||
segmentRegex = mkRegex "^\\[(.*)\\].*"
|
||||
locationRegex = mkRegex "^[[:space:]]*location[[:space:]]*=[[:space:]]*(.*)[[:space:]]*$"
|
||||
f name [] = []
|
||||
f name (line:rest) =
|
||||
case (matchRegex segmentRegex line, matchRegex locationRegex line) of
|
||||
(Just [next], _) -> f next rest
|
||||
(_, Just [location]) -> (name, location) : f name rest
|
||||
_ -> f name rest
|
||||
|
||||
-- | Scan the repo path for @*.eclass@ files in @eclass/@, then run
|
||||
-- 'eclassParser' on each of them to produce @[Eclass]@.
|
||||
--
|
||||
-- If the @eclass/@ directory doesn't exist, the scan is skipped for that
|
||||
-- repo.
|
||||
getEclasses :: RepoPath -> IO [Eclass]
|
||||
getEclasses repoLoc = do
|
||||
let eclassDir = repoLoc </> "eclass"
|
||||
|
||||
files <- handle catcher $ listDirectory eclassDir
|
||||
let names = filter (\(_, e) -> e == ".eclass") $ map splitExtension files
|
||||
|
||||
forM (names :: [(String, String)]) $ \(name, ext) -> do
|
||||
contents <- withFile (eclassDir </> name <.> ext) ReadMode readFully
|
||||
return $ Eclass name $ eclassParser (lines contents)
|
||||
|
||||
where
|
||||
catcher :: IOException -> IO [String]
|
||||
catcher e = do
|
||||
hPutStrLn stderr $ "Unable to find .eclass files: " ++ show e
|
||||
return []
|
||||
|
||||
-- | Scan a @.eclass@ file for any @@@ECLASS_VARIABLE:@ comments, generating
|
||||
-- a list of eclass variables.
|
||||
eclassParser :: [String] -> [String]
|
||||
eclassParser lines = mapMaybe match lines
|
||||
where
|
||||
varRegex = mkRegex "^[[:space:]]*#[[:space:]]*@ECLASS_VARIABLE:[[:space:]]*([^[:space:]]*)[[:space:]]*$"
|
||||
match str = head <$> matchRegex varRegex str
|
||||
|
||||
-- | Run the command and return the full stdout string (stdin is ignored).
|
||||
--
|
||||
-- If the command exits with a non-zero exit code, this will throw an
|
||||
-- error including the captured contents of stdout and stderr.
|
||||
runOrDie :: FilePath -> [String] -> IO String
|
||||
runOrDie cmd args = bracket acquire release $ \(_,o,e,p) -> do
|
||||
ot <- readFully (fromJust o)
|
||||
et <- readFully (fromJust e)
|
||||
ec <- waitForProcess p
|
||||
case ec of
|
||||
ExitSuccess -> pure ot
|
||||
ExitFailure i -> fail $ unlines $ map unwords
|
||||
$ [ [ show cmd ]
|
||||
++ map show args
|
||||
++ [ "failed with exit code", show i]
|
||||
, [ "stdout:" ], [ ot ]
|
||||
, [ "stderr:" ], [ et ]
|
||||
]
|
||||
where
|
||||
acquire = createProcess (proc cmd args)
|
||||
{ std_in = NoStream
|
||||
, std_out = CreatePipe
|
||||
, std_err = CreatePipe
|
||||
}
|
||||
release (i,o,e,p) = do
|
||||
_ <- waitForProcess p
|
||||
forM_ [i,o,e] $ mapM_ hClose
|
||||
|
||||
readFully :: Handle -> IO String
|
||||
readFully handle = do
|
||||
hSetBinaryMode handle True
|
||||
str <- hGetContents handle
|
||||
length str `seq` return str
|
Reference in New Issue
Block a user