{-# LANGUAGE RecordWildCards #-}
{-|
Module      : Ranking.Glicko.Core
License     : GPL-3
Maintainer  : rasmus@precenth.eu
Stability   : experimental

This module contains the main function, 'compute'. Use this to compute new ratings from
old ones.

>>> let ps = compute [] [Match 1 2 1 0] def
>>> ps
[ Player { playerId = 1
         , playerRating = 1662.3108939062977
         , playerDev = 290.31896371798047
         , playerVol = 5.999967537233814e-2
         , playerInactivity = 0
         , playerAge = 1 }
, Player { playerId = 2
         , playerRating = 1337.6891060937023
         , playerDev = 290.31896371798047
         , playerVol = 5.999967537233814e-2
         , playerInactivity = 0
         , playerAge = 1 }]
>>> compute ps [Match 1 3 0 0] def
[ Player { playerId = 1
         , playerRating = 1623.996484575735
         , playerDev = 256.3451684359266
         , playerVol = 5.999869083062934e-2
         , playerInactivity = 0
         , playerAge = 2 }
, Player { playerId = 2
         , playerRating = 1337.6891060937023
         , playerDev = 290.5060065906196
         , playerVol = 5.999967537233814e-2
         , playerInactivity = 1
         , playerAge = 2 }
, Player { playerId = 3
         , playerRating = 1557.6214863132009
         , playerDev = 286.9272058793522
         , playerVol = 5.999899836136578e-2
         , playerInactivity = 0
         , playerAge = 1 }]
-}
module Ranking.Glicko.Core
       ( compute
       , computeP
       , newToOld
       , oldToNew ) where

import Prelude hiding ((^))
import qualified Prelude as P

import Data.Maybe
import Control.Parallel.Strategies
import Data.Map (Map)
import qualified Data.Map.Strict as Map
import Data.Set (Set)
import qualified Data.Set as Set

import Ranking.Glicko.Types

(^) :: Double -> Integer -> Double
^ :: Double -> Integer -> Double
(^) = Double -> Integer -> Double
forall a b. (Num a, Integral b) => a -> b -> a
(P.^)

-- Run map in parallel
pMap :: NFData b => Int -> (a -> b) -> [a] -> [b]
pMap :: Int -> (a -> b) -> [a] -> [b]
pMap Int
chunkSize a -> b
f = Strategy [b] -> [b] -> [b]
forall a. Strategy a -> a -> a
withStrategy (Int -> Strategy b -> Strategy [b]
forall a. Int -> Strategy a -> Strategy [a]
parListChunk Int
chunkSize Strategy b
forall a. NFData a => Strategy a
rdeepseq) ([b] -> [b]) -> ([a] -> [b]) -> [a] -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map a -> b
f

-- | Computes new ratings from the previous and adds new ones using the
-- specified settings.
compute :: [Player 1]       -- ^ Input players
        -> [Match]          -- ^ Matches played this period
        -> GlickoSettings   -- ^ Settings for computing the score values and adding new
                            -- players.
        -> [Player 1]       -- ^ Updated player ratings
compute :: [Player 1] -> [Match] -> GlickoSettings -> [Player 1]
compute = (((Int, Player 2) -> Player 1) -> [(Int, Player 2)] -> [Player 1])
-> [Player 1] -> [Match] -> GlickoSettings -> [Player 1]
compute' ((Int, Player 2) -> Player 1) -> [(Int, Player 2)] -> [Player 1]
forall a b. (a -> b) -> [a] -> [b]
map

-- | Same as 'compute' but runs in parallel using the specified chunkSize
computeP :: Int -> [Player 1] -> [Match] -> GlickoSettings -> [Player 1]
computeP :: Int -> [Player 1] -> [Match] -> GlickoSettings -> [Player 1]
computeP Int
chunkSize = (((Int, Player 2) -> Player 1) -> [(Int, Player 2)] -> [Player 1])
-> [Player 1] -> [Match] -> GlickoSettings -> [Player 1]
compute' (Int
-> ((Int, Player 2) -> Player 1) -> [(Int, Player 2)] -> [Player 1]
forall b a. NFData b => Int -> (a -> b) -> [a] -> [b]
pMap Int
chunkSize)

-- Update all player ratings
compute' :: (((PlayerId, Player 2) -> Player 1) -> [(PlayerId, Player 2)] -> [Player 1])
         -> [Player 1]
         -> [Match]
         -> GlickoSettings
         -> [Player 1]
compute' :: (((Int, Player 2) -> Player 1) -> [(Int, Player 2)] -> [Player 1])
-> [Player 1] -> [Match] -> GlickoSettings -> [Player 1]
compute' ((Int, Player 2) -> Player 1) -> [(Int, Player 2)] -> [Player 1]
map' [Player 1]
ps [Match]
ms GlickoSettings
settings = ((Int, Player 2) -> Player 1) -> [(Int, Player 2)] -> [Player 1]
map' (Player 2 -> Player 1
newToOld (Player 2 -> Player 1)
-> ((Int, Player 2) -> Player 2) -> (Int, Player 2) -> Player 1
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Player 2 -> Player 2
updater (Player 2 -> Player 2)
-> ((Int, Player 2) -> Player 2) -> (Int, Player 2) -> Player 2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Player 2) -> Player 2
forall a b. (a, b) -> b
snd) ([(Int, Player 2)] -> [Player 1])
-> (Map Int (Player 2) -> [(Int, Player 2)])
-> Map Int (Player 2)
-> [Player 1]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Int (Player 2) -> [(Int, Player 2)]
forall k a. Map k a -> [(k, a)]
Map.toList (Map Int (Player 2) -> [Player 1])
-> Map Int (Player 2) -> [Player 1]
forall a b. (a -> b) -> a -> b
$ Map Int (Player 2)
pmap'
  where pmap :: Map Int (Player 1)
pmap = [(Int, Player 1)] -> Map Int (Player 1)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Int, Player 1)] -> Map Int (Player 1))
-> [(Int, Player 1)] -> Map Int (Player 1)
forall a b. (a -> b) -> a -> b
$ (Player 1 -> (Int, Player 1)) -> [Player 1] -> [(Int, Player 1)]
forall a b. (a -> b) -> [a] -> [b]
map (\Player 1
p -> (Player 1 -> Int
forall (version :: Nat). Player version -> Int
playerId Player 1
p, Player 1
p)) [Player 1]
ps
        pmap' :: Map Int (Player 2)
pmap' = (Player 1 -> Player 2) -> Map Int (Player 1) -> Map Int (Player 2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Player 1 -> Player 2
oldToNew (Map Int (Player 1)
-> [Match] -> GlickoSettings -> Map Int (Player 1)
preprocess Map Int (Player 1)
pmap [Match]
ms GlickoSettings
settings)
        matches :: [RatedMatch]
matches = Map Int (Player 2) -> [Match] -> [RatedMatch]
preprocessMatches Map Int (Player 2)
pmap' [Match]
ms
        updater :: Player 2 -> Player 2
updater Player 2
p = Player 2 -> [RatedMatch] -> GlickoSettings -> Player 2
updatePlayer Player 2
p [RatedMatch]
matches GlickoSettings
settings

-- Compute new rating for player
updatePlayer :: Player 2 -> [RatedMatch] -> GlickoSettings -> Player 2
updatePlayer :: Player 2 -> [RatedMatch] -> GlickoSettings -> Player 2
updatePlayer Player 2
p [RatedMatch]
ms GlickoSettings{ tau :: GlickoSettings -> Double
tau = Double
tau, scoreFunction :: GlickoSettings -> ScoreFunction
scoreFunction = ScoreFunction
scoreFun }
  | [RatedMatch] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [RatedMatch]
matches = Player 2
p { playerDev :: Double
playerDev        = Double -> Double
forall a. Floating a => a -> a
sqrt (Double
Double -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
Double -> Integer -> Double
^Integer
2)
                     , playerInactivity :: Int
playerInactivity = Player 2 -> Int
forall (version :: Nat). Player version -> Int
playerInactivity Player 2
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
                     , playerAge :: Int
playerAge        = Player 2 -> Int
forall (version :: Nat). Player version -> Int
playerAge Player 2
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
  | Bool
otherwise    = Player 2
p { playerDev :: Double
playerDev        = Double
φ'
                     , playerRating :: Double
playerRating     = Double
µ'
                     , playerVol :: Double
playerVol        = Double
σ'
                     , playerInactivity :: Int
playerInactivity = Int
0
                     , playerAge :: Int
playerAge        = Player 2 -> Int
forall (version :: Nat). Player version -> Int
playerAge Player 2
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
  where -- Initial values for player
        pµ :: Double
 = Player 2 -> Double
forall (version :: Nat). Player version -> Double
playerRating Player 2
p
        pφ :: Double
 = Player 2 -> Double
forall (version :: Nat). Player version -> Double
playerDev Player 2
p
        pσ :: Double
 = Player 2 -> Double
forall (version :: Nat). Player version -> Double
playerVol Player 2
p
        -- Values for opponent in match `m`
        µ :: (a, Player version, c, d) -> Double
µ (a
_, Player version
opp, c
_, d
_) = Player version -> Double
forall (version :: Nat). Player version -> Double
playerRating Player version
opp
        φ :: (a, Player version, c, d) -> Double
φ (a
_, Player version
opp, c
_, d
_) = Player version -> Double
forall (version :: Nat). Player version -> Double
playerDev Player version
opp
        -- Score value for match
        s :: RatedMatch -> Double
        s :: RatedMatch -> Double
s (Player 2
_,Player 2
_,Int
sa,Int
sb) = ScoreFunction -> Int -> Int -> Double
compareScores ScoreFunction
scoreFun Int
sa Int
sb
        -- Convenience function for E(µ, µj, φj)
        e :: (a, Player version, c, d) -> Double
e (a, Player version, c, d)
m = Double -> Double -> Double -> Double
_E Double
 ((a, Player version, c, d) -> Double
forall a (version :: Nat) c d. (a, Player version, c, d) -> Double
µ (a, Player version, c, d)
m) ((a, Player version, c, d) -> Double
forall a (version :: Nat) c d. (a, Player version, c, d) -> Double
φ (a, Player version, c, d)
m)
        -- Step 3: v
        v :: Double
v = Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (RatedMatch -> Double) -> Double
summer (\RatedMatch
m -> Double -> Double
_g (RatedMatch -> Double
forall a (version :: Nat) c d. (a, Player version, c, d) -> Double
φ RatedMatch
m)Double -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
* RatedMatch -> Double
forall a (version :: Nat) c d. (a, Player version, c, d) -> Double
e RatedMatch
m Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- RatedMatch -> Double
forall a (version :: Nat) c d. (a, Player version, c, d) -> Double
e RatedMatch
m))
        -- Step 4: ∆
        delta :: Double
delta = Double
v Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
step4sum
        -- Step 5: σ'
        σ' :: Double
σ' = Double -> Double -> Double -> Double -> Double -> Double
calcSigma Double
delta Double
 Double
 Double
v Double
tau
        -- Step 6: φ∗
        φstar :: Double
φstar = Double -> Double
forall a. Floating a => a -> a
sqrt (Double
Double -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
σ'Double -> Integer -> Double
^Integer
2)
        -- Step 7: φ' and µ'
        φ' :: Double
φ' = Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double -> Double
forall a. Floating a => a -> a
sqrt (Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
φstarDouble -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
v)
        µ' :: Double
µ' = Double
 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
φ'Double -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
step4sum

        -- Helper used in both ∆ and µ'
        step4sum :: Double
step4sum = (RatedMatch -> Double) -> Double
summer (\RatedMatch
m -> Double -> Double
_g (RatedMatch -> Double
forall a (version :: Nat) c d. (a, Player version, c, d) -> Double
φ RatedMatch
m) Double -> Double -> Double
forall a. Num a => a -> a -> a
* (RatedMatch -> Double
s RatedMatch
m Double -> Double -> Double
forall a. Num a => a -> a -> a
- RatedMatch -> Double
forall a (version :: Nat) c d. (a, Player version, c, d) -> Double
e RatedMatch
m))
        -- Helper to abstract `Sum from j=1 to m`
        summer :: (RatedMatch -> Double) -> Double
        summer :: (RatedMatch -> Double) -> Double
summer RatedMatch -> Double
f = [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Double] -> Double)
-> ([RatedMatch] -> [Double]) -> [RatedMatch] -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RatedMatch -> Double) -> [RatedMatch] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map RatedMatch -> Double
f ([RatedMatch] -> Double) -> [RatedMatch] -> Double
forall a b. (a -> b) -> a -> b
$ [RatedMatch]
matches

        -- All matches `p` played in, arranged so that `p` is the first player
        matches :: [RatedMatch]
        matches :: [RatedMatch]
matches = (RatedMatch -> RatedMatch) -> [RatedMatch] -> [RatedMatch]
forall a b. (a -> b) -> [a] -> [b]
map RatedMatch -> RatedMatch
swap
                  ([RatedMatch] -> [RatedMatch])
-> ([RatedMatch] -> [RatedMatch]) -> [RatedMatch] -> [RatedMatch]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RatedMatch -> Bool) -> [RatedMatch] -> [RatedMatch]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Player 2
pla, Player 2
plb, Int
_, Int
_) -> Player 2
pla Player 2 -> Player 2 -> Bool
forall a. Eq a => a -> a -> Bool
== Player 2
p Bool -> Bool -> Bool
|| Player 2
plb Player 2 -> Player 2 -> Bool
forall a. Eq a => a -> a -> Bool
== Player 2
p)
                  ([RatedMatch] -> [RatedMatch]) -> [RatedMatch] -> [RatedMatch]
forall a b. (a -> b) -> a -> b
$ [RatedMatch]
ms

        swap :: RatedMatch -> RatedMatch
        swap :: RatedMatch -> RatedMatch
swap m :: RatedMatch
m@(Player 2
pla, Player 2
plb, Int
sca, Int
scb)
         | Player 2
pla Player 2 -> Player 2 -> Bool
forall a. Eq a => a -> a -> Bool
== Player 2
p  = RatedMatch
m
         | Bool
otherwise = (Player 2
plb, Player 2
pla, Int
scb, Int
sca)

type RatedMatch = (Player 2, Player 2, Score, Score)

-- g and E from step 3-4
_g :: Double -> Double
_g :: Double -> Double
_g Double
φ = Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double -> Double
forall a. Floating a => a -> a
sqrt (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
3Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
φDouble -> Integer -> Double
^Integer
2Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/(Double
forall a. Floating a => a
piDouble -> Integer -> Double
^Integer
2))

_E :: Double -> Double -> Double -> Double
_E :: Double -> Double -> Double -> Double
_E Double
µ Double
µj Double
φj = Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double -> Double
forall a. Floating a => a -> a
exp (- Double -> Double
_g Double
φj Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
µ Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
µj)))

-- Computes σ' in step 5
calcSigma :: Double -> Double -> Double -> Double -> Double -> Double
calcSigma :: Double -> Double -> Double -> Double -> Double -> Double
calcSigma Double
delta Double
φ Double
σ Double
v Double
tau = Double -> Double -> Double -> Double -> Double
step Double
a Double
b (Double -> Double
f Double
a) (Double -> Double
f Double
b)
  where step :: Double -> Double -> Double -> Double -> Double
step Double
a' Double
b' Double
fa Double
fb
          | Double -> Double
forall a. Num a => a -> a
abs (Double
b' Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
a') Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
ε = Double -> Double
forall a. Floating a => a -> a
exp (Double
a'Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2)
          | Double
fcDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
fb         Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0  = Double -> Double -> Double -> Double -> Double
step Double
b' Double
c Double
fb     Double
fc
          | Bool
otherwise          = Double -> Double -> Double -> Double -> Double
step Double
a' Double
c (Double
faDouble -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2) Double
fc
          where c :: Double
c = Double
a' Double -> Double -> Double
forall a. Num a => a -> a -> a
+ (Double
a' Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
b') Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
faDouble -> Double -> Double
forall a. Fractional a => a -> a -> a
/(Double
fb Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
fa)
                fc :: Double
fc = Double -> Double
f Double
c
        a :: Double
a = Double -> Double
forall a. Floating a => a -> a
log (Double -> Double) -> Double -> Double
forall a b. (a -> b) -> a -> b
$ Double
σ Double -> Integer -> Double
^ Integer
2
        b :: Double
b = if Double
deltaDouble -> Integer -> Double
^Integer
2 Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
φDouble -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
v then Double -> Double
forall a. Floating a => a -> a
log (Double
deltaDouble -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
φDouble -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
v) else Double -> Double
fixB Double
1
        fixB :: Double -> Double
fixB Double
k = if Double -> Double
f (Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
kDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tau) Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 then Double -> Double
fixB (Double
kDouble -> Double -> Double
forall a. Num a => a -> a -> a
+Double
1) else Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
kDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
tau
        f :: Double -> Double
f Double
x = (Double -> Double
forall a. Floating a => a -> a
exp Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
deltaDouble -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
φDouble -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
v Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double -> Double
forall a. Floating a => a -> a
exp Double
x)) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
φDouble -> Integer -> Double
^Integer
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
v Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double -> Double
forall a. Floating a => a -> a
exp Double
x)Double -> Integer -> Double
^Integer
2) Double -> Double -> Double
forall a. Num a => a -> a -> a
- (Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
a) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
tauDouble -> Integer -> Double
^Integer
2

-- Tolerance used in calcSigma
ε :: Double
ε :: Double
ε = Double
0.000001

-- Add new default players where missing
preprocess :: Map PlayerId (Player 1)
           -> [Match]
           -> GlickoSettings
           -> Map PlayerId (Player 1)
preprocess :: Map Int (Player 1)
-> [Match] -> GlickoSettings -> Map Int (Player 1)
preprocess Map Int (Player 1)
ps [Match]
ms GlickoSettings
settings =
  Map Int (Player 1) -> Map Int (Player 1) -> Map Int (Player 1)
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union Map Int (Player 1)
ps
  (Map Int (Player 1) -> Map Int (Player 1))
-> (Set Int -> Map Int (Player 1)) -> Set Int -> Map Int (Player 1)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Player 1) -> Set Int -> Map Int (Player 1)
forall k a. (k -> a) -> Set k -> Map k a
Map.fromSet (\Int
i -> Player Any
forall (version :: Nat). Player version
defaultPlayer { playerId :: Int
playerId = Int
i })
  (Set Int -> Map Int (Player 1)) -> Set Int -> Map Int (Player 1)
forall a b. (a -> b) -> a -> b
$ Set Int
playersInMatches Set Int -> Set Int -> Set Int
forall a. Ord a => Set a -> Set a -> Set a
`Set.difference` Set Int
players
  where playersInMatches :: Set Int
playersInMatches = [Int] -> Set Int
forall a. Ord a => [a] -> Set a
Set.fromList ([Int] -> Set Int) -> [Int] -> Set Int
forall a b. (a -> b) -> a -> b
$ (\Match
m -> [Match -> Int
matchPlayerA Match
m, Match -> Int
matchPlayerB Match
m]) (Match -> [Int]) -> [Match] -> [Int]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Match]
ms
        players :: Set Int
players = Map Int (Player 1) -> Set Int
forall k a. Map k a -> Set k
Map.keysSet Map Int (Player 1)
ps
        defaultPlayer :: Player version
defaultPlayer = Player :: forall (version :: Nat).
Int -> Double -> Double -> Double -> Int -> Int -> Player version
Player { playerId :: Int
playerId = -Int
1
                               , playerRating :: Double
playerRating = GlickoSettings -> Double
initialRating GlickoSettings
settings
                               , playerDev :: Double
playerDev = GlickoSettings -> Double
initialDeviation GlickoSettings
settings
                               , playerVol :: Double
playerVol = GlickoSettings -> Double
initialVolatility GlickoSettings
settings
                               , playerInactivity :: Int
playerInactivity = Int
0
                               , playerAge :: Int
playerAge = Int
0}


-- Pull the players into the matches
preprocessMatches :: Map PlayerId (Player 2) -> [Match] -> [RatedMatch]
preprocessMatches :: Map Int (Player 2) -> [Match] -> [RatedMatch]
preprocessMatches Map Int (Player 2)
ps = (Match -> Maybe RatedMatch) -> [Match] -> [RatedMatch]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Match -> Maybe RatedMatch
f
  where f :: Match -> Maybe RatedMatch
f Match
m = do
          Player 2
pla <- Int -> Map Int (Player 2) -> Maybe (Player 2)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Match -> Int
matchPlayerA Match
m) Map Int (Player 2)
ps
          Player 2
plb <- Int -> Map Int (Player 2) -> Maybe (Player 2)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Match -> Int
matchPlayerB Match
m) Map Int (Player 2)
ps
          RatedMatch -> Maybe RatedMatch
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Player 2
pla, Player 2
plb, Match -> Int
matchScoreA Match
m, Match -> Int
matchScoreB Match
m)

-- | Convert ratings from Glicko to Glicko-2
oldToNew :: Player 1 -> Player 2
oldToNew :: Player 1 -> Player 2
oldToNew p :: Player 1
p@Player{ playerRating :: forall (version :: Nat). Player version -> Double
playerRating = Double
r, playerDev :: forall (version :: Nat). Player version -> Double
playerDev = Double
d} =
  Player 1
p { playerRating :: Double
playerRating = (Double
r Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
1500) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
glicko2Multiplier
    , playerDev :: Double
playerDev    = Double
d Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
glicko2Multiplier }

-- | Convert ratings from Glicko-2 to Glicko
newToOld :: Player 2 -> Player 1
newToOld :: Player 2 -> Player 1
newToOld p :: Player 2
p@Player{ playerRating :: forall (version :: Nat). Player version -> Double
playerRating = Double
r, playerDev :: forall (version :: Nat). Player version -> Double
playerDev = Double
d} =
  Player 2
p { playerRating :: Double
playerRating = Double
r Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
glicko2Multiplier Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
1500
    , playerDev :: Double
playerDev    = Double
d Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
glicko2Multiplier}

glicko2Multiplier :: Double
glicko2Multiplier :: Double
glicko2Multiplier = Double
173.7178

playersToMap :: [Player v] -> Map PlayerId (Player v)
playersToMap :: [Player v] -> Map Int (Player v)
playersToMap = [(Int, Player v)] -> Map Int (Player v)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Int, Player v)] -> Map Int (Player v))
-> ([Player v] -> [(Int, Player v)])
-> [Player v]
-> Map Int (Player v)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Player v -> (Int, Player v)) -> [Player v] -> [(Int, Player v)]
forall a b. (a -> b) -> [a] -> [b]
map (\Player v
p -> (Player v -> Int
forall (version :: Nat). Player version -> Int
playerId Player v
p, Player v
p))