1
+ {-# LANGUAGE LambdaCase #-}
2
+ {-# LANGUAGE ScopedTypeVariables #-}
3
+
1
4
module Main where
2
5
3
6
import Test.Framework (defaultMain , testGroup )
@@ -6,6 +9,9 @@ import Test.QuickCheck
6
9
import Data.Algorithm.Diff
7
10
import Data.Algorithm.DiffContext
8
11
import Data.Algorithm.DiffOutput
12
+ import qualified Data.Array as A
13
+ import Data.Foldable
14
+ import Data.Semigroup (Arg (.. ))
9
15
import Text.PrettyPrint
10
16
11
17
import System.IO
@@ -32,7 +38,8 @@ main = defaultMain [ testGroup "sub props" [
32
38
slTest2 " lcsBoth" prop_lcsBoth,
33
39
slTest2 " recover first" prop_recoverFirst,
34
40
slTest2 " recover second" prop_recoverSecond,
35
- slTest2 " lcs" prop_lcs
41
+ slTest2 " lcs" prop_lcs,
42
+ testProperty " compare random with reference" prop_compare_with_reference
36
43
],
37
44
testGroup " output props" [
38
45
testProperty " self generates empty" $ forAll shortLists prop_ppDiffEqual,
@@ -210,3 +217,59 @@ prop_context_diff =
210
217
actual = getContextDiff 2 (lines textA) (lines textB)
211
218
textA = " a\n b\n c\n d\n e\n f\n g\n h\n i\n j\n k\n "
212
219
textB = " a\n b\n d\n e\n f\n g\n h\n i\n j\n "
220
+
221
+ -- | Reference implementation, very slow.
222
+ naiveGetDiffBy :: forall a b . (a -> b -> Bool ) -> [a ] -> [b ] -> [PolyDiff a b ]
223
+ naiveGetDiffBy eq as bs = reverse $ (\ (Arg _ ds) -> ds) $ tbl A. ! (length us, length vs)
224
+ where
225
+ us = A. listArray (0 , length as - 1 ) as
226
+ vs = A. listArray (0 , length bs - 1 ) bs
227
+
228
+ -- Indices run up to length us/vs *inclusive*
229
+ tbl :: A. Array (Int , Int ) (Arg Word [PolyDiff a b ])
230
+ tbl = A. listArray ((0 , 0 ), (length us, length vs))
231
+ [ gen ui vi | ui <- [0 .. length us], vi <- [0 .. length vs] ]
232
+
233
+ gen :: Int -> Int -> Arg Word [PolyDiff a b ]
234
+ gen ui vi
235
+ | ui == 0 , vi == 0 = Arg 0 []
236
+ | ui == 0
237
+ = left'
238
+ | vi == 0
239
+ = top'
240
+ | otherwise
241
+ = if eq u v
242
+ then min (min left' top') diag'
243
+ else min left' top'
244
+ where
245
+ Arg leftL leftP = tbl A. ! (ui, vi - 1 )
246
+ Arg diagL diagP = tbl A. ! (ui - 1 , vi - 1 )
247
+ Arg topL topP = tbl A. ! (ui - 1 , vi)
248
+
249
+ u = us A. ! (ui - 1 )
250
+ v = vs A. ! (vi - 1 )
251
+
252
+ left' = Arg (leftL + 1 ) (Second v : leftP)
253
+ top' = Arg (topL + 1 ) (First u : topP)
254
+ diag' = Arg diagL (Both u v : diagP)
255
+
256
+ prop_compare_with_reference :: Positive Word -> [(Int , Int )] -> Property
257
+ prop_compare_with_reference (Positive x) ixs' =
258
+ counterexample (show (as, bs, d1, d2)) $
259
+ length (notBoth d1) === length (notBoth d2)
260
+ where
261
+ as = [0 .. max 100 x]
262
+ len = length as
263
+ ixs = filter (uncurry (/=) ) $ map (\ (i, j) -> (i `mod` len, j `mod` len)) $ take 100 ixs'
264
+ bs = foldl' applySwap as ixs
265
+ d1 = getDiffBy (==) as bs
266
+ d2 = naiveGetDiffBy (==) as bs
267
+
268
+ applySwap xs (i, j) = zipWith
269
+ (\ k x -> (if k == i then xs !! j else if k == j then xs !! i else x))
270
+ [0 .. ]
271
+ xs
272
+
273
+ notBoth = filter $ \ case
274
+ Both {} -> False
275
+ _ -> True
0 commit comments