Merge branch 'opqaque-interface' of https://github.com/ngzhian/shellcheck into ngzhian-opqaque-interface

This commit is contained in:
Vidar Holen 2018-08-18 20:31:54 -07:00
commit 932e2b3538
8 changed files with 186 additions and 52 deletions

View File

@ -74,7 +74,7 @@ data Options = Options {
defaultOptions = Options { defaultOptions = Options {
checkSpec = emptyCheckSpec, checkSpec = emptyCheckSpec,
externalSources = False, externalSources = False,
formatterOptions = FormatterOptions { formatterOptions = newFormatterOptions {
foColorOption = ColorAuto foColorOption = ColorAuto
}, },
minSeverity = StyleC minSeverity = StyleC

View File

@ -30,7 +30,7 @@ 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 :: AnalysisSpec -> AnalysisResult
analyzeScript spec = AnalysisResult { analyzeScript spec = newAnalysisResult {
arComments = arComments =
filterByAnnotation spec params . nub $ filterByAnnotation spec params . nub $
runAnalytics spec runAnalytics spec

View File

@ -109,12 +109,11 @@ data DataSource =
data VariableState = Dead Token String | Alive deriving (Show) data VariableState = Dead Token String | Alive deriving (Show)
defaultSpec root = AnalysisSpec { defaultSpec root = spec {
asScript = root,
asShellType = Nothing, asShellType = Nothing,
asCheckSourced = False, asCheckSourced = False,
asExecutionMode = Executed asExecutionMode = Executed
} } where spec = newAnalysisSpec root
pScript s = pScript s =
let let
@ -134,7 +133,14 @@ producesComments c s = do
makeComment :: Severity -> Id -> Code -> String -> TokenComment makeComment :: Severity -> Id -> Code -> String -> TokenComment
makeComment severity id code note = makeComment severity id code note =
TokenComment id $ Comment severity code note newTokenComment {
tcId = id,
tcComment = newComment {
cSeverity = severity,
cCode = code,
cMessage = note
}
}
addComment note = tell [note] addComment note = tell [note]
@ -811,10 +817,9 @@ filterByAnnotation asSpec params =
filter (not . shouldIgnore) filter (not . shouldIgnore)
where where
token = asScript asSpec token = asScript asSpec
idFor (TokenComment id _) = id
shouldIgnore note = shouldIgnore note =
any (shouldIgnoreFor (getCode note)) $ any (shouldIgnoreFor (getCode note)) $
getPath parents (T_Bang $ idFor note) getPath parents (T_Bang $ tcId note)
shouldIgnoreFor num (T_Annotation _ anns _) = shouldIgnoreFor num (T_Annotation _ anns _) =
any hasNum anns any hasNum anns
where where
@ -823,7 +828,7 @@ filterByAnnotation asSpec params =
shouldIgnoreFor _ T_Include {} = not $ asCheckSourced asSpec shouldIgnoreFor _ T_Include {} = not $ asCheckSourced asSpec
shouldIgnoreFor _ _ = False shouldIgnoreFor _ _ = False
parents = parentMap params parents = parentMap params
getCode (TokenComment _ (Comment _ c _)) = c getCode = cCode . tcComment
-- Is this a ${#anything}, to get string length or array count? -- Is this a ${#anything}, to get string length or array count?
isCountingReference (T_DollarBraced id token) = isCountingReference (T_DollarBraced id token) =

View File

@ -37,16 +37,20 @@ import Control.Monad
import Test.QuickCheck.All import Test.QuickCheck.All
tokenToPosition startMap (TokenComment id c) = fromMaybe fail $ do tokenToPosition startMap t = fromMaybe fail $ do
span <- Map.lookup id startMap span <- Map.lookup (tcId t) startMap
return $ PositionedComment (fst span) (snd span) c return $ newPositionedComment {
pcStartPos = fst span,
pcEndPos = snd span,
pcComment = tcComment t
}
where where
fail = error "Internal shellcheck error: id doesn't exist. Please report!" fail = error "Internal shellcheck error: id doesn't exist. Please report!"
checkScript :: Monad m => SystemInterface m -> CheckSpec -> m CheckResult checkScript :: Monad m => SystemInterface m -> CheckSpec -> m CheckResult
checkScript sys spec = do checkScript sys spec = do
results <- checkScript (csScript spec) results <- checkScript (csScript spec)
return CheckResult { return emptyCheckResult {
crFilename = csFilename spec, crFilename = csFilename spec,
crComments = results crComments = results
} }
@ -67,28 +71,38 @@ checkScript sys spec = do
return . nub . sortMessages . filter shouldInclude $ return . nub . sortMessages . filter shouldInclude $
(parseMessages ++ map translator analysisMessages) (parseMessages ++ map translator analysisMessages)
shouldInclude (PositionedComment _ _ (Comment severity code _)) = shouldInclude pc =
severity <= csMinSeverity spec && let code = cCode (pcComment pc)
code `notElem` csExcludedWarnings spec severity = cSeverity (pcComment pc)
in
code `notElem` csExcludedWarnings spec &&
severity <= csMinSeverity spec
sortMessages = sortBy (comparing order) sortMessages = sortBy (comparing order)
order (PositionedComment pos _ (Comment severity code message)) = order pc =
(posFile pos, posLine pos, posColumn pos, severity, code, message) let pos = pcStartPos pc
getPosition (PositionedComment pos _ _) = pos comment = pcComment pc in
(posFile pos,
posLine pos,
posColumn pos,
cSeverity comment,
cCode comment,
cMessage comment)
getPosition = pcStartPos
analysisSpec root = analysisSpec root =
AnalysisSpec { as {
asScript = root, asScript = root,
asShellType = csShellTypeOverride spec, asShellType = csShellTypeOverride spec,
asCheckSourced = csCheckSourced spec, asCheckSourced = csCheckSourced spec,
asExecutionMode = Executed asExecutionMode = Executed
} } where as = newAnalysisSpec root
getErrors sys spec = getErrors sys spec =
sort . map getCode . crComments $ sort . map getCode . crComments $
runIdentity (checkScript sys spec) runIdentity (checkScript sys spec)
where where
getCode (PositionedComment _ _ (Comment _ code _)) = code getCode = cCode . pcComment
check = checkWithIncludes [] check = checkWithIncludes []

View File

@ -30,17 +30,17 @@ data Formatter = Formatter {
footer :: IO () footer :: IO ()
} }
sourceFile (PositionedComment pos _ _) = posFile pos sourceFile = posFile . pcStartPos
lineNo (PositionedComment pos _ _) = posLine pos lineNo = posLine . pcStartPos
endLineNo (PositionedComment _ end _) = posLine end endLineNo = posLine . pcEndPos
colNo (PositionedComment pos _ _) = posColumn pos colNo = posColumn . pcStartPos
endColNo (PositionedComment _ end _) = posColumn end endColNo = posColumn . pcEndPos
codeNo (PositionedComment _ _ (Comment _ code _)) = code codeNo = cCode . pcComment
messageText (PositionedComment _ _ (Comment _ _ t)) = t messageText = cMessage . pcComment
severityText :: PositionedComment -> String severityText :: PositionedComment -> String
severityText (PositionedComment _ _ (Comment c _ _)) = severityText pc =
case c of case cSeverity (pcComment pc) of
ErrorC -> "error" ErrorC -> "error"
WarningC -> "warning" WarningC -> "warning"
InfoC -> "info" InfoC -> "info"
@ -51,11 +51,14 @@ makeNonVirtual comments contents =
map fix comments map fix comments
where where
ls = lines contents ls = lines contents
fix c@(PositionedComment start end comment) = PositionedComment start { fix c = c {
posColumn = realignColumn lineNo colNo c pcStartPos = (pcStartPos c) {
} end { posColumn = realignColumn lineNo colNo c
posColumn = realignColumn endLineNo endColNo c }
} comment , pcEndPos = (pcEndPos c) {
posColumn = realignColumn endLineNo endColNo c
}
}
realignColumn lineNo colNo c = realignColumn lineNo colNo c =
if lineNo c > 0 && lineNo c <= fromIntegral (length ls) if lineNo c > 0 && lineNo c <= fromIntegral (length ls)
then real (ls !! fromIntegral (lineNo c - 1)) 0 0 (colNo c) then real (ls !! fromIntegral (lineNo c - 1)) 0 0 (colNo c)

View File

@ -40,7 +40,10 @@ format = do
} }
instance ToJSON (PositionedComment) where instance ToJSON (PositionedComment) where
toJSON comment@(PositionedComment start end (Comment level code string)) = toJSON comment =
let start = pcStartPos comment
end = pcEndPos comment
c = pcComment comment in
object [ object [
"file" .= posFile start, "file" .= posFile start,
"line" .= posLine start, "line" .= posLine start,
@ -48,11 +51,14 @@ instance ToJSON (PositionedComment) where
"column" .= posColumn start, "column" .= posColumn start,
"endColumn" .= posColumn end, "endColumn" .= posColumn end,
"level" .= severityText comment, "level" .= severityText comment,
"code" .= code, "code" .= cCode c,
"message" .= string "message" .= cMessage c
] ]
toEncoding comment@(PositionedComment start end (Comment level code string)) = toEncoding comment =
let start = pcStartPos comment
end = pcEndPos comment
c = pcComment comment in
pairs ( pairs (
"file" .= posFile start "file" .= posFile start
<> "line" .= posLine start <> "line" .= posLine start
@ -60,8 +66,8 @@ instance ToJSON (PositionedComment) where
<> "column" .= posColumn start <> "column" .= posColumn start
<> "endColumn" .= posColumn end <> "endColumn" .= posColumn end
<> "level" .= severityText comment <> "level" .= severityText comment
<> "code" .= code <> "code" .= cCode c
<> "message" .= string <> "message" .= cMessage c
) )
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg

View File

@ -17,7 +17,39 @@
You should have received a copy of the GNU General Public License You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>. along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
module ShellCheck.Interface where module ShellCheck.Interface
(
SystemInterface(..)
, CheckSpec(csFilename, csScript, csCheckSourced, csExcludedWarnings, csShellTypeOverride, csMinSeverity)
, CheckResult(crFilename, crComments)
, ParseSpec(psFilename, psScript, psCheckSourced, psShellTypeOverride)
, ParseResult(prComments, prTokenPositions, prRoot)
, AnalysisSpec(asScript, asShellType, asExecutionMode, asCheckSourced)
, AnalysisResult(arComments)
, FormatterOptions(foColorOption)
, Shell(Ksh, Sh, Bash, Dash)
, ExecutionMode(Executed, Sourced)
, ErrorMessage
, Code
, Severity(ErrorC, WarningC, InfoC, StyleC)
, Position(posFile, posLine, posColumn)
, Comment(cSeverity, cCode, cMessage)
, PositionedComment(pcStartPos , pcEndPos , pcComment)
, ColorOption(ColorAuto, ColorAlways, ColorNever)
, TokenComment(tcId, tcComment)
, emptyCheckResult
, newParseResult
, newAnalysisSpec
, newAnalysisResult
, newFormatterOptions
, newPosition
, newTokenComment
, mockedSystemInterface
, newParseSpec
, emptyCheckSpec
, newPositionedComment
, newComment
) where
import ShellCheck.AST import ShellCheck.AST
import Control.Monad.Identity import Control.Monad.Identity
@ -44,6 +76,12 @@ data CheckResult = CheckResult {
crComments :: [PositionedComment] crComments :: [PositionedComment]
} deriving (Show, Eq) } deriving (Show, Eq)
emptyCheckResult :: CheckResult
emptyCheckResult = CheckResult {
crFilename = "",
crComments = []
}
emptyCheckSpec :: CheckSpec emptyCheckSpec :: CheckSpec
emptyCheckSpec = CheckSpec { emptyCheckSpec = CheckSpec {
csFilename = "", csFilename = "",
@ -76,6 +114,13 @@ data ParseResult = ParseResult {
prRoot :: Maybe Token prRoot :: Maybe Token
} deriving (Show, Eq) } deriving (Show, Eq)
newParseResult :: ParseResult
newParseResult = ParseResult {
prComments = [],
prTokenPositions = Map.empty,
prRoot = Nothing
}
-- Analyzer input and output -- Analyzer input and output
data AnalysisSpec = AnalysisSpec { data AnalysisSpec = AnalysisSpec {
asScript :: Token, asScript :: Token,
@ -84,16 +129,30 @@ data AnalysisSpec = AnalysisSpec {
asCheckSourced :: Bool asCheckSourced :: Bool
} }
newAnalysisSpec token = AnalysisSpec {
asScript = token,
asShellType = Nothing,
asExecutionMode = Executed,
asCheckSourced = False
}
newtype AnalysisResult = AnalysisResult { newtype AnalysisResult = AnalysisResult {
arComments :: [TokenComment] arComments :: [TokenComment]
} }
newAnalysisResult = AnalysisResult {
arComments = []
}
-- Formatter options -- Formatter options
newtype FormatterOptions = FormatterOptions { newtype FormatterOptions = FormatterOptions {
foColorOption :: ColorOption foColorOption :: ColorOption
} }
newFormatterOptions = FormatterOptions {
foColorOption = ColorAuto
}
-- Supporting data types -- Supporting data types
data Shell = Ksh | Sh | Bash | Dash deriving (Show, Eq) data Shell = Ksh | Sh | Bash | Dash deriving (Show, Eq)
@ -109,9 +168,48 @@ data Position = Position {
posColumn :: Integer -- 1 based source column, where tabs are 8 posColumn :: Integer -- 1 based source column, where tabs are 8
} deriving (Show, Eq) } deriving (Show, Eq)
data Comment = Comment Severity Code String deriving (Show, Eq) newPosition :: Position
data PositionedComment = PositionedComment Position Position Comment deriving (Show, Eq) newPosition = Position {
data TokenComment = TokenComment Id Comment deriving (Show, Eq) posFile = "",
posLine = 1,
posColumn = 1
}
data Comment = Comment {
cSeverity :: Severity,
cCode :: Code,
cMessage :: String
} deriving (Show, Eq)
newComment :: Comment
newComment = Comment {
cSeverity = StyleC,
cCode = 0,
cMessage = ""
}
data PositionedComment = PositionedComment {
pcStartPos :: Position,
pcEndPos :: Position,
pcComment :: Comment
} deriving (Show, Eq)
newPositionedComment :: PositionedComment
newPositionedComment = PositionedComment {
pcStartPos = newPosition,
pcEndPos = newPosition,
pcComment = newComment
}
data TokenComment = TokenComment {
tcId :: Id,
tcComment :: Comment
} deriving (Show, Eq)
newTokenComment = TokenComment {
tcId = Id 0,
tcComment = newComment
}
data ColorOption = data ColorOption =
ColorAuto ColorAuto

View File

@ -3051,11 +3051,11 @@ debugParseScript string =
result { result {
-- Remove the noisiest parts -- Remove the noisiest parts
prTokenPositions = Map.fromList [ prTokenPositions = Map.fromList [
(Id 0, (Position { (Id 0, (newPosition {
posFile = "removed for clarity", posFile = "removed for clarity",
posLine = -1, posLine = -1,
posColumn = -1 posColumn = -1
}, Position { }, newPosition {
posFile = "removed for clarity", posFile = "removed for clarity",
posLine = -1, posLine = -1,
posColumn = -1 posColumn = -1
@ -3144,14 +3144,14 @@ parseShell env name contents = do
(result, state) <- runParser env (parseWithNotes readScript) name contents (result, state) <- runParser env (parseWithNotes readScript) name contents
case result of case result of
Right (script, userstate) -> Right (script, userstate) ->
return ParseResult { return newParseResult {
prComments = map toPositionedComment $ nub $ parseNotes userstate ++ parseProblems state, prComments = map toPositionedComment $ nub $ parseNotes userstate ++ parseProblems state,
prTokenPositions = Map.map startEndPosToPos (positionMap userstate), prTokenPositions = Map.map startEndPosToPos (positionMap userstate),
prRoot = Just $ prRoot = Just $
reattachHereDocs script (hereDocMap userstate) reattachHereDocs script (hereDocMap userstate)
} }
Left err -> Left err ->
return ParseResult { return newParseResult {
prComments = prComments =
map toPositionedComment $ map toPositionedComment $
notesForContext (contextStack state) notesForContext (contextStack state)
@ -3218,10 +3218,18 @@ reattachHereDocs root map =
toPositionedComment :: ParseNote -> PositionedComment toPositionedComment :: ParseNote -> PositionedComment
toPositionedComment (ParseNote start end severity code message) = toPositionedComment (ParseNote start end severity code message) =
PositionedComment (posToPos start) (posToPos end) $ Comment severity code message newPositionedComment {
pcStartPos = (posToPos start)
, pcEndPos = (posToPos end)
, pcComment = newComment {
cSeverity = severity
, cCode = code
, cMessage = message
}
}
posToPos :: SourcePos -> Position posToPos :: SourcePos -> Position
posToPos sp = Position { posToPos sp = newPosition {
posFile = sourceName sp, posFile = sourceName sp,
posLine = fromIntegral $ sourceLine sp, posLine = fromIntegral $ sourceLine sp,
posColumn = fromIntegral $ sourceColumn sp posColumn = fromIntegral $ sourceColumn sp