The random instance generator and other improvements.
[match/match.git] / program / InstanceGenerator.hs
1 module InstanceGenerator where
2 import Instance
3 import System.Random
4 import RandomizedMonad
5 import Data.Array.IArray
6 import ArrayStuff
7
8 randomMap :: RandomGen g => g -> (g -> a -> b) -> [a] -> [b]
9 randomMap g f l = case l of
10         [] -> []
11         h:t -> let (g1, g2) = split g in (f g1 h):(randomMap g2 f t)
12 randomRep :: RandomGen g => g -> (g -> a) -> Int -> [a]
13 randomRep g f n = if n == 0 then []
14         else let (g1, g2) = split g in (f g1):(randomRep g2 f (n-1))
15
16 numTopics = 20
17
18 -- Expertise on each of the topics
19 type ReviewerInfo = Array Int Double
20
21 randomReviewerInfo = do
22         list <- sequence $ replicate numTopics $
23                 withProb [(0.15, return 2), (0.4, return 1)] (return 0)
24         return $ listArray (0, numTopics-1) list
25
26 -- One topic or two different topics
27 data ProposalTopics = PTopic1 Int | PTopic2 Int Int
28
29 --type ProposalAuthors = Maybe Int
30
31 type ProposalInfo = (ProposalTopics, Wt)
32
33 randomProposalTopics = do
34         t1 <- mrandomR (0, numTopics-1)
35         withProb [(0.5, return $ PTopic1 t1)] (do
36                 t2 <- filterRandomized (/= t1) $ mrandomR (0, numTopics-1)
37                 return $ PTopic2 t1 t2
38                 )
39
40 -- Add conflict of interest later.
41 {--
42 randomProposalAuthors = do
43         withProb [(0.5, return [])] (do
44                 a1 <- mrandomR (0, numRvrs-1)
45                 withProb [(0.5, return [a1])] (do
46                         a2 <- filterRandomized (/= a1) $ mrandomR (0, numRvrs-1)
47                         return [a1,a2]
48                         )
49                 )
50 --}
51
52 randomProposalInfo = do
53         topics <- randomProposalTopics
54         diff <- mrandomR (3, 5)
55         return (topics, fromInteger diff)
56
57 expertnessToPref expertness = if expertness == 0 then 7
58         else if expertness == 1 then 5
59         else 3
60
61 randomInstance :: Int -> Int -> Randomized Instance
62 randomInstance numRvrs numProps = do
63         reviewerInfosList <- sequence $ replicate numRvrs $ randomReviewerInfo
64         -- reviewerProfs is an array of arrays.
65         -- A pair-indexed array might be better...
66         let reviewerInfos = listArray (0, numRvrs-1) reviewerInfosList :: Array Int ReviewerInfo
67         proposalInfosList <- sequence $ replicate numProps $ randomProposalInfo
68         let proposalInfos = listArray (0, numProps-1) proposalInfosList :: Array Int ProposalInfo
69         let loadA = funcArray (0, numRvrs-1) $ const 1
70         let prefA = funcArray ((0, 0), (numRvrs-1, numProps-1)) (\(i,j) ->
71                 let
72                         ii = reviewerInfos ! i
73                         jj = proposalInfos ! j
74                         topicPref = case fst jj of
75                                 PTopic1 t1 -> expertnessToPref (ii ! t1)
76                                 PTopic2 t1 t2 -> (expertnessToPref (ii ! t1) + expertnessToPref (ii ! t2)) / 2
77                 in topicPref * snd jj - 4)
78         return $ Instance numRvrs numProps loadA prefA