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