- More evaluation.
[match/match.git] / program / TestUtils.hs
CommitLineData
fd0d2377
MM
1module TestUtils where
2import Control.Concurrent
3import Data.Array.IArray
4import Data.Graph.Inductive.Graph
5import Data.Graph.Inductive.Graphviz
6import Data.Graph.Inductive.Tree
89b7fd0d 7import Data.List
fd0d2377
MM
8import System.IO
9import System.Random
10import System.Posix.IO
11import System.Posix.Time
12import System.Process
05a6f0ed 13import PMInstance
fd0d2377 14import ProposalMatcher
89b7fd0d
MM
15import PMDefaults
16import PMInstanceGenerator
17import Evaluation
fd0d2377 18import MonadStuff
89b7fd0d 19import RandomizedMonad
fd0d2377
MM
20
21-- This module has stuff that is helpful for testing but isn't itself an example.
22
23-- A fixed-seeded random number generator for reproducible experimentation.
24myGen = read "314159265 1" :: StdGen
25
26-- Visualization stuff.
27data REdgeF = REdgeF Int Int Int Wt
28instance Show REdgeF where
29 show (REdgeF idx cap flow cost) = "#" ++ (show idx) ++ ": "
30 ++ (show flow) ++ " of " ++ (show cap) ++ " @ " ++ (show cost)
31flowAnnotate g fa =
32 mkGraph (labNodes g) (map (\(n1, n2, REdge i ca co) ->
33 (n1, n2, REdgeF i ca (fa ! i) co)) $ labEdges g) :: Gr () REdgeF
34
05a6f0ed
MM
35showInstanceAsGraph :: PMInstance -> PMatching -> Gr String String
36showInstanceAsGraph (PMInstance numRvrs numProps rloadA prefA) matchedPairs =
fd0d2377
MM
37 let
38 rvrNode i = i
39 propNode j = numRvrs + j
40 numNodes = numRvrs + numProps
41 theNodes = map (\i -> (rvrNode i, "R#" ++ show i ++
42 " (RLoad " ++ show (rloadA ! i) ++ ")")) [0..numRvrs-1] ++
43 map (\j -> (propNode j, "P#" ++ show j)) [0..numProps-1]
44 parenthesizeIf False s = s
45 parenthesizeIf True s = "(" ++ s ++ ")"
46 theEdges = do
47 i <- [0..numRvrs-1]
48 j <- [0..numProps-1]
49 return (rvrNode i, propNode j,
50 parenthesizeIf (elem (i, j) matchedPairs) $ show (prefA ! (i, j)))
51 in mkGraph theNodes theEdges
52
53goFile :: String -> IO ()
54goFile fname = do
55 pid <- runCommand ("gnome-open " ++ fname)
56 waitForProcess pid -- gnome-open exits immediately
57 nop
58
59createHandlePipe :: IO (Handle, Handle)
60createHandlePipe = do
61 (rFd, wFd) <- createPipe
62 rH <- fdToHandle rFd
63 wH <- fdToHandle wFd
64 return (rH, wH)
65
66-- GHCi seems to crash if I call this on a "showInstanceAsGraph" result without
67-- having previously forced evaluation of the matching.
68goGraph :: (Show a, Show b, Graph gr) => gr a b -> IO ()
69goGraph theGraph =
70 -- First generate graphviz code.
71 let gvCode = graphviz' theGraph in do
72 -- Then have `dot' convert it to postscript in a file.
73 (rH, wH) <- createHandlePipe
74 pt <- epochTime
75 let fname = "graph-" ++ show pt ++ ".ps"
76 dotPid <- runProcess "dot" ["-Tps", "-o", fname]
77 Nothing Nothing (Just rH) Nothing Nothing
78 forkIO (do
79 hPutStr wH gvCode
80 hClose wH)
81 waitForProcess dotPid
82 -- Then open the file.
83 goFile fname
89b7fd0d
MM
84
85-- Both-ways list difference
86(/\) :: Eq a => [a] -> [a] -> ([a], [a])
87l1 /\ l2 = (l1 \\ l2, l2 \\ l1)
88
89-- Evaluation!
90runEvaluation nr np = do
91 let inst = runRandom myGen $ randomInstance nr np
92 putStr (show inst ++ "\n")
93 let m0 = doMatching pmDefaults{loadTolerance = 0} inst
94 putStr ("Matching with load tolerance 0:\n" ++ show m0 ++ "\n")
95 let m1 = doMatching pmDefaults{loadTolerance = 1} inst
96 putStr ("Matching with load tolerance 1:\n" ++ show m1 ++ "\n")
97 putStr ("Differences:\n" ++ show (m0 /\ m1) ++ "\n")
98 let e0 = evaluateMatching pmDefaults{loadTolerance = 0} inst m0
99 putStr ("Evaluation of first matching:\n" ++ show e0 ++ "\n")
100 let e1 = evaluateMatching pmDefaults{loadTolerance = 1} inst m1
101 putStr ("Evaluation of second matching:\n" ++ show e1 ++ "\n")
102 putStr ("Evaluation differences:\n" ++
103 show (sortedDiffEvaluations e0 e1) ++ "\n")