- Add code to visualize an instance and matching as a graph (bipartite, rather
[match/match.git] / program / Test.hs
index 43f93a7..cef7a53 100644 (file)
@@ -1,19 +1,83 @@
-module Test where
+module Test (
+       -- Export everything we need to have fun in GHCi:
+       
+       -- See the results of examples.
+       module Test,
+       
+       -- Generate instances.
+       module Instance,
+       module InstanceGenerator,
+       
+       -- Solve instances.
+       module ProposalMatcher,
+       module ProposalMatcherConfig,
+       
+       -- Run randomized things.
+       module System.Random,
+       module RandomizedMonad,
+       
+       -- Visualize graphs.
+       module Data.Graph.Inductive.Graphviz
+) where
+import Instance
+import InstanceGenerator
+import ProposalMatcher
+import ProposalMatcherConfig
+import System.Random
+import RandomizedMonad
+import Data.Graph.Inductive.Graphviz
+
+-- Other imports we need
 import BellmanFord
-import UnitMinCostFlow
-import ProposalMatch
-import ProposalMatchConfig
-import Data.Array
+import NaiveMinCostFlow
+import Data.Array.IArray
+import Data.Array.Unboxed
 import Data.Graph.Inductive.Graph
 import Data.Graph.Inductive.Tree
+import ArrayStuff
+
+-- A fixed-seeded random number generator for reproducible experimentation.
+myGen = read "314159265 1" :: StdGen
 
+-- TESTING GRAPH ALGORITHMS
 myGraph = mkGraph [(0, ()), (1, ()), (2, ())]
-       [(0, 1, 2), (0, 2, 3), (2, 1, -2)] :: Gr () Double 
+       [(0, 1, (0, 2)), (0, 2, (1, 3)), (2, 1, (2, -2))] :: Gr () (Int, Int)
+
+bfResult = bellmanFord snd 0 myGraph
+
+flowArray = minCostFlow (0, 2) fst (const 1) snd myGraph (0, 1)
 
-spTree1 = spTree 0 myGraph
+myNCGraph = mkGraph [(0, ())] [(0, 0, -1)] :: Gr () Int
+bfNCResult = bellmanFord id 0 myNCGraph
 
-(flowVal, flowResid) = umcf 0 1 myGraph
+-- VISUALIZATION STUFF
+data REdgeF = REdgeF Int Int Int Wt
+instance Show REdgeF where
+       show (REdgeF idx cap flow cost) = "#" ++ (show idx) ++ ": "
+               ++ (show flow) ++ " of " ++ (show cap) ++ " @ " ++ (show cost)
+flowAnnotate g fa =
+       mkGraph (labNodes g) (map (\(n1, n2, REdge i ca co) ->
+               (n1, n2, REdgeF i ca (fa ! i) co)) $ labEdges g) :: Gr () REdgeF
 
+showInstanceAsGraph :: Instance -> [(Int, Int)] -> Gr String String
+showInstanceAsGraph (Instance numRvrs numProps rloadA prefA) matchedPairs =
+       let
+               rvrNode i = i
+               propNode j = numRvrs + j
+               numNodes = numRvrs + numProps
+               theNodes = map (\i -> (rvrNode i, "R#" ++ show i ++
+                               " (RLoad " ++ show (rloadA ! i) ++ ")")) [0..numRvrs-1] ++
+                       map (\j -> (propNode j, "P#" ++ show j)) [0..numProps-1]
+               parenthesizeIf False s = s
+               parenthesizeIf True s = "(" ++ s ++ ")"
+               theEdges = do
+                       i <- [0..numRvrs-1]
+                       j <- [0..numProps-1]
+                       return (rvrNode i, propNode j,
+                               parenthesizeIf (elem (i, j) matchedPairs) $ show (prefA ! (i, j)))
+       in mkGraph theNodes theEdges
+
+-- PROPOSAL-MATCHING EXAMPLES
 -- Example from idea book p. 425
 {- 
 (myNumRvrs, myNumProps) = (4, 3)
@@ -27,16 +91,18 @@ myPrefsArray = array ((0,0), (myNumRvrs-1,myNumProps-1)) [
 
 (myNumRvrs, myNumProps) = (5, 3)
 
-myPrefsArray = array ((0,0), (myNumRvrs-1,myNumProps-1)) [
-       ((0, 0), 15), ((1, 0), 10), ((2, 0), 15), ((3, 0), 40), ((4, 0), 20),
-       ((0, 1), 30), ((1, 1),  7), ((2, 1), 10), ((3, 1), 15), ((4, 1), 15),
-       ((0, 2), 15), ((1, 2), 25), ((2, 2), 20), ((3, 2), 20), ((4, 2), 15)
-       ]
+myPrefs = transposeArray $ listArray ((0,0), (myNumProps-1,myNumRvrs-1)) [
+       15, 10, 15, 40, 20,
+       30,  7, 10, 15, 15,
+       15, 25, 20, 20, 15
+       ] :: UArray (Int, Int) Wt
 
-myPrefs = \i j -> myPrefsArray ! (i, j)
-myInst = Instance myNumRvrs myNumProps myPrefs
+myInst = Instance myNumRvrs myNumProps (funcArray (0, myNumRvrs-1) $ const 1) myPrefs
 
---rdnGraph = doReduction myInst (const (fromInteger wantExpertReviews))
---(rdnFlowVal, rdnFlowResid) = umcf 0 1 rdnGraph
---rdnFlow = flowDiff rdnGraph rdnFlowResid
+rdnResult = doReduction myInst
+ReductionResult rrg rrso rrsi rreib rredi = rdnResult
+rdnFlowArray = minCostFlow rreib reIdx reCap reCost rrg (rrso, rrsi)
+rrg2 = flowAnnotate rrg rdnFlowArray
 myMatching = doMatching myInst
+
+iGraph = showInstanceAsGraph myInst myMatching -- Visualize me!