-- Do not edit! Automatically created with doctest-extract from src/Data/Graph/Comfort.hs {-# LINE 91 "src/Data/Graph/Comfort.hs" #-} module Test.Data.Graph.Comfort where import qualified Test.DocTest.Driver as DocTest {-# LINE 92 "src/Data/Graph/Comfort.hs" #-} import Test.Base import qualified Data.Graph.Comfort as Graph import qualified Data.Map as Map import qualified Data.Set as Set import qualified Data.Char as Char import qualified Control.Monad.Trans.Class as MT import qualified Control.Monad.Trans.State as MS import Control.Applicative (pure) import Data.Functor.Identity (Identity(Identity), runIdentity) import qualified Test.QuickCheck as QC import Test.QuickCheck ((==>)) deleteNodeIfExists :: Node -> MonoGraph -> MonoGraph deleteNodeIfExists n gr = maybe gr (const $ Graph.deleteNode n gr) $ Graph.lookupNode n gr isolated :: (Graph.Edge e, Ord n) => Graph.Graph e n el nl -> n -> Bool isolated gr n = Set.null (Graph.adjacentEdgeSet gr n) nodeAction :: (Monad m) => NodeLabel -> MS.StateT NodeLabel m NodeLabel nodeAction x = do y <- MS.get; MS.put x; return y evalTraverseNode :: NodeLabel -> MonoGraph -> MonoGraph evalTraverseNode nl = flip MS.evalState nl . Graph.traverseNode nodeAction edgeAction :: (Monad m) => EdgeLabel -> MS.StateT EdgeLabel m EdgeLabel edgeAction x = MS.modify (x+) >> MS.get evalTraverseEdge :: EdgeLabel -> MonoGraph -> MonoGraph evalTraverseEdge el = flip MS.evalState el . Graph.traverseEdge edgeAction evalTraverse :: NodeLabel -> EdgeLabel -> MonoGraph -> MonoGraph evalTraverse nl el = flip MS.evalState el . flip MS.evalStateT nl . Graph.traverse nodeAction (MT.lift . edgeAction) test :: DocTest.T () test = do DocTest.printPrefix "Data.Graph.Comfort:358: " {-# LINE 358 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 358 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) -> Graph.isConsistent (Graph.reverse gr)) DocTest.printPrefix "Data.Graph.Comfort:359: " {-# LINE 359 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 359 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) -> Graph.reverse (Graph.reverse gr) == gr) DocTest.printPrefix "Data.Graph.Comfort:410: " {-# LINE 410 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 410 "src/Data/Graph/Comfort.hs" #-} (Graph.isEmpty (Graph.empty :: MonoGraph)) DocTest.printPrefix "Data.Graph.Comfort:411: " {-# LINE 411 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 411 "src/Data/Graph/Comfort.hs" #-} (Graph.isConsistent (Graph.empty :: MonoGraph)) DocTest.printPrefix "Data.Graph.Comfort:465: " {-# LINE 465 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 465 "src/Data/Graph/Comfort.hs" #-} (\(GraphAndEdge gr e) -> Graph.lookupEdge e gr == Map.lookup e (Graph.edgeLabels gr)) DocTest.printPrefix "Data.Graph.Comfort:483: " {-# LINE 483 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 483 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) n -> Graph.lookupNode n gr == Map.lookup n (Graph.nodeLabels gr)) DocTest.printPrefix "Data.Graph.Comfort:527: " {-# LINE 527 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 527 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) n -> Graph.isConsistent $ deleteNodeIfExists n gr) DocTest.printPrefix "Data.Graph.Comfort:528: " {-# LINE 528 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 528 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) n nl -> Graph.deleteNode n (Graph.insertNode n nl gr) == deleteNodeIfExists n gr) DocTest.printPrefix "Data.Graph.Comfort:529: " {-# LINE 529 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 529 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) -> let isolatedNodes = filter (isolated gr) $ Graph.nodes gr in not (null isolatedNodes) ==> QC.forAll (QC.elements isolatedNodes) $ \n nl -> Graph.insertNode n nl gr == Graph.insertNode n nl (Graph.deleteNode n gr)) DocTest.printPrefix "Data.Graph.Comfort:555: " {-# LINE 555 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 555 "src/Data/Graph/Comfort.hs" #-} (\(GraphAndEdge gr e) -> Graph.isConsistent $ Graph.deleteEdge e gr) DocTest.printPrefix "Data.Graph.Comfort:556: " {-# LINE 556 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 556 "src/Data/Graph/Comfort.hs" #-} (\(GraphAndEdge gr e) el -> Graph.deleteEdge e (Graph.insertEdge e el gr) == Graph.deleteEdge e gr) DocTest.printPrefix "Data.Graph.Comfort:557: " {-# LINE 557 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 557 "src/Data/Graph/Comfort.hs" #-} (\(GraphAndEdge gr e) el -> Graph.insertEdge e el gr == Graph.insertEdge e el (Graph.deleteEdge e gr)) DocTest.printPrefix "Data.Graph.Comfort:568: " {-# LINE 568 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 568 "src/Data/Graph/Comfort.hs" #-} (\(GraphAndEdge gr e) -> Graph.filterEdgeWithKey (\ei _ -> e/=ei) gr == Graph.deleteEdge e gr) DocTest.printPrefix "Data.Graph.Comfort:621: " {-# LINE 621 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 621 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) n nl -> Graph.isConsistent $ Graph.insertNode n nl gr) DocTest.printPrefix "Data.Graph.Comfort:622: " {-# LINE 622 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 622 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) n nl -> Graph.lookupNode n (Graph.insertNode n nl gr) == Just nl) DocTest.printPrefix "Data.Graph.Comfort:634: " {-# LINE 634 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 634 "src/Data/Graph/Comfort.hs" #-} (\(GraphAndEdge gr e) el -> Graph.isConsistent $ Graph.insertEdge e el gr) DocTest.printPrefix "Data.Graph.Comfort:635: " {-# LINE 635 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 635 "src/Data/Graph/Comfort.hs" #-} (\(GraphAndEdge gr e) el -> Graph.lookupEdge e (Graph.insertEdge e el gr) == Just el) DocTest.printPrefix "Data.Graph.Comfort:669: " {-# LINE 669 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 669 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) -> gr == Graph.fromMap (Graph.nodeLabels gr) (Graph.edgeLabels gr)) DocTest.printPrefix "Data.Graph.Comfort:689: " {-# LINE 689 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 689 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) -> Graph.mapNode id gr == gr) DocTest.printPrefix "Data.Graph.Comfort:702: " {-# LINE 702 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 702 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) -> Graph.mapEdge id gr == gr) DocTest.printPrefix "Data.Graph.Comfort:738: " {-# LINE 738 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 738 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) nl -> Graph.isConsistent $ evalTraverseNode nl gr) DocTest.printPrefix "Data.Graph.Comfort:739: " {-# LINE 739 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 739 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) -> runIdentity (Graph.traverseNode (Identity . Char.toUpper) gr) == Graph.mapNode Char.toUpper gr) DocTest.printPrefix "Data.Graph.Comfort:752: " {-# LINE 752 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 752 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) el -> Graph.isConsistent $ evalTraverseEdge el gr) DocTest.printPrefix "Data.Graph.Comfort:753: " {-# LINE 753 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 753 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) el -> runIdentity (Graph.traverseEdge (Identity . (el+)) gr) == Graph.mapEdge (el+) gr) DocTest.printPrefix "Data.Graph.Comfort:764: " {-# LINE 764 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 764 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) nl el -> Graph.isConsistent $ evalTraverse nl el gr) DocTest.printPrefix "Data.Graph.Comfort:765: " {-# LINE 765 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 765 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) nl el -> evalTraverse nl el gr == evalTraverseNode nl (evalTraverseEdge el gr)) DocTest.printPrefix "Data.Graph.Comfort:766: " {-# LINE 766 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 766 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) nl el -> evalTraverse nl el gr == evalTraverseEdge el (evalTraverseNode nl gr)) DocTest.printPrefix "Data.Graph.Comfort:767: " {-# LINE 767 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 767 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) nl -> flip MS.evalState nl (Graph.traverseNode nodeAction gr) == flip MS.evalState nl (Graph.traverse nodeAction pure gr)) DocTest.printPrefix "Data.Graph.Comfort:768: " {-# LINE 768 "src/Data/Graph/Comfort.hs" #-} DocTest.property {-# LINE 768 "src/Data/Graph/Comfort.hs" #-} (\(TestGraph gr) el -> flip MS.evalState el (Graph.traverseEdge edgeAction gr) == flip MS.evalState el (Graph.traverse pure edgeAction gr))