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
|
||||
}
|
||||
in
|
||||
[R start new_end r]
|
||||
newReplacement {
|
||||
repStartPos = start,
|
||||
repEndPos = new_end,
|
||||
repString = r
|
||||
}
|
||||
replace_end id params n r =
|
||||
-- because of the way we count columns 1-based
|
||||
-- we have to offset end columns by 1
|
||||
|
@ -262,9 +266,13 @@ replace_end id params n r =
|
|||
posColumn = posColumn end + 1
|
||||
}
|
||||
in
|
||||
[R new_start new_end r]
|
||||
newReplacement {
|
||||
repStartPos = new_start,
|
||||
repEndPos = new_end,
|
||||
repString = r
|
||||
}
|
||||
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)"
|
||||
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) =
|
||||
addComment $
|
||||
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 `...`."
|
||||
checkBackticks _ _ = return ()
|
||||
|
||||
|
@ -2570,7 +2578,7 @@ checkUncheckedCdPushdPopd params root =
|
|||
&& not (isCondition $ getPath (parentMap params) t)) $
|
||||
-- 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."
|
||||
(replace_end (getId t) params 0 " || exit")
|
||||
[replace_end (getId t) params 0 " || exit"]
|
||||
checkElement _ = return ()
|
||||
name t = fromMaybe "" $ getCommandName t
|
||||
isSafeDir t = case oversimplify t of
|
||||
|
|
|
@ -39,6 +39,19 @@ format = do
|
|||
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
|
||||
toJSON comment =
|
||||
let start = pcStartPos comment
|
||||
|
@ -52,7 +65,8 @@ instance ToJSON (PositionedComment) where
|
|||
"endColumn" .= posColumn end,
|
||||
"level" .= severityText comment,
|
||||
"code" .= cCode c,
|
||||
"message" .= cMessage c
|
||||
"message" .= cMessage c,
|
||||
"fix" .= pcFix comment
|
||||
]
|
||||
|
||||
toEncoding comment =
|
||||
|
@ -68,6 +82,7 @@ instance ToJSON (PositionedComment) where
|
|||
<> "level" .= severityText comment
|
||||
<> "code" .= cCode c
|
||||
<> "message" .= cMessage c
|
||||
<> "replaceWith" .= pcFix comment
|
||||
)
|
||||
|
||||
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
||||
|
@ -77,4 +92,3 @@ collectResult ref result _ =
|
|||
finish ref = do
|
||||
list <- readIORef ref
|
||||
BL.putStrLn $ encode list
|
||||
|
||||
|
|
|
@ -142,11 +142,12 @@ fixedString comment line =
|
|||
apply_replacement rs line 0
|
||||
where
|
||||
apply_replacement [] s _ = s
|
||||
apply_replacement ((R startp endp r):xs) s offset =
|
||||
let start = posColumn startp
|
||||
end = posColumn endp
|
||||
z = do_replace start end s r
|
||||
len_r = (fromIntegral . length) r in
|
||||
apply_replacement (rep:xs) s offset =
|
||||
let replacementString = repString rep
|
||||
start = (posColumn . repStartPos) rep
|
||||
end = (posColumn . repEndPos) rep
|
||||
z = do_replace start end s replacementString
|
||||
len_r = (fromIntegral . length) replacementString in
|
||||
apply_replacement xs z (offset + (end - start) + len_r)
|
||||
|
||||
-- start and end comes from pos, which is 1 based
|
||||
|
|
|
@ -50,7 +50,8 @@ module ShellCheck.Interface
|
|||
, newPositionedComment
|
||||
, newComment
|
||||
, Fix
|
||||
, Replacement(R)
|
||||
, Replacement(repStartPos, repEndPos, repString)
|
||||
, newReplacement
|
||||
) where
|
||||
|
||||
import ShellCheck.AST
|
||||
|
@ -196,9 +197,17 @@ newComment = Comment {
|
|||
}
|
||||
|
||||
-- only support single line for now
|
||||
data Replacement =
|
||||
R Position Position String
|
||||
deriving (Show, Eq)
|
||||
data Replacement = Replacement {
|
||||
repStartPos :: Position,
|
||||
repEndPos :: Position,
|
||||
repString :: String
|
||||
} deriving (Show, Eq)
|
||||
|
||||
newReplacement = Replacement {
|
||||
repStartPos = newPosition,
|
||||
repEndPos = newPosition,
|
||||
repString = ""
|
||||
}
|
||||
|
||||
type Fix = [Replacement]
|
||||
|
||||
|
|
Loading…
Reference in New Issue