mirror of
https://github.com/koalaman/shellcheck
synced 2025-07-08 14:01:11 -07:00
Example plumbing for Portage variables
This commit is contained in:
parent
90d3172dfe
commit
0138a6fafc
9 changed files with 96 additions and 59 deletions
|
@ -396,10 +396,12 @@ ioInterface options files = do
|
||||||
inputs <- mapM normalize files
|
inputs <- mapM normalize files
|
||||||
cache <- newIORef emptyCache
|
cache <- newIORef emptyCache
|
||||||
configCache <- newIORef ("", Nothing)
|
configCache <- newIORef ("", Nothing)
|
||||||
|
portageVars <- newIORef Nothing
|
||||||
return (newSystemInterface :: SystemInterface IO) {
|
return (newSystemInterface :: SystemInterface IO) {
|
||||||
siReadFile = get cache inputs,
|
siReadFile = get cache inputs,
|
||||||
siFindSource = findSourceFile inputs (sourcePaths options),
|
siFindSource = findSourceFile inputs (sourcePaths options),
|
||||||
siGetConfig = getConfig configCache
|
siGetConfig = getConfig configCache,
|
||||||
|
siGetPortageVariables = getOrLoadPortage portageVars
|
||||||
}
|
}
|
||||||
where
|
where
|
||||||
emptyCache :: Map.Map FilePath String
|
emptyCache :: Map.Map FilePath String
|
||||||
|
@ -523,6 +525,18 @@ ioInterface options files = do
|
||||||
("SCRIPTDIR":rest) -> joinPath (scriptdir:rest)
|
("SCRIPTDIR":rest) -> joinPath (scriptdir:rest)
|
||||||
_ -> str
|
_ -> str
|
||||||
|
|
||||||
|
getOrLoadPortage cache = do
|
||||||
|
x <- readIORef cache
|
||||||
|
case x of
|
||||||
|
Just m -> do
|
||||||
|
hPutStrLn stderr "Reusing previous Portage variables"
|
||||||
|
return m
|
||||||
|
Nothing -> do
|
||||||
|
hPutStrLn stderr "Computing Portage variables"
|
||||||
|
vars <- return $ Map.fromList [("foo", ["bar", "baz"])] -- TODO: Actually read the variables
|
||||||
|
writeIORef cache $ Just vars
|
||||||
|
return vars
|
||||||
|
|
||||||
inputFile file = do
|
inputFile file = do
|
||||||
(handle, shouldCache) <-
|
(handle, shouldCache) <-
|
||||||
if file == "-"
|
if file == "-"
|
||||||
|
|
|
@ -314,7 +314,7 @@ runAndGetComments f s = do
|
||||||
let pr = pScript s
|
let pr = pScript s
|
||||||
root <- prRoot pr
|
root <- prRoot pr
|
||||||
let spec = defaultSpec pr
|
let spec = defaultSpec pr
|
||||||
let params = makeParameters spec
|
let params = runIdentity $ makeParameters (mockedSystemInterface []) spec
|
||||||
return $
|
return $
|
||||||
filterByAnnotation spec params $
|
filterByAnnotation spec params $
|
||||||
f params root
|
f params root
|
||||||
|
@ -2451,7 +2451,7 @@ checkUnassignedReferences = checkUnassignedReferences' False
|
||||||
checkUnassignedReferences' includeGlobals params t = warnings
|
checkUnassignedReferences' includeGlobals params t = warnings
|
||||||
where
|
where
|
||||||
(readMap, writeMap) = execState (mapM tally $ variableFlow params) (Map.empty, Map.empty)
|
(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, _)) =
|
tally (Assignment (_, _, name, _)) =
|
||||||
modify (\(read, written) -> (read, Map.insert name () written))
|
modify (\(read, written) -> (read, Map.insert name () written))
|
||||||
|
|
|
@ -31,14 +31,14 @@ import qualified ShellCheck.Checks.ShellSupport
|
||||||
|
|
||||||
|
|
||||||
-- TODO: Clean up the cruft this is layered on
|
-- TODO: Clean up the cruft this is layered on
|
||||||
analyzeScript :: AnalysisSpec -> AnalysisResult
|
analyzeScript :: Monad m => SystemInterface m -> AnalysisSpec -> m AnalysisResult
|
||||||
analyzeScript spec = newAnalysisResult {
|
analyzeScript sys spec = do
|
||||||
|
params <- makeParameters sys spec
|
||||||
|
return $ newAnalysisResult {
|
||||||
arComments =
|
arComments =
|
||||||
filterByAnnotation spec params . nub $
|
filterByAnnotation spec params . nub $
|
||||||
runChecker params (checkers spec params)
|
runChecker params (checkers spec params)
|
||||||
}
|
}
|
||||||
where
|
|
||||||
params = makeParameters spec
|
|
||||||
|
|
||||||
checkers spec params = mconcat $ map ($ params) [
|
checkers spec params = mconcat $ map ($ params) [
|
||||||
ShellCheck.Analytics.checker spec,
|
ShellCheck.Analytics.checker spec,
|
||||||
|
|
|
@ -103,7 +103,9 @@ data Parameters = Parameters {
|
||||||
-- map from token id to start and end position
|
-- map from token id to start and end position
|
||||||
tokenPositions :: Map.Map Id (Position, Position),
|
tokenPositions :: Map.Map Id (Position, Position),
|
||||||
-- Result from Control Flow Graph analysis (including data flow analysis)
|
-- 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)
|
} deriving (Show)
|
||||||
|
|
||||||
-- TODO: Cache results of common AST ops here
|
-- TODO: Cache results of common AST ops here
|
||||||
|
@ -152,7 +154,7 @@ producesComments c s = do
|
||||||
let pr = pScript s
|
let pr = pScript s
|
||||||
prRoot pr
|
prRoot pr
|
||||||
let spec = defaultSpec pr
|
let spec = defaultSpec pr
|
||||||
let params = makeParameters spec
|
let params = runIdentity $ makeParameters (mockedSystemInterface []) spec
|
||||||
return . not . null $ filterByAnnotation spec params $ runChecker params c
|
return . not . null $ filterByAnnotation spec params $ runChecker params c
|
||||||
|
|
||||||
makeComment :: Severity -> Id -> Code -> String -> TokenComment
|
makeComment :: Severity -> Id -> Code -> String -> TokenComment
|
||||||
|
@ -196,11 +198,22 @@ makeCommentWithFix severity id code str fix =
|
||||||
}
|
}
|
||||||
in force withFix
|
in force withFix
|
||||||
|
|
||||||
makeParameters spec = params
|
makeParameters :: Monad m => SystemInterface m -> AnalysisSpec -> m Parameters
|
||||||
|
makeParameters sys spec = do
|
||||||
|
extraVars <-
|
||||||
|
case shell of
|
||||||
|
Bash -> do -- TODO: EBuild type
|
||||||
|
vars <- siGetPortageVariables sys
|
||||||
|
return $ Map.findWithDefault [] "foo" vars -- TODO: Determine what to look up in map
|
||||||
|
_ -> return []
|
||||||
|
return $ makeParams extraVars
|
||||||
|
where
|
||||||
|
shell = fromMaybe (determineShell (asFallbackShell spec) root) $ asShellType spec
|
||||||
|
makeParams extraVars = params
|
||||||
where
|
where
|
||||||
params = Parameters {
|
params = Parameters {
|
||||||
rootNode = root,
|
rootNode = root,
|
||||||
shellType = fromMaybe (determineShell (asFallbackShell spec) root) $ asShellType spec,
|
shellType = shell,
|
||||||
hasSetE = containsSetE root,
|
hasSetE = containsSetE root,
|
||||||
hasLastpipe =
|
hasLastpipe =
|
||||||
case shellType params of
|
case shellType params of
|
||||||
|
@ -225,11 +238,13 @@ makeParameters spec = params
|
||||||
parentMap = getParentTree root,
|
parentMap = getParentTree root,
|
||||||
variableFlow = getVariableFlow params root,
|
variableFlow = getVariableFlow params root,
|
||||||
tokenPositions = asTokenPositions spec,
|
tokenPositions = asTokenPositions spec,
|
||||||
cfgAnalysis = CF.analyzeControlFlow cfParams root
|
cfgAnalysis = CF.analyzeControlFlow cfParams root,
|
||||||
|
additionalKnownVariables = extraVars
|
||||||
}
|
}
|
||||||
cfParams = CF.CFGParameters {
|
cfParams = CF.CFGParameters {
|
||||||
CF.cfLastpipe = hasLastpipe params,
|
CF.cfLastpipe = hasLastpipe params,
|
||||||
CF.cfPipefail = hasPipefail params
|
CF.cfPipefail = hasPipefail params,
|
||||||
|
CF.cfAdditionalInitialVariables = additionalKnownVariables params
|
||||||
}
|
}
|
||||||
root = asScript spec
|
root = asScript spec
|
||||||
|
|
||||||
|
|
|
@ -167,7 +167,9 @@ data CFGParameters = CFGParameters {
|
||||||
-- Whether the last element in a pipeline runs in the current shell
|
-- Whether the last element in a pipeline runs in the current shell
|
||||||
cfLastpipe :: Bool,
|
cfLastpipe :: Bool,
|
||||||
-- Whether all elements in a pipeline count towards the exit status
|
-- 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 {
|
data CFGResult = CFGResult {
|
||||||
|
|
|
@ -197,12 +197,13 @@ unreachableState = modified newInternalState {
|
||||||
}
|
}
|
||||||
|
|
||||||
-- The default state we assume we get from the environment
|
-- The default state we assume we get from the environment
|
||||||
createEnvironmentState :: InternalState
|
createEnvironmentState :: CFGParameters -> InternalState
|
||||||
createEnvironmentState = do
|
createEnvironmentState params = do
|
||||||
foldl' (flip ($)) newInternalState $ concat [
|
foldl' (flip ($)) newInternalState $ concat [
|
||||||
addVars Data.internalVariables unknownVariableState,
|
addVars Data.internalVariables unknownVariableState,
|
||||||
addVars Data.variablesWithoutSpaces spacelessVariableState,
|
addVars Data.variablesWithoutSpaces spacelessVariableState,
|
||||||
addVars Data.specialIntegerVariables integerVariableState
|
addVars Data.specialIntegerVariables integerVariableState,
|
||||||
|
addVars (cfAdditionalInitialVariables params) unknownVariableState
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
addVars names val = map (\name -> insertGlobal name val) names
|
addVars names val = map (\name -> insertGlobal name val) names
|
||||||
|
@ -1344,7 +1345,7 @@ analyzeControlFlow params t =
|
||||||
runST $ f cfg entry exit
|
runST $ f cfg entry exit
|
||||||
where
|
where
|
||||||
f cfg entry exit = do
|
f cfg entry exit = do
|
||||||
let env = createEnvironmentState
|
let env = createEnvironmentState params
|
||||||
ctx <- newCtx $ cfGraph cfg
|
ctx <- newCtx $ cfGraph cfg
|
||||||
-- Do a dataflow analysis starting on the root node
|
-- Do a dataflow analysis starting on the root node
|
||||||
exitState <- runRoot ctx env entry exit
|
exitState <- runRoot ctx env entry exit
|
||||||
|
|
|
@ -88,11 +88,12 @@ checkScript sys spec = do
|
||||||
asTokenPositions = tokenPositions,
|
asTokenPositions = tokenPositions,
|
||||||
asOptionalChecks = getEnableDirectives root ++ csOptionalChecks spec
|
asOptionalChecks = getEnableDirectives root ++ csOptionalChecks spec
|
||||||
} where as = newAnalysisSpec root
|
} where as = newAnalysisSpec root
|
||||||
let analysisMessages =
|
let getAnalysisMessages =
|
||||||
maybe []
|
case prRoot result of
|
||||||
(arComments . analyzeScript . analysisSpec)
|
Just root -> arComments <$> (analyzeScript sys $ analysisSpec root)
|
||||||
$ prRoot result
|
Nothing -> return []
|
||||||
let translator = tokenToPosition tokenPositions
|
let translator = tokenToPosition tokenPositions
|
||||||
|
analysisMessages <- getAnalysisMessages
|
||||||
return . nub . sortMessages . filter shouldInclude $
|
return . nub . sortMessages . filter shouldInclude $
|
||||||
(parseMessages ++ map translator analysisMessages)
|
(parseMessages ++ map translator analysisMessages)
|
||||||
|
|
||||||
|
|
|
@ -117,7 +117,8 @@ dummySystemInterface = mockedSystemInterface [
|
||||||
cfgParams :: CFGParameters
|
cfgParams :: CFGParameters
|
||||||
cfgParams = CFGParameters {
|
cfgParams = CFGParameters {
|
||||||
cfLastpipe = False,
|
cfLastpipe = False,
|
||||||
cfPipefail = False
|
cfPipefail = False,
|
||||||
|
cfAdditionalInitialVariables = []
|
||||||
}
|
}
|
||||||
|
|
||||||
-- An example script to play with
|
-- An example script to play with
|
||||||
|
|
|
@ -87,7 +87,9 @@ data SystemInterface m = SystemInterface {
|
||||||
-- find the sourced file
|
-- find the sourced file
|
||||||
siFindSource :: String -> Maybe Bool -> [String] -> String -> m FilePath,
|
siFindSource :: String -> Maybe Bool -> [String] -> String -> m FilePath,
|
||||||
-- | Get the configuration file (name, contents) for a filename
|
-- | 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
|
-- ShellCheck input and output
|
||||||
|
@ -141,7 +143,8 @@ newSystemInterface =
|
||||||
SystemInterface {
|
SystemInterface {
|
||||||
siReadFile = \_ _ -> return $ Left "Not implemented",
|
siReadFile = \_ _ -> return $ Left "Not implemented",
|
||||||
siFindSource = \_ _ _ name -> return name,
|
siFindSource = \_ _ _ name -> return name,
|
||||||
siGetConfig = \_ -> return Nothing
|
siGetConfig = \_ -> return Nothing,
|
||||||
|
siGetPortageVariables = return Map.empty
|
||||||
}
|
}
|
||||||
|
|
||||||
-- Parser input and output
|
-- Parser input and output
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue