module Project where studentInput = [["1", "MmcG", "","",""], ["2", "CM", "GE", "", ""], ["3", "BG", "CM", "GE", "JN"], ["4", "JC", "CM", "GE", "JN"], ["5", "GE", "DF", "TC", ""], ["6", "BG", "MH", "MH", "JG"], ["7", "JC", "JN", "JN", "JH"], ["8", "JS", "GE", "CM", "RR"], ["9", "NM", "JS", "AM", "JC"], ["10", "MM", "JC", "TS", "GE"], ["11", "JC", "AM", "DF", "MT"], ["12", "CM", "JN", "JH", "DF"], ["13", "BG", "MM", "CM", "AM"], ["14", "CM", "AM", "DF", "GE"], ["15", "DF", "JC", "CM", "JS"], ["16", "MM", "CM", "BG", "AM"], ["17", "GE", "CM", "DF", "AM"], ["18", "JC", "JS", "CM", "JS"], ["19", "JS", "RR", "DF", "JS"], ["20", "CM", "GE", "RR", "JN"], ["21", "CM", "MM", "GE", "GP"], ["22", "", "", "", ""], ["23", "GE", "AM", "CM", "JC"], ["24", "CT", "CT", "CT", "JS"], ["25", "CT", "JH", "", ""], ["26", "JN", "JH", "JN", "JH"], ["27", "JN", "JH", "JH", "MH"], ["28", "JoC", "JN", "", ""], ["29", "JC", "JN", "JN", "JH"], ["30", "JN", "JS", "JoC", "MH"], ["31", "JN", "MH", "JS", "TH"], ["32", "MH", "JN", "MH", ""], ["33", "MH", "JN", "JH", "DoR"], ["34", "JN", "JN", "JN", "JN"], ["35", "JoC", "JoC", "JoC", "CT"], ["36", "MH", "DoR", "AK", "MH"], ["37", "MH", "CT", "JN", "JH"], ["38", "CT", "", "", ""], ["39", "MH", "", "", "CT"], ["40", "CT", "JN", "MH", ""], ["41", "JN", "JN", "JN", "JH"], ["42", "RR", "JC", "AM", "AM"], ["43", "GE", "", "", ""], ["44", "MH", "MH", "RR", "NM"], ["45", "", "", "", ""], ["46", "RR", "JS", "JC", "GP"], ["47", "JS", "JN", "JN", ""], ["48", "JS", "JN", "JN", "JN"], ["49", "TH", "TH", "TH", "TH"], ["50", "JC", "RR", "RR", ""] ] staffInput = ["GE", "GE", "MmcG", "BG", "RD", "TC", "JB", "JB", "JM", "JM", "CM", "CM", "CM", "NM", "NM", "TS", "MT", "MoC", "AM", "AM", "DF", "DF", "MM", "JW", "JW", "GP", "GP", "CT", "CT", "CT", "JH", "JH", "JoC", "JoC", "JC", "JC", "TH", "TH", "MH", "MH", "DoR", "DoR", "JN", "JN", "AK", "AK", "RR", "RR", "JS", "JS"] --For Staff input there is 50 names but some are repeated since there is --not enough staff to accomdate all the students. The staffInput is given --by their initials numberOfStudents = length studentInput studentName i = (studentInput !! (i-1)) !! 0 staffName i = (staffInput !! (i-1)) firstChoice i = (studentInput !! (i-1)) !! 1 secondChoice i = (studentInput !! (i-1)) !! 2 thirdChoice i = (studentInput !! (i-1)) !! 3 fourthChoice i = (studentInput !! (i-1)) !! 4 initialState i = i --initialstate is the position of the students relative to the staffInput --i.e student 1 will have GE and student 5 would have RD and so on weight(i,j) = if firstChoice i == staffName j then 0 else if secondChoice i == staffName j then 4 else if thirdChoice i == staffName j then 8 else if fourthChoice i == staffName j then 12 else 16 --Each staffName is given a weighting according to the student ranking successor s i = s (i+1) --This is to map it onto the next element let s i = initialstate i position i s = if i== (s 1) then 1 else 1+(position i (successor s)) --Finds position of student relative to the staffInput --Try position 9 initialstate initialstate studentiAssignedToStaff i s = staffName (position i s) --Shows staffName at a certain position stWeight s n = if (n==1) then weight((s 1),((numberOfStudents -n) +1)) else (weight ((s 1), ((numberOfStudents -n) +1))) + (stWeight (successor s) (n-1) ) stateWeight s = stWeight s numberOfStudents --stateWeight is the sum of i=1 to 50 weight(initialstate i, i) or --it can be the transposition of initialstate tr i j x = if (and [i/=x,j/=x]) then x else if (i==x) then j else i myMod k n = if ((mod k n)==0) then n else mod k n myDiv k n = if ((mod k n)==0) then (div k n) -1 else div k n trans k x= tr (1+(myDiv k numberOfStudents)) ((myMod k numberOfStudents)) x --These four lines above transposes two elements in the list i.e our initialstate is --[1,2,...,49,50] it will be continously transposed so get a desirable assignment gFunction s k = if (k==(numberOfStudents*numberOfStudents)) then s else if (stateWeight s)>(stateWeight (s.(trans k))) then (s.(trans k)) else gFunction s (k+1) --gFunction is the state obtained from s by interchanging the ith & jth --enteries of initialstate such that {stateweight initialstate > stateweight transpose initialstate} nextState s = gFunction s 1 --start at initialstate and compute initialstate, gFunction(initialstate), --gFunction(gFunction(initialstate)) etc finalState s = if ((stateWeight s) == (stateWeight (nextState s))) then s else finalState (nextState s) --Output when stateWeight initialstate == stateweight (nextstate initialstate) studentsSupervisor i = studentiAssignedToStaff i (finalState initialState) --Last line outputs what is the particular students supervisor