From 4470fe715c359f953dd07951f1732d5a209d1c59 Mon Sep 17 00:00:00 2001 From: Russell Harmon Date: Sat, 18 Jun 2016 22:15:01 -0700 Subject: [PATCH 01/12] Support emitting a correct end column on SC2086 This does the necessary work to emit end columns on AST analyses. SC2086 is made to emit a correct end column as an illustrative example. For example: ``` $ shellcheck -s bash -f json /dev/stdin <<< 'echo $1' [{"file":"/dev/stdin","line":1,"endLine":1,"column":6,"endColumn":8,"level":"info","code":2086,"message":"Double quote to prevent globbing and word splitting."}] ``` This change deprecates the parser's getNextId and getNextIdAt, replacing it with a new withNextId function. This function has the type signature: withNextId :: Monad m => ParsecT s UserState (SCBase m) (Id -> b) -> ParsecT s UserState (SCBase m) b Specifically, it should be used to wrap read* functions and will pass in a newly generated Id which should be used to represent that node. Sub-parsers will need their own call to withNextId in order to get a unique Id. In doing this, withNextId can now track both the entry and exit position of every read* parser which uses it, enabling the tracking of end columns throughout the application. --- src/ShellCheck/Checker.hs | 12 ++++--- src/ShellCheck/Interface.hs | 1 + src/ShellCheck/Parser.hs | 63 +++++++++++++++++++++++++++++-------- 3 files changed, 59 insertions(+), 17 deletions(-) diff --git a/src/ShellCheck/Checker.hs b/src/ShellCheck/Checker.hs index 72259ad..3127c26 100644 --- a/src/ShellCheck/Checker.hs +++ b/src/ShellCheck/Checker.hs @@ -29,6 +29,7 @@ import Data.Functor import Data.List import Data.Maybe import Data.Ord +import Control.Applicative import Control.Monad.Identity import qualified Data.Map as Map import qualified System.IO @@ -37,11 +38,14 @@ import Control.Monad import Test.QuickCheck.All -tokenToPosition map (TokenComment id c) = fromMaybe fail $ do - position <- Map.lookup id map - return $ PositionedComment position position c +tokenToPosition startMap endMap (TokenComment id c) = fromMaybe fail $ do + position <- maybePosition + endPosition <- maybeEndPosition <|> maybePosition + return $ PositionedComment position endPosition c where fail = error "Internal shellcheck error: id doesn't exist. Please report!" + maybeEndPosition = Map.lookup id endMap + maybePosition = Map.lookup id startMap checkScript :: Monad m => SystemInterface m -> CheckSpec -> m CheckResult checkScript sys spec = do @@ -62,7 +66,7 @@ checkScript sys spec = do fromMaybe [] $ (arComments . analyzeScript . analysisSpec) <$> prRoot result - let translator = tokenToPosition (prTokenPositions result) + let translator = tokenToPosition (prTokenPositions result) (prTokenEndPositions result) return . nub . sortMessages . filter shouldInclude $ (parseMessages ++ map translator analysisMessages) diff --git a/src/ShellCheck/Interface.hs b/src/ShellCheck/Interface.hs index a76c7e0..001222d 100644 --- a/src/ShellCheck/Interface.hs +++ b/src/ShellCheck/Interface.hs @@ -62,6 +62,7 @@ data ParseSpec = ParseSpec { data ParseResult = ParseResult { prComments :: [PositionedComment], prTokenPositions :: Map.Map Id Position, + prTokenEndPositions :: Map.Map Id Position, prRoot :: Maybe Token } deriving (Show, Eq) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index dafbe0a..5adae09 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -136,6 +136,38 @@ almostSpace = char c return ' ' +withNextId :: Monad m => ParsecT s UserState (SCBase m) (Id -> b) -> ParsecT s UserState (SCBase m) b +withNextId p = do + start <- getPosition + id <- createId + setStartPos id start + fn <- p + let t = fn id + end <- getPosition + setEndPos id end + return t + where + createId = do + state <- getState + let id = incId (lastId state) + putState $ state { + lastId = id + } + return id + where incId (Id n) = Id $ n+1 + setStartPos id sourcepos = do + state <- getState + let newMap = Map.insert id sourcepos (positionMap state) + putState $ state { + positionMap = newMap + } + setEndPos id sourcepos = do + state <- getState + let newMap = Map.insert id sourcepos (positionEndMap state) + putState $ state { + positionEndMap = newMap + } + --------- Message/position annotation on top of user state data Note = Note Id Severity Code String deriving (Show, Eq) data ParseNote = ParseNote SourcePos SourcePos Severity Code String deriving (Show, Eq) @@ -152,6 +184,7 @@ data HereDocContext = data UserState = UserState { lastId :: Id, positionMap :: Map.Map Id SourcePos, + positionEndMap :: Map.Map Id SourcePos, parseNotes :: [ParseNote], hereDocMap :: Map.Map Id [Token], pendingHereDocs :: [HereDocContext] @@ -159,6 +192,7 @@ data UserState = UserState { initialUserState = UserState { lastId = Id $ -1, positionMap = Map.empty, + positionEndMap = Map.empty, parseNotes = [], hereDocMap = Map.empty, pendingHereDocs = [] @@ -172,6 +206,7 @@ noteToParseNote map (Note id severity code message) = getLastId = lastId <$> getState +-- Deprecated by withNextId getNextIdAt sourcepos = do state <- getState let newId = incId (lastId state) @@ -183,6 +218,7 @@ getNextIdAt sourcepos = do return newId where incId (Id n) = Id $ n+1 +-- Deprecated by withNextId getNextId :: Monad m => SCParser m Id getNextId = do pos <- getPosition @@ -1190,8 +1226,7 @@ prop_readDoubleQuoted7 = isOk readSimpleCommand "echo \"${ ls;}bar\"" prop_readDoubleQuoted8 = isWarning readDoubleQuoted "\"\x201Chello\x201D\"" prop_readDoubleQuoted9 = isWarning readDoubleQuoted "\"foo\\n\"" prop_readDoubleQuoted10 = isOk readDoubleQuoted "\"foo\\\\n\"" -readDoubleQuoted = called "double quoted string" $ do - id <- getNextId +readDoubleQuoted = called "double quoted string" $ withNextId $ do startPos <- getPosition doubleQuote x <- many doubleQuotedPart @@ -1201,7 +1236,7 @@ readDoubleQuoted = called "double quoted string" $ do try . lookAhead $ suspectCharAfterQuotes <|> oneOf "$\"" when (any hasLineFeed x && not (startsWithLineFeed x)) $ suggestForgotClosingQuote startPos endPos "double quoted string" - return $ T_DoubleQuoted id x + return $ \id -> T_DoubleQuoted id x where startsWithLineFeed (T_Literal _ ('\n':_):_) = True startsWithLineFeed _ = False @@ -1544,16 +1579,18 @@ prop_readDollarVariable3 = isWarning (readDollarVariable >> anyChar) "$10" prop_readDollarVariable4 = isWarning (readDollarVariable >> string "[@]") "$arr[@]" prop_readDollarVariable5 = isWarning (readDollarVariable >> string "[f") "$arr[f" -readDollarVariable = do - id <- getNextId +readDollarVariable :: Monad m => ParsecT String UserState (SCBase m) Token +readDollarVariable = withNextId $ do pos <- getPosition - let singleCharred p = do + let + singleCharred p = do n <- p value <- wrap [n] - return (T_DollarBraced id value) + return $ \id -> (T_DollarBraced id value) - let positional = do + let + positional = do value <- singleCharred digit return value `attempting` do lookAhead digit @@ -1564,17 +1601,15 @@ readDollarVariable = do let regular = do name <- readVariableName value <- wrap name - return (T_DollarBraced id value) `attempting` do + return (\id -> (T_DollarBraced id value)) `attempting` do lookAhead $ char '[' parseNoteAt pos ErrorC 1087 "Use braces when expanding arrays, e.g. ${array[idx]} (or ${var}[.. to quiet)." try $ char '$' >> (positional <|> special <|> regular) where - wrap s = do - x <- getNextId - y <- getNextId - return $ T_NormalWord x [T_Literal y s] + wrap s = withNextId $ withNextId $ do + return $ \x y -> T_NormalWord x [T_Literal y s] readVariableName = do f <- variableStart @@ -3002,6 +3037,7 @@ parseShell env name contents = do return ParseResult { prComments = map toPositionedComment $ nub $ parseNotes userstate ++ parseProblems state, prTokenPositions = Map.map posToPos (positionMap userstate), + prTokenEndPositions = Map.map posToPos (positionEndMap userstate), prRoot = Just $ reattachHereDocs script (hereDocMap userstate) } @@ -3013,6 +3049,7 @@ parseShell env name contents = do ++ [makeErrorFor err] ++ parseProblems state, prTokenPositions = Map.empty, + prTokenEndPositions = Map.empty, prRoot = Nothing } From 48ac654a9369b029f234c510c0347507d75ef524 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Sat, 26 May 2018 23:25:22 -0700 Subject: [PATCH 02/12] Merge end pos map into start pos map --- src/ShellCheck/Checker.hs | 8 +++---- src/ShellCheck/Interface.hs | 3 +-- src/ShellCheck/Parser.hs | 48 ++++++++++++++++--------------------- 3 files changed, 26 insertions(+), 33 deletions(-) diff --git a/src/ShellCheck/Checker.hs b/src/ShellCheck/Checker.hs index 3127c26..4b0ba1e 100644 --- a/src/ShellCheck/Checker.hs +++ b/src/ShellCheck/Checker.hs @@ -38,14 +38,14 @@ import Control.Monad import Test.QuickCheck.All -tokenToPosition startMap endMap (TokenComment id c) = fromMaybe fail $ do +tokenToPosition startMap (TokenComment id c) = fromMaybe fail $ do position <- maybePosition endPosition <- maybeEndPosition <|> maybePosition return $ PositionedComment position endPosition c where fail = error "Internal shellcheck error: id doesn't exist. Please report!" - maybeEndPosition = Map.lookup id endMap - maybePosition = Map.lookup id startMap + maybePosition = fmap fst $ Map.lookup id startMap + maybeEndPosition = join $ fmap snd $ Map.lookup id startMap checkScript :: Monad m => SystemInterface m -> CheckSpec -> m CheckResult checkScript sys spec = do @@ -66,7 +66,7 @@ checkScript sys spec = do fromMaybe [] $ (arComments . analyzeScript . analysisSpec) <$> prRoot result - let translator = tokenToPosition (prTokenPositions result) (prTokenEndPositions result) + let translator = tokenToPosition (prTokenPositions result) return . nub . sortMessages . filter shouldInclude $ (parseMessages ++ map translator analysisMessages) diff --git a/src/ShellCheck/Interface.hs b/src/ShellCheck/Interface.hs index 001222d..fb5f492 100644 --- a/src/ShellCheck/Interface.hs +++ b/src/ShellCheck/Interface.hs @@ -61,8 +61,7 @@ data ParseSpec = ParseSpec { data ParseResult = ParseResult { prComments :: [PositionedComment], - prTokenPositions :: Map.Map Id Position, - prTokenEndPositions :: Map.Map Id Position, + prTokenPositions :: Map.Map Id (Position, Maybe Position), prRoot :: Maybe Token } deriving (Show, Eq) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 5adae09..59d67dc 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -136,15 +136,14 @@ almostSpace = char c return ' ' -withNextId :: Monad m => ParsecT s UserState (SCBase m) (Id -> b) -> ParsecT s UserState (SCBase m) b +withNextId :: Monad m => SCParser m (Id -> b) -> SCParser m b withNextId p = do start <- getPosition id <- createId - setStartPos id start fn <- p let t = fn id end <- getPosition - setEndPos id end + setPos id start end return t where createId = do @@ -155,18 +154,12 @@ withNextId p = do } return id where incId (Id n) = Id $ n+1 - setStartPos id sourcepos = do + setPos id start end = do state <- getState - let newMap = Map.insert id sourcepos (positionMap state) + let newMap = Map.insert id (start, Just end) (positionMap state) putState $ state { positionMap = newMap } - setEndPos id sourcepos = do - state <- getState - let newMap = Map.insert id sourcepos (positionEndMap state) - putState $ state { - positionEndMap = newMap - } --------- Message/position annotation on top of user state data Note = Note Id Severity Code String deriving (Show, Eq) @@ -183,8 +176,7 @@ data HereDocContext = data UserState = UserState { lastId :: Id, - positionMap :: Map.Map Id SourcePos, - positionEndMap :: Map.Map Id SourcePos, + positionMap :: Map.Map Id (SourcePos, Maybe SourcePos), parseNotes :: [ParseNote], hereDocMap :: Map.Map Id [Token], pendingHereDocs :: [HereDocContext] @@ -192,7 +184,6 @@ data UserState = UserState { initialUserState = UserState { lastId = Id $ -1, positionMap = Map.empty, - positionEndMap = Map.empty, parseNotes = [], hereDocMap = Map.empty, pendingHereDocs = [] @@ -210,7 +201,7 @@ getLastId = lastId <$> getState getNextIdAt sourcepos = do state <- getState let newId = incId (lastId state) - let newMap = Map.insert newId sourcepos (positionMap state) + let newMap = Map.insert newId (sourcepos, Just sourcepos) (positionMap state) putState $ state { lastId = newId, positionMap = newMap @@ -354,7 +345,7 @@ parseProblemAt pos = parseProblemAtWithEnd pos pos parseProblemAtId :: Monad m => Id -> Severity -> Integer -> String -> SCParser m () parseProblemAtId id level code msg = do map <- getMap - let pos = Map.findWithDefault + let (pos, _) = Map.findWithDefault (error "Internal error (no position for id). Please report.") id map parseProblemAt pos level code msg @@ -1579,18 +1570,16 @@ prop_readDollarVariable3 = isWarning (readDollarVariable >> anyChar) "$10" prop_readDollarVariable4 = isWarning (readDollarVariable >> string "[@]") "$arr[@]" prop_readDollarVariable5 = isWarning (readDollarVariable >> string "[f") "$arr[f" -readDollarVariable :: Monad m => ParsecT String UserState (SCBase m) Token +readDollarVariable :: Monad m => SCParser m Token readDollarVariable = withNextId $ do pos <- getPosition - let - singleCharred p = do + let singleCharred p = do n <- p value <- wrap [n] return $ \id -> (T_DollarBraced id value) - let - positional = do + let positional = do value <- singleCharred digit return value `attempting` do lookAhead digit @@ -1679,7 +1668,7 @@ readPendingHereDocs = do swapContext ctx $ do docPos <- getPosition - tokenPos <- Map.findWithDefault (error "Missing ID") id <$> getMap + (tokenPos, _) <- Map.findWithDefault (error "Missing ID") id <$> getMap (terminated, wasWarned, lines) <- readDocLines dashed endToken let hereData = unlines lines unless terminated $ do @@ -2945,11 +2934,15 @@ debugParseScript string = result { -- Remove the noisiest parts prTokenPositions = Map.fromList [ - (Id 0, Position { + (Id 0, (Position { posFile = "removed for clarity", posLine = -1, posColumn = -1 - })] + }, Just Position { + posFile = "removed for clarity", + posLine = -1, + posColumn = -1 + }))] } where result = runIdentity $ @@ -3036,8 +3029,7 @@ parseShell env name contents = do Right (script, userstate) -> return ParseResult { prComments = map toPositionedComment $ nub $ parseNotes userstate ++ parseProblems state, - prTokenPositions = Map.map posToPos (positionMap userstate), - prTokenEndPositions = Map.map posToPos (positionEndMap userstate), + prTokenPositions = Map.map startEndPosToPos (positionMap userstate), prRoot = Just $ reattachHereDocs script (hereDocMap userstate) } @@ -3049,7 +3041,6 @@ parseShell env name contents = do ++ [makeErrorFor err] ++ parseProblems state, prTokenPositions = Map.empty, - prTokenEndPositions = Map.empty, prRoot = Nothing } @@ -3119,6 +3110,9 @@ posToPos sp = Position { posColumn = fromIntegral $ sourceColumn sp } +startEndPosToPos :: (SourcePos, Maybe SourcePos) -> (Position, Maybe Position) +startEndPosToPos (s, me) = (posToPos s, fmap posToPos me) + -- TODO: Clean up crusty old code that this is layered on top of parseScript :: Monad m => SystemInterface m -> ParseSpec -> m ParseResult From e496b413bdbd9b3bf5377bf03385fa57432db171 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Thu, 7 Jun 2018 21:30:20 -0700 Subject: [PATCH 03/12] Remove usage of withNextId --- src/ShellCheck/Parser.hs | 45 ++++++++++------------------------------ 1 file changed, 11 insertions(+), 34 deletions(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 59d67dc..c7224f4 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -136,31 +136,6 @@ almostSpace = char c return ' ' -withNextId :: Monad m => SCParser m (Id -> b) -> SCParser m b -withNextId p = do - start <- getPosition - id <- createId - fn <- p - let t = fn id - end <- getPosition - setPos id start end - return t - where - createId = do - state <- getState - let id = incId (lastId state) - putState $ state { - lastId = id - } - return id - where incId (Id n) = Id $ n+1 - setPos id start end = do - state <- getState - let newMap = Map.insert id (start, Just end) (positionMap state) - putState $ state { - positionMap = newMap - } - --------- Message/position annotation on top of user state data Note = Note Id Severity Code String deriving (Show, Eq) data ParseNote = ParseNote SourcePos SourcePos Severity Code String deriving (Show, Eq) @@ -197,7 +172,6 @@ noteToParseNote map (Note id severity code message) = getLastId = lastId <$> getState --- Deprecated by withNextId getNextIdAt sourcepos = do state <- getState let newId = incId (lastId state) @@ -209,7 +183,6 @@ getNextIdAt sourcepos = do return newId where incId (Id n) = Id $ n+1 --- Deprecated by withNextId getNextId :: Monad m => SCParser m Id getNextId = do pos <- getPosition @@ -1217,7 +1190,8 @@ prop_readDoubleQuoted7 = isOk readSimpleCommand "echo \"${ ls;}bar\"" prop_readDoubleQuoted8 = isWarning readDoubleQuoted "\"\x201Chello\x201D\"" prop_readDoubleQuoted9 = isWarning readDoubleQuoted "\"foo\\n\"" prop_readDoubleQuoted10 = isOk readDoubleQuoted "\"foo\\\\n\"" -readDoubleQuoted = called "double quoted string" $ withNextId $ do +readDoubleQuoted = called "double quoted string" $ do + id <- getNextId startPos <- getPosition doubleQuote x <- many doubleQuotedPart @@ -1227,7 +1201,7 @@ readDoubleQuoted = called "double quoted string" $ withNextId $ do try . lookAhead $ suspectCharAfterQuotes <|> oneOf "$\"" when (any hasLineFeed x && not (startsWithLineFeed x)) $ suggestForgotClosingQuote startPos endPos "double quoted string" - return $ \id -> T_DoubleQuoted id x + return $ T_DoubleQuoted id x where startsWithLineFeed (T_Literal _ ('\n':_):_) = True startsWithLineFeed _ = False @@ -1571,13 +1545,14 @@ prop_readDollarVariable4 = isWarning (readDollarVariable >> string "[@]") "$arr[ prop_readDollarVariable5 = isWarning (readDollarVariable >> string "[f") "$arr[f" readDollarVariable :: Monad m => SCParser m Token -readDollarVariable = withNextId $ do +readDollarVariable = do + id <- getNextId pos <- getPosition let singleCharred p = do n <- p value <- wrap [n] - return $ \id -> (T_DollarBraced id value) + return $ (T_DollarBraced id value) let positional = do value <- singleCharred digit @@ -1590,15 +1565,17 @@ readDollarVariable = withNextId $ do let regular = do name <- readVariableName value <- wrap name - return (\id -> (T_DollarBraced id value)) `attempting` do + return (T_DollarBraced id value) `attempting` do lookAhead $ char '[' parseNoteAt pos ErrorC 1087 "Use braces when expanding arrays, e.g. ${array[idx]} (or ${var}[.. to quiet)." try $ char '$' >> (positional <|> special <|> regular) where - wrap s = withNextId $ withNextId $ do - return $ \x y -> T_NormalWord x [T_Literal y s] + wrap s = do + x <- getNextId + y <- getNextId + return $ T_NormalWord x [T_Literal y s] readVariableName = do f <- variableStart From 0c459ae2cb42be1d5bd8b8f883e04a75dbd5e9ce Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Thu, 7 Jun 2018 21:32:49 -0700 Subject: [PATCH 04/12] Add function to set end pos of start id --- src/ShellCheck/Parser.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index c7224f4..a11af7a 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -188,6 +188,16 @@ getNextId = do pos <- getPosition getNextIdAt pos +endPosOfStartId s = do + endPos <- getPosition + state <- getState + let setEndPos (start, _) = Just (start, Just endPos) + let newMap = Map.update setEndPos s (positionMap state) + putState $ state { + lastId = s, + positionMap = newMap + } + addToHereDocMap id list = do state <- getState let map = hereDocMap state From 3848788c2d277b1fc24b39fab0551f038d234976 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Thu, 7 Jun 2018 21:52:29 -0700 Subject: [PATCH 05/12] Add end pos to readDollarVariable --- src/ShellCheck/Parser.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index a11af7a..2d5290b 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -1562,6 +1562,7 @@ readDollarVariable = do let singleCharred p = do n <- p value <- wrap [n] + endPosOfStartId id return $ (T_DollarBraced id value) let positional = do @@ -1575,6 +1576,7 @@ readDollarVariable = do let regular = do name <- readVariableName value <- wrap name + endPosOfStartId id return (T_DollarBraced id value) `attempting` do lookAhead $ char '[' parseNoteAt pos ErrorC 1087 "Use braces when expanding arrays, e.g. ${array[idx]} (or ${var}[.. to quiet)." From 29e8c0a16ecbef90171936998d064880ac66e194 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Thu, 7 Jun 2018 22:25:09 -0700 Subject: [PATCH 06/12] Add end pos to readDollarBraced --- src/ShellCheck/Parser.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 2d5290b..0488b00 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -1536,6 +1536,7 @@ readDollarBraced = called "parameter expansion" $ do try (string "${") word <- readDollarBracedWord char '}' + endPosOfStartId id return $ T_DollarBraced id word prop_readDollarExpansion1= isOk readDollarExpansion "$(echo foo; ls\n)" From 8ff35fb4af895353ed035be8304beca067a9b2af Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Thu, 7 Jun 2018 23:09:59 -0700 Subject: [PATCH 07/12] Add end pos to readSingleQuoted --- src/ShellCheck/Parser.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 0488b00..a608403 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -1097,6 +1097,7 @@ readSingleQuoted = called "single quoted string" $ do when ('\n' `elem` string && not ("\n" `isPrefixOf` string)) $ suggestForgotClosingQuote startPos endPos "single quoted string" + endPosOfStartId id return (T_SingleQuoted id string) readSingleQuotedLiteral = do From 1699c9e9ba597dacd405c9bef5768fad35f12344 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Tue, 12 Jun 2018 21:56:53 -0700 Subject: [PATCH 08/12] Add api to begin and end a span of source code --- src/ShellCheck/Parser.hs | 21 +++++++++++++++++++++ 1 file changed, 21 insertions(+) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index a608403..3cb2411 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -188,6 +188,27 @@ getNextId = do pos <- getPosition getNextIdAt pos +data IncompleteInterval = IncompleteInterval SourcePos + +startSpan = IncompleteInterval <$> getPosition + +endSpan (IncompleteInterval start) = do + id <- getNextIdAt start + endPos <- getPosition + state <- getState + let setEndPos (start, _) = Just (start, Just endPos) + let newMap = Map.update setEndPos id (positionMap state) + putState $ state { + lastId = id, + positionMap = newMap + } + return id + +zeroWidthSpan = do + start <- startSpan + id <- endSpan start + return id + endPosOfStartId s = do endPos <- getPosition state <- getState From e717802de1ddf66bbe1f91feddd26d132f2fc726 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Tue, 12 Jun 2018 22:11:11 -0700 Subject: [PATCH 09/12] Change usage of endPosOfStartId to startSpan and endSpan --- src/ShellCheck/Parser.hs | 24 +++++++----------------- 1 file changed, 7 insertions(+), 17 deletions(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 3cb2411..8daa957 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -209,16 +209,6 @@ zeroWidthSpan = do id <- endSpan start return id -endPosOfStartId s = do - endPos <- getPosition - state <- getState - let setEndPos (start, _) = Just (start, Just endPos) - let newMap = Map.update setEndPos s (positionMap state) - putState $ state { - lastId = s, - positionMap = newMap - } - addToHereDocMap id list = do state <- getState let map = hereDocMap state @@ -1100,7 +1090,7 @@ prop_readSingleQuoted6 = isOk readSimpleCommand "foo='bar cow 'arg" prop_readSingleQuoted7 = isOk readSingleQuoted "'foo\x201C\&bar'" prop_readSingleQuoted8 = isWarning readSingleQuoted "'foo\x2018\&bar'" readSingleQuoted = called "single quoted string" $ do - id <- getNextId + start <- startSpan startPos <- getPosition singleQuote s <- many readSingleQuotedPart @@ -1118,7 +1108,7 @@ readSingleQuoted = called "single quoted string" $ do when ('\n' `elem` string && not ("\n" `isPrefixOf` string)) $ suggestForgotClosingQuote startPos endPos "single quoted string" - endPosOfStartId id + id <- endSpan start return (T_SingleQuoted id string) readSingleQuotedLiteral = do @@ -1554,11 +1544,11 @@ prop_readDollarBraced2 = isOk readDollarBraced "${foo/'{cow}'}" prop_readDollarBraced3 = isOk readDollarBraced "${foo%%$(echo cow\\})}" prop_readDollarBraced4 = isOk readDollarBraced "${foo#\\}}" readDollarBraced = called "parameter expansion" $ do - id <- getNextId + start <- startSpan try (string "${") word <- readDollarBracedWord char '}' - endPosOfStartId id + id <- endSpan start return $ T_DollarBraced id word prop_readDollarExpansion1= isOk readDollarExpansion "$(echo foo; ls\n)" @@ -1579,13 +1569,13 @@ prop_readDollarVariable5 = isWarning (readDollarVariable >> string "[f") "$arr[f readDollarVariable :: Monad m => SCParser m Token readDollarVariable = do - id <- getNextId + start <- startSpan pos <- getPosition let singleCharred p = do n <- p value <- wrap [n] - endPosOfStartId id + id <- endSpan start return $ (T_DollarBraced id value) let positional = do @@ -1599,7 +1589,7 @@ readDollarVariable = do let regular = do name <- readVariableName value <- wrap name - endPosOfStartId id + id <- endSpan start return (T_DollarBraced id value) `attempting` do lookAhead $ char '[' parseNoteAt pos ErrorC 1087 "Use braces when expanding arrays, e.g. ${array[idx]} (or ${var}[.. to quiet)." From b9a9eb2529e40a29224fc3114ed20d5e2c3c6d0d Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Tue, 12 Jun 2018 22:16:00 -0700 Subject: [PATCH 10/12] Change getNextId to create a zero width span at new id --- src/ShellCheck/Parser.hs | 10 +++------- 1 file changed, 3 insertions(+), 7 deletions(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 8daa957..41724a5 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -185,8 +185,9 @@ getNextIdAt sourcepos = do getNextId :: Monad m => SCParser m Id getNextId = do - pos <- getPosition - getNextIdAt pos + start <- startSpan + id <- endSpan start + return id data IncompleteInterval = IncompleteInterval SourcePos @@ -204,11 +205,6 @@ endSpan (IncompleteInterval start) = do } return id -zeroWidthSpan = do - start <- startSpan - id <- endSpan start - return id - addToHereDocMap id list = do state <- getState let map = hereDocMap state From 4111ce8fde65255fe7d3f82d87ca24bbf47c0e13 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Tue, 12 Jun 2018 22:39:06 -0700 Subject: [PATCH 11/12] Make end pos non-optional --- src/ShellCheck/Checker.hs | 7 ++----- src/ShellCheck/Interface.hs | 2 +- src/ShellCheck/Parser.hs | 16 ++++++++-------- 3 files changed, 11 insertions(+), 14 deletions(-) diff --git a/src/ShellCheck/Checker.hs b/src/ShellCheck/Checker.hs index 4b0ba1e..bd722ce 100644 --- a/src/ShellCheck/Checker.hs +++ b/src/ShellCheck/Checker.hs @@ -39,13 +39,10 @@ import Control.Monad import Test.QuickCheck.All tokenToPosition startMap (TokenComment id c) = fromMaybe fail $ do - position <- maybePosition - endPosition <- maybeEndPosition <|> maybePosition - return $ PositionedComment position endPosition c + span <- Map.lookup id startMap + return $ PositionedComment (fst span) (snd span) c where fail = error "Internal shellcheck error: id doesn't exist. Please report!" - maybePosition = fmap fst $ Map.lookup id startMap - maybeEndPosition = join $ fmap snd $ Map.lookup id startMap checkScript :: Monad m => SystemInterface m -> CheckSpec -> m CheckResult checkScript sys spec = do diff --git a/src/ShellCheck/Interface.hs b/src/ShellCheck/Interface.hs index fb5f492..9936653 100644 --- a/src/ShellCheck/Interface.hs +++ b/src/ShellCheck/Interface.hs @@ -61,7 +61,7 @@ data ParseSpec = ParseSpec { data ParseResult = ParseResult { prComments :: [PositionedComment], - prTokenPositions :: Map.Map Id (Position, Maybe Position), + prTokenPositions :: Map.Map Id (Position, Position), prRoot :: Maybe Token } deriving (Show, Eq) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 41724a5..2d8168f 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -151,7 +151,7 @@ data HereDocContext = data UserState = UserState { lastId :: Id, - positionMap :: Map.Map Id (SourcePos, Maybe SourcePos), + positionMap :: Map.Map Id (SourcePos, SourcePos), parseNotes :: [ParseNote], hereDocMap :: Map.Map Id [Token], pendingHereDocs :: [HereDocContext] @@ -175,7 +175,7 @@ getLastId = lastId <$> getState getNextIdAt sourcepos = do state <- getState let newId = incId (lastId state) - let newMap = Map.insert newId (sourcepos, Just sourcepos) (positionMap state) + let newMap = Map.insert newId (sourcepos, sourcepos) (positionMap state) putState $ state { lastId = newId, positionMap = newMap @@ -197,7 +197,7 @@ endSpan (IncompleteInterval start) = do id <- getNextIdAt start endPos <- getPosition state <- getState - let setEndPos (start, _) = Just (start, Just endPos) + let setEndPos (start, _) = Just (start, endPos) let newMap = Map.update setEndPos id (positionMap state) putState $ state { lastId = id, @@ -335,9 +335,9 @@ parseProblemAt pos = parseProblemAtWithEnd pos pos parseProblemAtId :: Monad m => Id -> Severity -> Integer -> String -> SCParser m () parseProblemAtId id level code msg = do map <- getMap - let (pos, _) = Map.findWithDefault + let (start, end) = Map.findWithDefault (error "Internal error (no position for id). Please report.") id map - parseProblemAt pos level code msg + parseProblemAtWithEnd start end level code msg -- Store non-parse problems inside @@ -2936,7 +2936,7 @@ debugParseScript string = posFile = "removed for clarity", posLine = -1, posColumn = -1 - }, Just Position { + }, Position { posFile = "removed for clarity", posLine = -1, posColumn = -1 @@ -3108,8 +3108,8 @@ posToPos sp = Position { posColumn = fromIntegral $ sourceColumn sp } -startEndPosToPos :: (SourcePos, Maybe SourcePos) -> (Position, Maybe Position) -startEndPosToPos (s, me) = (posToPos s, fmap posToPos me) +startEndPosToPos :: (SourcePos, SourcePos) -> (Position, Position) +startEndPosToPos (s, e) = (posToPos s, posToPos e) -- TODO: Clean up crusty old code that this is layered on top of parseScript :: Monad m => From b63483d44cc58efc9685dbd9059d17e12dbd0411 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Tue, 12 Jun 2018 22:50:02 -0700 Subject: [PATCH 12/12] Remove unused import --- src/ShellCheck/Checker.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/ShellCheck/Checker.hs b/src/ShellCheck/Checker.hs index bd722ce..f70a776 100644 --- a/src/ShellCheck/Checker.hs +++ b/src/ShellCheck/Checker.hs @@ -29,7 +29,6 @@ import Data.Functor import Data.List import Data.Maybe import Data.Ord -import Control.Applicative import Control.Monad.Identity import qualified Data.Map as Map import qualified System.IO