Skip to content

Commit 0354c3a

Browse files
committed
Redo tests of TransClos, going back to basics.
Remove use of 'isSubsequenceOf'. Strengthen arbitrary graph choices. Simplify and make consistent the testing procedure, with comments.
1 parent 83711c9 commit 0354c3a

File tree

1 file changed

+31
-27
lines changed

1 file changed

+31
-27
lines changed

test/Data/Graph/Inductive/Query/Properties.hs

Lines changed: 31 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ import Test.Hspec (Spec, describe, it, shouldBe, shouldMatchList,
2626
import Test.QuickCheck
2727

2828
import Control.Arrow (second)
29-
import Data.List (delete, sort, unfoldr, isSubsequenceOf, group)
29+
import Data.List (delete, sort, unfoldr, group, (\\))
3030
import qualified Data.Set as S
3131

3232
#if __GLASGOW_HASKELL__ < 710
@@ -327,38 +327,42 @@ test_sp _ cg = all test_p (map unLPath (msTree g))
327327
-- -----------------------------------------------------------------------------
328328
-- TransClos
329329

330-
test_trc :: (ArbGraph gr, Eq (BaseGraph gr a ())) => Proxy (gr a b)
331-
-> UConnected (SimpleGraph gr) a ()
332-
-> Bool
333-
test_trc _ cg = gReach == trc g
330+
-- | The transitive, reflexive closure of a graph means that every
331+
-- node is a successor of itself, and also that if (a, b) is an edge,
332+
-- and (b, c) is an edge, then (a, c) must also be an edge.
333+
test_trc :: DynGraph gr => Proxy (gr a b) -> (NoMultipleEdges gr) a b -> Bool
334+
test_trc _ nme = all valid $ nodes gTrans
334335
where
335-
g = connGraph cg
336-
337-
lns = labNodes g
338-
339-
gReach = (`asTypeOf` g)
340-
. insEdges [(v,w,()) | (v,_) <- lns, (w,_) <- lns]
341-
$ mkGraph lns []
342-
343-
test_tc :: (ArbGraph gr, Eq (BaseGraph gr a ())) => Proxy (gr a b)
344-
-> Connected (SimpleGraph gr) a ()
345-
-> Bool
346-
test_tc _ cg = all valid $ nodes gTrans
336+
g = emap (const ()) (nmeGraph nme)
337+
gTrans = trc g
338+
valid n =
339+
-- For each node n, check that:
340+
-- the successors for n in gTrans are a superset of the successors for n in g.
341+
null (suc g n \\ suc gTrans n) &&
342+
-- the successors for n in gTrans are exactly equal to the reachable nodes for n in g, plus n.
343+
sort (suc gTrans n) == map head (group (sort (n:[ v | u <- suc g n, v <- reachable u g ])))
344+
345+
-- | The transitive closure of a graph means that if (a, b) is an
346+
-- edge, and (b, c) is an edge, then (a, c) must also be an edge.
347+
test_tc :: DynGraph gr => Proxy (gr a b) -> (NoMultipleEdges gr) a b -> Bool
348+
test_tc _ nme = all valid $ nodes gTrans
347349
where
348-
g = connGraph cg
350+
g = nmeGraph nme
349351
gTrans = tc g
350-
valid n = suc g n `isSubsequenceOf` suc gTrans n &&
351-
sort (suc gTrans n) == map head (group (sort [ v | u <- suc g n, v <- reachable u g ]))
352-
353-
test_rc :: (ArbGraph gr, Eq (BaseGraph gr a ())) => Proxy (gr a b)
354-
-> Connected (SimpleGraph gr) a ()
355-
-> Bool
356-
test_rc _ cg = and [ n `elem` suc gRefl n | n <- nodes gRefl ]
352+
valid n =
353+
-- For each node n, check that:
354+
-- the successors for n in gTrans are a superset of the successors for n in g.
355+
null (suc g n \\ suc gTrans n) &&
356+
-- the successors for n in gTrans are exactly equal to the reachable nodes for n in g.
357+
sort (suc gTrans n) == map head (group (sort [ v | u <- suc g n, v <- reachable u g ]))
358+
359+
-- | The reflexive closure of a graph means that all nodes are a
360+
-- successor of themselves.
361+
test_rc :: DynGraph gr => Proxy (gr a b) -> gr a b -> Bool
362+
test_rc _ g = and [ n `elem` suc gRefl n | n <- nodes gRefl ]
357363
where
358-
g = connGraph cg
359364
gRefl = rc g
360365

361-
362366
-- -----------------------------------------------------------------------------
363367
-- Utility functions
364368

0 commit comments

Comments
 (0)