Change definition of Replacement, add ToJSON instance for it
This commit is contained in:
parent
4a87d2a3de
commit
5ed89d2241
|
@ -249,7 +249,11 @@ replace_start id params n r =
|
||||||
posColumn = posColumn start + n
|
posColumn = posColumn start + n
|
||||||
}
|
}
|
||||||
in
|
in
|
||||||
[R start new_end r]
|
newReplacement {
|
||||||
|
repStartPos = start,
|
||||||
|
repEndPos = new_end,
|
||||||
|
repString = r
|
||||||
|
}
|
||||||
replace_end id params n r =
|
replace_end id params n r =
|
||||||
-- because of the way we count columns 1-based
|
-- because of the way we count columns 1-based
|
||||||
-- we have to offset end columns by 1
|
-- we have to offset end columns by 1
|
||||||
|
@ -262,9 +266,13 @@ replace_end id params n r =
|
||||||
posColumn = posColumn end + 1
|
posColumn = posColumn end + 1
|
||||||
}
|
}
|
||||||
in
|
in
|
||||||
[R new_start new_end r]
|
newReplacement {
|
||||||
|
repStartPos = new_start,
|
||||||
|
repEndPos = new_end,
|
||||||
|
repString = r
|
||||||
|
}
|
||||||
surround_with id params s =
|
surround_with id params s =
|
||||||
(replace_start id params 0 s) ++ (replace_end id params 0 s)
|
[replace_start id params 0 s, replace_end id params 0 s]
|
||||||
|
|
||||||
prop_checkEchoWc3 = verify checkEchoWc "n=$(echo $foo | wc -c)"
|
prop_checkEchoWc3 = verify checkEchoWc "n=$(echo $foo | wc -c)"
|
||||||
checkEchoWc _ (T_Pipeline id _ [a, b]) =
|
checkEchoWc _ (T_Pipeline id _ [a, b]) =
|
||||||
|
@ -1363,7 +1371,7 @@ prop_checkBackticks3 = verifyNot checkBackticks "echo `#inlined comment` foo"
|
||||||
checkBackticks params (T_Backticked id list) | not (null list) =
|
checkBackticks params (T_Backticked id list) | not (null list) =
|
||||||
addComment $
|
addComment $
|
||||||
makeCommentWithFix StyleC id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
makeCommentWithFix StyleC id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
||||||
((replace_start id params 1 "$(") ++ (replace_end id params 1 ")"))
|
[(replace_start id params 1 "$("), (replace_end id params 1 ")")]
|
||||||
-- style id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
-- style id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
||||||
checkBackticks _ _ = return ()
|
checkBackticks _ _ = return ()
|
||||||
|
|
||||||
|
@ -2570,7 +2578,7 @@ checkUncheckedCdPushdPopd params root =
|
||||||
&& not (isCondition $ getPath (parentMap params) t)) $
|
&& not (isCondition $ getPath (parentMap params) t)) $
|
||||||
-- warn (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
|
-- warn (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
|
||||||
warnWithFix (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
|
warnWithFix (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
|
||||||
(replace_end (getId t) params 0 " || exit")
|
[replace_end (getId t) params 0 " || exit"]
|
||||||
checkElement _ = return ()
|
checkElement _ = return ()
|
||||||
name t = fromMaybe "" $ getCommandName t
|
name t = fromMaybe "" $ getCommandName t
|
||||||
isSafeDir t = case oversimplify t of
|
isSafeDir t = case oversimplify t of
|
||||||
|
|
|
@ -39,6 +39,19 @@ format = do
|
||||||
footer = finish ref
|
footer = finish ref
|
||||||
}
|
}
|
||||||
|
|
||||||
|
instance ToJSON Replacement where
|
||||||
|
toJSON replacement =
|
||||||
|
let start = repStartPos replacement
|
||||||
|
end = repEndPos replacement
|
||||||
|
str = repString replacement in
|
||||||
|
object [
|
||||||
|
"line" .= posLine start,
|
||||||
|
"endLine" .= posLine end,
|
||||||
|
"column" .= posColumn start,
|
||||||
|
"endColumn" .= posColumn end,
|
||||||
|
"replaceWith" .= str
|
||||||
|
]
|
||||||
|
|
||||||
instance ToJSON (PositionedComment) where
|
instance ToJSON (PositionedComment) where
|
||||||
toJSON comment =
|
toJSON comment =
|
||||||
let start = pcStartPos comment
|
let start = pcStartPos comment
|
||||||
|
@ -52,7 +65,8 @@ instance ToJSON (PositionedComment) where
|
||||||
"endColumn" .= posColumn end,
|
"endColumn" .= posColumn end,
|
||||||
"level" .= severityText comment,
|
"level" .= severityText comment,
|
||||||
"code" .= cCode c,
|
"code" .= cCode c,
|
||||||
"message" .= cMessage c
|
"message" .= cMessage c,
|
||||||
|
"fix" .= pcFix comment
|
||||||
]
|
]
|
||||||
|
|
||||||
toEncoding comment =
|
toEncoding comment =
|
||||||
|
@ -68,6 +82,7 @@ instance ToJSON (PositionedComment) where
|
||||||
<> "level" .= severityText comment
|
<> "level" .= severityText comment
|
||||||
<> "code" .= cCode c
|
<> "code" .= cCode c
|
||||||
<> "message" .= cMessage c
|
<> "message" .= cMessage c
|
||||||
|
<> "replaceWith" .= pcFix comment
|
||||||
)
|
)
|
||||||
|
|
||||||
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
||||||
|
@ -77,4 +92,3 @@ collectResult ref result _ =
|
||||||
finish ref = do
|
finish ref = do
|
||||||
list <- readIORef ref
|
list <- readIORef ref
|
||||||
BL.putStrLn $ encode list
|
BL.putStrLn $ encode list
|
||||||
|
|
||||||
|
|
|
@ -142,11 +142,12 @@ fixedString comment line =
|
||||||
apply_replacement rs line 0
|
apply_replacement rs line 0
|
||||||
where
|
where
|
||||||
apply_replacement [] s _ = s
|
apply_replacement [] s _ = s
|
||||||
apply_replacement ((R startp endp r):xs) s offset =
|
apply_replacement (rep:xs) s offset =
|
||||||
let start = posColumn startp
|
let replacementString = repString rep
|
||||||
end = posColumn endp
|
start = (posColumn . repStartPos) rep
|
||||||
z = do_replace start end s r
|
end = (posColumn . repEndPos) rep
|
||||||
len_r = (fromIntegral . length) r in
|
z = do_replace start end s replacementString
|
||||||
|
len_r = (fromIntegral . length) replacementString in
|
||||||
apply_replacement xs z (offset + (end - start) + len_r)
|
apply_replacement xs z (offset + (end - start) + len_r)
|
||||||
|
|
||||||
-- start and end comes from pos, which is 1 based
|
-- start and end comes from pos, which is 1 based
|
||||||
|
|
|
@ -50,7 +50,8 @@ module ShellCheck.Interface
|
||||||
, newPositionedComment
|
, newPositionedComment
|
||||||
, newComment
|
, newComment
|
||||||
, Fix
|
, Fix
|
||||||
, Replacement(R)
|
, Replacement(repStartPos, repEndPos, repString)
|
||||||
|
, newReplacement
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import ShellCheck.AST
|
import ShellCheck.AST
|
||||||
|
@ -196,9 +197,17 @@ newComment = Comment {
|
||||||
}
|
}
|
||||||
|
|
||||||
-- only support single line for now
|
-- only support single line for now
|
||||||
data Replacement =
|
data Replacement = Replacement {
|
||||||
R Position Position String
|
repStartPos :: Position,
|
||||||
deriving (Show, Eq)
|
repEndPos :: Position,
|
||||||
|
repString :: String
|
||||||
|
} deriving (Show, Eq)
|
||||||
|
|
||||||
|
newReplacement = Replacement {
|
||||||
|
repStartPos = newPosition,
|
||||||
|
repEndPos = newPosition,
|
||||||
|
repString = ""
|
||||||
|
}
|
||||||
|
|
||||||
type Fix = [Replacement]
|
type Fix = [Replacement]
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue