make hlint happy
This commit is contained in:
parent
72563ba54c
commit
94b5950ca5
10
src/Diff.hs
10
src/Diff.hs
|
@ -1,3 +1,5 @@
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
|
|
||||||
module Diff
|
module Diff
|
||||||
( diffToks
|
( diffToks
|
||||||
) where
|
) where
|
||||||
|
@ -49,8 +51,8 @@ stripEqToks t1 t2 = (pre, post, t1', t2')
|
||||||
lastDiff (i + 1)
|
lastDiff (i + 1)
|
||||||
| otherwise = i
|
| otherwise = i
|
||||||
e = lastDiff 0
|
e = lastDiff 0
|
||||||
pre = map (\t -> (Keep, t)) . V.toList . V.take b $ t1
|
pre = map (Keep, ) . V.toList . V.take b $ t1
|
||||||
post = map (\t -> (Keep, t)) . V.toList . V.drop (l1 - e) $ t1
|
post = map (Keep, ) . V.toList . V.drop (l1 - e) $ t1
|
||||||
t1' = V.slice b (l1 - e - b) t1
|
t1' = V.slice b (l1 - e - b) t1
|
||||||
t2' = V.slice b (l2 - e - b) t2
|
t2' = V.slice b (l2 - e - b) t2
|
||||||
|
|
||||||
|
@ -59,8 +61,8 @@ diffToks t1' t2' = pre ++ res ++ post
|
||||||
where
|
where
|
||||||
(pre, post, t1, t2) = stripEqToks t1' t2'
|
(pre, post, t1, t2) = stripEqToks t1' t2'
|
||||||
res
|
res
|
||||||
| V.null t1 = map (\t -> (Add, t)) (V.toList t2)
|
| V.null t1 = map (Add, ) (V.toList t2)
|
||||||
| V.null t2 = map (\t -> (Remove, t)) (V.toList t1)
|
| V.null t2 = map (Remove, ) (V.toList t1)
|
||||||
| V.length t1 >= V.length t2 =
|
| V.length t1 >= V.length t2 =
|
||||||
diffToks' $
|
diffToks' $
|
||||||
DiffEnv
|
DiffEnv
|
||||||
|
|
11
src/Diff3.hs
11
src/Diff3.hs
|
@ -1,3 +1,4 @@
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
module Diff3 where
|
module Diff3 where
|
||||||
|
|
||||||
import Diff
|
import Diff
|
||||||
|
@ -28,8 +29,8 @@ diff3Toks tMine tOrig tYour =
|
||||||
align ((Add, a):as) bs@((Remove, _):_) = (Mine, (Add, a)) : align as bs
|
align ((Add, a):as) bs@((Remove, _):_) = (Mine, (Add, a)) : align as bs
|
||||||
align as@((Remove, _):_) ((Add, b):bs) = (Your, (Add, b)) : align as bs
|
align as@((Remove, _):_) ((Add, b):bs) = (Your, (Add, b)) : align as bs
|
||||||
align [] [] = []
|
align [] [] = []
|
||||||
align as@((Add, _):_) [] = map ((,) Mine) as
|
align as@((Add, _):_) [] = map (Mine,) as
|
||||||
align [] bs@((Add, _):_) = map ((,) Your) bs
|
align [] bs@((Add, _):_) = map (Your,) bs
|
||||||
align _ _ = error "Internal failure: diffstreams seem broken, cannot align"
|
align _ _ = error "Internal failure: diffstreams seem broken, cannot align"
|
||||||
conflict :: [(Origin, (Op, Tok))] -> Diff
|
conflict :: [(Origin, (Op, Tok))] -> Diff
|
||||||
conflict [] = []
|
conflict [] = []
|
||||||
|
@ -46,9 +47,9 @@ diff3Toks tMine tOrig tYour =
|
||||||
[tokMine, tokYour] = map (map snd.filter ((/= Remove) . fst)) mys
|
[tokMine, tokYour] = map (map snd.filter ((/= Remove) . fst)) mys
|
||||||
in if tokOrigsMine /= tokOrigsYour
|
in if tokOrigsMine /= tokOrigsYour
|
||||||
then error "Internal failure: merge origins differ"
|
then error "Internal failure: merge origins differ"
|
||||||
else map ((,) MineChanged) tokMine ++
|
else map (MineChanged,) tokMine ++
|
||||||
map ((,) Original) tokOrigsMine ++
|
map (Original,) tokOrigsMine ++
|
||||||
map ((,) YourChanged) tokYour
|
map (YourChanged,) tokYour
|
||||||
stable (Stable, _) = True
|
stable (Stable, _) = True
|
||||||
stable _ = False
|
stable _ = False
|
||||||
unstable = not . stable
|
unstable = not . stable
|
||||||
|
|
|
@ -25,7 +25,7 @@ pprDiff1 :: (Op, Tok) -> BB.Builder
|
||||||
pprDiff1 (op, (tok, s)) =
|
pprDiff1 (op, (tok, s)) =
|
||||||
fromString pfx <> escNewlines s <> lineSep
|
fromString pfx <> escNewlines s <> lineSep
|
||||||
where
|
where
|
||||||
pfx = opc:tc:[]
|
pfx = [opc,tc]
|
||||||
opc = case op of
|
opc = case op of
|
||||||
Add -> '+'
|
Add -> '+'
|
||||||
Keep -> ' '
|
Keep -> ' '
|
||||||
|
|
|
@ -101,7 +101,7 @@ actionOption =
|
||||||
adiffOptions = ADiffOptions <$> redfaOption <*> actionOption
|
adiffOptions = ADiffOptions <$> redfaOption <*> actionOption
|
||||||
|
|
||||||
loadToks redfa f =
|
loadToks redfa f =
|
||||||
mmapFileByteString f Nothing >>= redfaTokenize redfa >>= pure . V.fromList
|
mmapFileByteString f Nothing >>= (V.fromList <$> redfaTokenize redfa)
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main =
|
main =
|
||||||
|
|
Loading…
Reference in a new issue