Add a Diff output format

This commit is contained in:
Vidar Holen 2019-06-23 19:05:12 -07:00
parent b8b4a11348
commit b1aeee564c
8 changed files with 265 additions and 8 deletions

View file

@ -1,6 +1,7 @@
## Since previous release ## Since previous release
### Added ### Added
- Preliminary support for fix suggestions - Preliminary support for fix suggestions
- New `-f diff` unified diff format for auto-fixes
- Files containing Bats tests can now be checked - Files containing Bats tests can now be checked
- Directory wide directives can now be placed in a `.shellcheckrc` - Directory wide directives can now be placed in a `.shellcheckrc`
- Optional checks: Use `--list-optional` to show a list of tests, - Optional checks: Use `--list-optional` to show a list of tests,

View file

@ -57,6 +57,7 @@ library
bytestring, bytestring,
containers >= 0.5, containers >= 0.5,
deepseq >= 1.4.0.0, deepseq >= 1.4.0.0,
Diff >= 0.2.0,
directory >= 1.2.3.0, directory >= 1.2.3.0,
mtl >= 2.2.1, mtl >= 2.2.1,
filepath, filepath,
@ -78,6 +79,7 @@ library
ShellCheck.Fixer ShellCheck.Fixer
ShellCheck.Formatter.Format ShellCheck.Formatter.Format
ShellCheck.Formatter.CheckStyle ShellCheck.Formatter.CheckStyle
ShellCheck.Formatter.Diff
ShellCheck.Formatter.GCC ShellCheck.Formatter.GCC
ShellCheck.Formatter.JSON ShellCheck.Formatter.JSON
ShellCheck.Formatter.JSON1 ShellCheck.Formatter.JSON1
@ -100,6 +102,7 @@ executable shellcheck
bytestring, bytestring,
containers, containers,
deepseq >= 1.4.0.0, deepseq >= 1.4.0.0,
Diff >= 0.2.0,
directory >= 1.2.3.0, directory >= 1.2.3.0,
mtl >= 2.2.1, mtl >= 2.2.1,
filepath, filepath,
@ -118,6 +121,7 @@ test-suite test-shellcheck
bytestring, bytestring,
containers, containers,
deepseq >= 1.4.0.0, deepseq >= 1.4.0.0,
Diff >= 0.2.0,
directory >= 1.2.3.0, directory >= 1.2.3.0,
mtl >= 2.2.1, mtl >= 2.2.1,
filepath, filepath,

View file

@ -152,6 +152,23 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
... ...
</checkstyle> </checkstyle>
**diff**
: Auto-fixes in unified diff format. Can be piped to `git apply` or `patch -p1`
to automatically apply fixes.
--- a/test.sh
+++ b/test.sh
@@ -2,6 +2,6 @@
## Example of a broken script.
for f in $(ls *.m3u)
do
- grep -qi hq.*mp3 $f \
+ grep -qi hq.*mp3 "$f" \
&& echo -e 'Playlist $f contains a HQ file in mp3 format'
done
**json1** **json1**
: Json is a popular serialization format that is more suitable for web : Json is a popular serialization format that is more suitable for web

View file

@ -25,6 +25,7 @@ import ShellCheck.Regex
import qualified ShellCheck.Formatter.CheckStyle import qualified ShellCheck.Formatter.CheckStyle
import ShellCheck.Formatter.Format import ShellCheck.Formatter.Format
import qualified ShellCheck.Formatter.Diff
import qualified ShellCheck.Formatter.GCC import qualified ShellCheck.Formatter.GCC
import qualified ShellCheck.Formatter.JSON import qualified ShellCheck.Formatter.JSON
import qualified ShellCheck.Formatter.JSON1 import qualified ShellCheck.Formatter.JSON1
@ -141,6 +142,7 @@ parseArguments argv =
formats :: FormatterOptions -> Map.Map String (IO Formatter) formats :: FormatterOptions -> Map.Map String (IO Formatter)
formats options = Map.fromList [ formats options = Map.fromList [
("checkstyle", ShellCheck.Formatter.CheckStyle.format), ("checkstyle", ShellCheck.Formatter.CheckStyle.format),
("diff", ShellCheck.Formatter.Diff.format options),
("gcc", ShellCheck.Formatter.GCC.format), ("gcc", ShellCheck.Formatter.GCC.format),
("json", ShellCheck.Formatter.JSON.format), ("json", ShellCheck.Formatter.JSON.format),
("json1", ShellCheck.Formatter.JSON1.format), ("json1", ShellCheck.Formatter.JSON1.format),

View file

@ -0,0 +1,222 @@
{-
Copyright 2019 Vidar 'koala_man' Holen
This file is part of ShellCheck.
https://www.shellcheck.net
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.Formatter.Diff (format, ShellCheck.Formatter.Diff.runTests) where
import ShellCheck.Interface
import ShellCheck.Fixer
import ShellCheck.Formatter.Format
import Control.Monad
import Data.Algorithm.Diff
import Data.Array
import Data.IORef
import Data.List
import Data.Maybe
import qualified Data.Map as M
import GHC.Exts (sortWith)
import System.IO
import System.FilePath
import Test.QuickCheck
import Debug.Trace
ltt x = trace (show x) x
format :: FormatterOptions -> IO Formatter
format options = do
didOutput <- newIORef False
shouldColor <- shouldOutputColor (foColorOption options)
let color = if shouldColor then colorize else nocolor
return Formatter {
header = return (),
footer = checkFooter didOutput color,
onFailure = reportFailure color,
onResult = reportResult didOutput color
}
contextSize = 3
red = 31
green = 32
yellow = 33
cyan = 36
bold = 1
nocolor n = id
colorize n s = (ansi n) ++ s ++ (ansi 0)
ansi n = "\x1B[" ++ show n ++ "m"
printErr :: ColorFunc -> String -> IO ()
printErr color = hPutStrLn stderr . color bold . color red
reportFailure color file msg = printErr color $ file ++ ": " ++ msg
checkFooter didOutput color = do
output <- readIORef didOutput
unless output $
printErr color "Issues were detected, but none were auto-fixable. Use another format to see them."
type ColorFunc = (Int -> String -> String)
data DiffDoc a = DiffDoc String [DiffRegion a]
data DiffRegion a = DiffRegion (Int, Int) (Int, Int) [Diff a]
reportResult :: (IORef Bool) -> ColorFunc -> CheckResult -> SystemInterface IO -> IO ()
reportResult didOutput color result sys = do
let comments = crComments result
let suggestedFixes = mapMaybe pcFix comments
let fixmap = buildFixMap suggestedFixes
mapM_ output $ M.toList fixmap
where
output (name, fix) = do
file <- (siReadFile sys) name
case file of
Right contents -> do
putStrLn $ formatDoc color $ makeDiff name contents fix
writeIORef didOutput True
Left msg -> reportFailure color name msg
makeDiff :: String -> String -> Fix -> DiffDoc String
makeDiff name contents fix =
DiffDoc name $ findRegions . groupDiff $ computeDiff contents fix
computeDiff :: String -> Fix -> [Diff String]
computeDiff contents fix =
let old = lines contents
array = listArray (1, fromIntegral $ (length old)) old
new = applyFix fix array
in getDiff old new
-- Group changes into hunks
groupDiff :: [Diff a] -> [(Bool, [Diff a])]
groupDiff = filter (\(_, l) -> not (null l)) . hunt []
where
-- Churn through 'Both's until we find a difference
hunt current [] = [(False, reverse current)]
hunt current (x@Both {}:rest) = hunt (x:current) rest
hunt current list =
let (context, previous) = splitAt contextSize current
in (False, reverse previous) : gather context 0 list
-- Pick out differences until we find a run of Both's
gather current n [] =
let (extras, patch) = splitAt (max 0 $ n - contextSize) current
in [(True, reverse patch), (False, reverse extras)]
gather current n list@(Both {}:_) | n == contextSize*2 =
let (context, previous) = splitAt contextSize current
in (True, reverse previous) : hunt context list
gather current n (x@Both {}:rest) = gather (x:current) (n+1) rest
gather current n (x:rest) = gather (x:current) 0 rest
-- Get line numbers for hunks
findRegions :: [(Bool, [Diff String])] -> [DiffRegion String]
findRegions = find' 1 1
where
find' _ _ [] = []
find' left right ((output, run):rest) =
let (dl, dr) = countDelta run
remainder = find' (left+dl) (right+dr) rest
in
if output
then DiffRegion (left, dl) (right, dr) run : remainder
else remainder
-- Get left/right line counts for a hunk
countDelta :: [Diff a] -> (Int, Int)
countDelta = count' 0 0
where
count' left right [] = (left, right)
count' left right (x:rest) =
case x of
Both {} -> count' (left+1) (right+1) rest
First {} -> count' (left+1) right rest
Second {} -> count' left (right+1) rest
formatRegion :: ColorFunc -> DiffRegion String -> String
formatRegion color (DiffRegion left right diffs) =
let header = color cyan ("@@ -" ++ (tup left) ++ " +" ++ (tup right) ++" @@")
in
unlines $ header : map format diffs
where
tup (a,b) = (show a) ++ "," ++ (show b)
format (Both x _) = ' ':x
format (First x) = color red $ '-':x
format (Second x) = color green $ '+':x
formatDoc color (DiffDoc name regions) =
(color bold $ "--- " ++ ("a" </> name)) ++ "\n" ++
(color bold $ "+++ " ++ ("b" </> name)) ++ "\n" ++
concatMap (formatRegion color) regions
-- Create a Map from filename to Fix
buildFixMap :: [Fix] -> M.Map String Fix
buildFixMap fixes = perFile
where
splitFixes = concatMap splitFixByFile fixes
perFile = groupByMap (posFile . repStartPos . head . fixReplacements) splitFixes
-- There are currently no multi-file fixes, but let's handle it anyways
splitFixByFile :: Fix -> [Fix]
splitFixByFile fix = map makeFix $ groupBy sameFile (fixReplacements fix)
where
sameFile rep1 rep2 = (posFile $ repStartPos rep1) == (posFile $ repStartPos rep2)
makeFix reps = newFix { fixReplacements = reps }
groupByMap :: (Ord k, Monoid v) => (v -> k) -> [v] -> M.Map k v
groupByMap f = M.fromListWith (<>) . map (\x -> (f x, x))
-- For building unit tests
b n = Both n n
l = First
r = Second
prop_identifiesProperContext = groupDiff [b 1, b 2, b 3, b 4, l 5, b 6, b 7, b 8, b 9] ==
[(False, [b 1]), -- Omitted
(True, [b 2, b 3, b 4, l 5, b 6, b 7, b 8]), -- A change with three lines of context
(False, [b 9])] -- Omitted
prop_includesContextFromStartIfNecessary = groupDiff [b 4, l 5, b 6, b 7, b 8, b 9] ==
[ -- Nothing omitted
(True, [b 4, l 5, b 6, b 7, b 8]), -- A change with three lines of context
(False, [b 9])] -- Omitted
prop_includesContextUntilEndIfNecessary = groupDiff [b 4, l 5] ==
[ -- Nothing omitted
(True, [b 4, l 5])
] -- Nothing Omitted
prop_splitsIntoMultipleHunks = groupDiff [l 1, b 1, b 2, b 3, b 4, b 5, b 6, b 7, r 8] ==
[ -- Nothing omitted
(True, [l 1, b 1, b 2, b 3]),
(False, [b 4]),
(True, [b 5, b 6, b 7, r 8])
] -- Nothing Omitted
prop_splitsIntoMultipleHunksUnlessTouching = groupDiff [l 1, b 1, b 2, b 3, b 4, b 5, b 6, r 7] ==
[
(True, [l 1, b 1, b 2, b 3, b 4, b 5, b 6, r 7])
]
prop_countDeltasWorks = countDelta [b 1, l 2, r 3, r 4, b 5] == (3,4)
prop_countDeltasWorks2 = countDelta [] == (0,0)
return []
runTests = $quickCheckAll

View file

@ -22,8 +22,12 @@ module ShellCheck.Formatter.Format where
import ShellCheck.Data import ShellCheck.Data
import ShellCheck.Interface import ShellCheck.Interface
import ShellCheck.Fixer import ShellCheck.Fixer
import Control.Monad import Control.Monad
import Data.Array import Data.Array
import Data.List
import System.IO
import System.Info
-- A formatter that carries along an arbitrary piece of data -- A formatter that carries along an arbitrary piece of data
data Formatter = Formatter { data Formatter = Formatter {
@ -59,6 +63,17 @@ makeNonVirtual comments contents =
fixReplacements = map (\r -> removeTabStops r arr) (fixReplacements f) fixReplacements = map (\r -> removeTabStops r arr) (fixReplacements f)
} }
fix c = (removeTabStops c arr) { fix c = (removeTabStops c arr) {
pcFix = liftM untabbedFix (pcFix c) pcFix = fmap untabbedFix (pcFix c)
} }
shouldOutputColor :: ColorOption -> IO Bool
shouldOutputColor colorOption = do
term <- hIsTerminalDevice stdout
let windows = "mingw" `isPrefixOf` os
let isUsableTty = term && not windows
let useColor = case colorOption of
ColorAlways -> True
ColorNever -> False
ColorAuto -> isUsableTty
return useColor

View file

@ -188,13 +188,7 @@ code num = "SC" ++ show num
getColorFunc :: ColorOption -> IO ColorFunc getColorFunc :: ColorOption -> IO ColorFunc
getColorFunc colorOption = do getColorFunc colorOption = do
term <- hIsTerminalDevice stdout useColor <- shouldOutputColor colorOption
let windows = "mingw" `isPrefixOf` os
let isUsableTty = term && not windows
let useColor = case colorOption of
ColorAlways -> True
ColorNever -> False
ColorAuto -> isUsableTty
return $ if useColor then colorComment else const id return $ if useColor then colorComment else const id
where where
colorComment level comment = colorComment level comment =

View file

@ -8,6 +8,7 @@ import qualified ShellCheck.Checker
import qualified ShellCheck.Checks.Commands import qualified ShellCheck.Checks.Commands
import qualified ShellCheck.Checks.ShellSupport import qualified ShellCheck.Checks.ShellSupport
import qualified ShellCheck.Fixer import qualified ShellCheck.Fixer
import qualified ShellCheck.Formatter.Diff
import qualified ShellCheck.Parser import qualified ShellCheck.Parser
main = do main = do
@ -19,6 +20,7 @@ main = do
,ShellCheck.Checks.Commands.runTests ,ShellCheck.Checks.Commands.runTests
,ShellCheck.Checks.ShellSupport.runTests ,ShellCheck.Checks.ShellSupport.runTests
,ShellCheck.Fixer.runTests ,ShellCheck.Fixer.runTests
,ShellCheck.Formatter.Diff.runTests
,ShellCheck.Parser.runTests ,ShellCheck.Parser.runTests
] ]
if and results if and results