{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

module Cardano.Ledger.Shelley.PoolRank
  ( desirability,
    PerformanceEstimate (..),
    NonMyopic (..),
    getTopRankedPools,
    getTopRankedPoolsVMap,
    nonMyopicStake,
    nonMyopicMemberRew,
    percentile',
    Histogram (..),
    LogWeight (..),
    likelihood,
    applyDecay,
    Likelihood (..),
    leaderProbability,
  )
where

import Cardano.Binary
  ( FromCBOR (..),
    ToCBOR (..),
    decodeDouble,
    encodeDouble,
    encodeListLen,
  )
import Cardano.Ledger.BaseTypes
  ( ActiveSlotCoeff,
    BoundedRational (..),
    NonNegativeInterval,
    UnitInterval,
    activeSlotVal,
  )
import Cardano.Ledger.Coin (Coin (..), coinToRational)
import qualified Cardano.Ledger.Crypto as CC (Crypto)
import Cardano.Ledger.Keys (KeyHash, KeyRole (..))
import Cardano.Ledger.Serialization
  ( decodeRecordNamedT,
    decodeSeq,
    encodeFoldable,
  )
import Cardano.Ledger.Shelley.EpochBoundary (maxPool)
import Cardano.Ledger.Shelley.Rewards (StakeShare (..), memberRew)
import Cardano.Ledger.Shelley.TxBody (PoolParams (..))
import Cardano.Slotting.Slot (EpochSize (..))
import Control.DeepSeq (NFData)
import Control.Monad.Trans
import Data.Default.Class (Default, def)
import Data.Foldable (find)
import Data.Function (on)
import Data.List (sortBy)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe)
import Data.Ratio ((%))
import qualified Data.Sequence as Seq
import Data.Sequence.Strict (StrictSeq)
import qualified Data.Sequence.Strict as StrictSeq
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Sharing
import qualified Data.VMap as VMap
import GHC.Generics (Generic)
import GHC.Records (HasField (getField))
import Lens.Micro (_1)
import NoThunks.Class (NoThunks (..))
import Numeric.Natural (Natural)
import Quiet

newtype LogWeight = LogWeight {LogWeight -> Float
unLogWeight :: Float}
  deriving (LogWeight -> LogWeight -> Bool
(LogWeight -> LogWeight -> Bool)
-> (LogWeight -> LogWeight -> Bool) -> Eq LogWeight
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogWeight -> LogWeight -> Bool
$c/= :: LogWeight -> LogWeight -> Bool
== :: LogWeight -> LogWeight -> Bool
$c== :: LogWeight -> LogWeight -> Bool
Eq, (forall x. LogWeight -> Rep LogWeight x)
-> (forall x. Rep LogWeight x -> LogWeight) -> Generic LogWeight
forall x. Rep LogWeight x -> LogWeight
forall x. LogWeight -> Rep LogWeight x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LogWeight x -> LogWeight
$cfrom :: forall x. LogWeight -> Rep LogWeight x
Generic, Eq LogWeight
Eq LogWeight
-> (LogWeight -> LogWeight -> Ordering)
-> (LogWeight -> LogWeight -> Bool)
-> (LogWeight -> LogWeight -> Bool)
-> (LogWeight -> LogWeight -> Bool)
-> (LogWeight -> LogWeight -> Bool)
-> (LogWeight -> LogWeight -> LogWeight)
-> (LogWeight -> LogWeight -> LogWeight)
-> Ord LogWeight
LogWeight -> LogWeight -> Bool
LogWeight -> LogWeight -> Ordering
LogWeight -> LogWeight -> LogWeight
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LogWeight -> LogWeight -> LogWeight
$cmin :: LogWeight -> LogWeight -> LogWeight
max :: LogWeight -> LogWeight -> LogWeight
$cmax :: LogWeight -> LogWeight -> LogWeight
>= :: LogWeight -> LogWeight -> Bool
$c>= :: LogWeight -> LogWeight -> Bool
> :: LogWeight -> LogWeight -> Bool
$c> :: LogWeight -> LogWeight -> Bool
<= :: LogWeight -> LogWeight -> Bool
$c<= :: LogWeight -> LogWeight -> Bool
< :: LogWeight -> LogWeight -> Bool
$c< :: LogWeight -> LogWeight -> Bool
compare :: LogWeight -> LogWeight -> Ordering
$ccompare :: LogWeight -> LogWeight -> Ordering
$cp1Ord :: Eq LogWeight
Ord, Integer -> LogWeight
LogWeight -> LogWeight
LogWeight -> LogWeight -> LogWeight
(LogWeight -> LogWeight -> LogWeight)
-> (LogWeight -> LogWeight -> LogWeight)
-> (LogWeight -> LogWeight -> LogWeight)
-> (LogWeight -> LogWeight)
-> (LogWeight -> LogWeight)
-> (LogWeight -> LogWeight)
-> (Integer -> LogWeight)
-> Num LogWeight
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> LogWeight
$cfromInteger :: Integer -> LogWeight
signum :: LogWeight -> LogWeight
$csignum :: LogWeight -> LogWeight
abs :: LogWeight -> LogWeight
$cabs :: LogWeight -> LogWeight
negate :: LogWeight -> LogWeight
$cnegate :: LogWeight -> LogWeight
* :: LogWeight -> LogWeight -> LogWeight
$c* :: LogWeight -> LogWeight -> LogWeight
- :: LogWeight -> LogWeight -> LogWeight
$c- :: LogWeight -> LogWeight -> LogWeight
+ :: LogWeight -> LogWeight -> LogWeight
$c+ :: LogWeight -> LogWeight -> LogWeight
Num, LogWeight -> ()
(LogWeight -> ()) -> NFData LogWeight
forall a. (a -> ()) -> NFData a
rnf :: LogWeight -> ()
$crnf :: LogWeight -> ()
NFData, Context -> LogWeight -> IO (Maybe ThunkInfo)
Proxy LogWeight -> String
(Context -> LogWeight -> IO (Maybe ThunkInfo))
-> (Context -> LogWeight -> IO (Maybe ThunkInfo))
-> (Proxy LogWeight -> String)
-> NoThunks LogWeight
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy LogWeight -> String
$cshowTypeOf :: Proxy LogWeight -> String
wNoThunks :: Context -> LogWeight -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> LogWeight -> IO (Maybe ThunkInfo)
noThunks :: Context -> LogWeight -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> LogWeight -> IO (Maybe ThunkInfo)
NoThunks, Typeable LogWeight
Typeable LogWeight
-> (LogWeight -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy LogWeight -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
    -> Proxy [LogWeight] -> Size)
-> ToCBOR LogWeight
LogWeight -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [LogWeight] -> Size
(forall t. ToCBOR t => Proxy t -> Size) -> Proxy LogWeight -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [LogWeight] -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [LogWeight] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy LogWeight -> Size
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy LogWeight -> Size
toCBOR :: LogWeight -> Encoding
$ctoCBOR :: LogWeight -> Encoding
$cp1ToCBOR :: Typeable LogWeight
ToCBOR, Typeable LogWeight
Decoder s LogWeight
Typeable LogWeight
-> (forall s. Decoder s LogWeight)
-> (Proxy LogWeight -> Text)
-> FromCBOR LogWeight
Proxy LogWeight -> Text
forall s. Decoder s LogWeight
forall a.
Typeable a
-> (forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
label :: Proxy LogWeight -> Text
$clabel :: Proxy LogWeight -> Text
fromCBOR :: Decoder s LogWeight
$cfromCBOR :: forall s. Decoder s LogWeight
$cp1FromCBOR :: Typeable LogWeight
FromCBOR)
  deriving (Int -> LogWeight -> ShowS
[LogWeight] -> ShowS
LogWeight -> String
(Int -> LogWeight -> ShowS)
-> (LogWeight -> String)
-> ([LogWeight] -> ShowS)
-> Show LogWeight
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogWeight] -> ShowS
$cshowList :: [LogWeight] -> ShowS
show :: LogWeight -> String
$cshow :: LogWeight -> String
showsPrec :: Int -> LogWeight -> ShowS
$cshowsPrec :: Int -> LogWeight -> ShowS
Show) via Quiet LogWeight

toLogWeight :: Double -> LogWeight
toLogWeight :: Double -> LogWeight
toLogWeight Double
d = Float -> LogWeight
LogWeight (Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Double -> Float) -> Double -> Float
forall a b. (a -> b) -> a -> b
$ Double -> Double
forall a. Floating a => a -> a
log Double
d)

fromLogWeight :: LogWeight -> Double
fromLogWeight :: LogWeight -> Double
fromLogWeight (LogWeight Float
l) = Double -> Double
forall a. Floating a => a -> a
exp (Float -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
l)

newtype Histogram = Histogram {Histogram -> StrictSeq LogWeight
unHistogram :: StrictSeq LogWeight}
  deriving (Histogram -> Histogram -> Bool
(Histogram -> Histogram -> Bool)
-> (Histogram -> Histogram -> Bool) -> Eq Histogram
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Histogram -> Histogram -> Bool
$c/= :: Histogram -> Histogram -> Bool
== :: Histogram -> Histogram -> Bool
$c== :: Histogram -> Histogram -> Bool
Eq, Int -> Histogram -> ShowS
[Histogram] -> ShowS
Histogram -> String
(Int -> Histogram -> ShowS)
-> (Histogram -> String)
-> ([Histogram] -> ShowS)
-> Show Histogram
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Histogram] -> ShowS
$cshowList :: [Histogram] -> ShowS
show :: Histogram -> String
$cshow :: Histogram -> String
showsPrec :: Int -> Histogram -> ShowS
$cshowsPrec :: Int -> Histogram -> ShowS
Show, (forall x. Histogram -> Rep Histogram x)
-> (forall x. Rep Histogram x -> Histogram) -> Generic Histogram
forall x. Rep Histogram x -> Histogram
forall x. Histogram -> Rep Histogram x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Histogram x -> Histogram
$cfrom :: forall x. Histogram -> Rep Histogram x
Generic)

newtype Likelihood = Likelihood {Likelihood -> StrictSeq LogWeight
unLikelihood :: StrictSeq LogWeight}
  -- TODO: replace with small data structure
  deriving (Int -> Likelihood -> ShowS
[Likelihood] -> ShowS
Likelihood -> String
(Int -> Likelihood -> ShowS)
-> (Likelihood -> String)
-> ([Likelihood] -> ShowS)
-> Show Likelihood
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Likelihood] -> ShowS
$cshowList :: [Likelihood] -> ShowS
show :: Likelihood -> String
$cshow :: Likelihood -> String
showsPrec :: Int -> Likelihood -> ShowS
$cshowsPrec :: Int -> Likelihood -> ShowS
Show, Eq Likelihood
Eq Likelihood
-> (Likelihood -> Likelihood -> Ordering)
-> (Likelihood -> Likelihood -> Bool)
-> (Likelihood -> Likelihood -> Bool)
-> (Likelihood -> Likelihood -> Bool)
-> (Likelihood -> Likelihood -> Bool)
-> (Likelihood -> Likelihood -> Likelihood)
-> (Likelihood -> Likelihood -> Likelihood)
-> Ord Likelihood
Likelihood -> Likelihood -> Bool
Likelihood -> Likelihood -> Ordering
Likelihood -> Likelihood -> Likelihood
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Likelihood -> Likelihood -> Likelihood
$cmin :: Likelihood -> Likelihood -> Likelihood
max :: Likelihood -> Likelihood -> Likelihood
$cmax :: Likelihood -> Likelihood -> Likelihood
>= :: Likelihood -> Likelihood -> Bool
$c>= :: Likelihood -> Likelihood -> Bool
> :: Likelihood -> Likelihood -> Bool
$c> :: Likelihood -> Likelihood -> Bool
<= :: Likelihood -> Likelihood -> Bool
$c<= :: Likelihood -> Likelihood -> Bool
< :: Likelihood -> Likelihood -> Bool
$c< :: Likelihood -> Likelihood -> Bool
compare :: Likelihood -> Likelihood -> Ordering
$ccompare :: Likelihood -> Likelihood -> Ordering
$cp1Ord :: Eq Likelihood
Ord, (forall x. Likelihood -> Rep Likelihood x)
-> (forall x. Rep Likelihood x -> Likelihood) -> Generic Likelihood
forall x. Rep Likelihood x -> Likelihood
forall x. Likelihood -> Rep Likelihood x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Likelihood x -> Likelihood
$cfrom :: forall x. Likelihood -> Rep Likelihood x
Generic, Likelihood -> ()
(Likelihood -> ()) -> NFData Likelihood
forall a. (a -> ()) -> NFData a
rnf :: Likelihood -> ()
$crnf :: Likelihood -> ()
NFData)

instance NoThunks Likelihood

instance Eq Likelihood where
  == :: Likelihood -> Likelihood -> Bool
(==) = StrictSeq LogWeight -> StrictSeq LogWeight -> Bool
forall a. Eq a => a -> a -> Bool
(==) (StrictSeq LogWeight -> StrictSeq LogWeight -> Bool)
-> (Likelihood -> StrictSeq LogWeight)
-> Likelihood
-> Likelihood
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Likelihood -> StrictSeq LogWeight
unLikelihood (Likelihood -> StrictSeq LogWeight)
-> (Likelihood -> Likelihood) -> Likelihood -> StrictSeq LogWeight
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Likelihood -> Likelihood
normalizeLikelihood

instance Semigroup Likelihood where
  (Likelihood StrictSeq LogWeight
x) <> :: Likelihood -> Likelihood -> Likelihood
<> (Likelihood StrictSeq LogWeight
y) =
    Likelihood -> Likelihood
normalizeLikelihood (Likelihood -> Likelihood) -> Likelihood -> Likelihood
forall a b. (a -> b) -> a -> b
$ StrictSeq LogWeight -> Likelihood
Likelihood ((LogWeight -> LogWeight -> LogWeight)
-> StrictSeq LogWeight
-> StrictSeq LogWeight
-> StrictSeq LogWeight
forall a b c.
(a -> b -> c) -> StrictSeq a -> StrictSeq b -> StrictSeq c
StrictSeq.zipWith LogWeight -> LogWeight -> LogWeight
forall a. Num a => a -> a -> a
(+) StrictSeq LogWeight
x StrictSeq LogWeight
y)

instance Monoid Likelihood where
  mempty :: Likelihood
mempty = StrictSeq LogWeight -> Likelihood
Likelihood (StrictSeq LogWeight -> Likelihood)
-> StrictSeq LogWeight -> Likelihood
forall a b. (a -> b) -> a -> b
$ Seq LogWeight -> StrictSeq LogWeight
forall a. Seq a -> StrictSeq a
StrictSeq.forceToStrict (Seq LogWeight -> StrictSeq LogWeight)
-> Seq LogWeight -> StrictSeq LogWeight
forall a b. (a -> b) -> a -> b
$ Int -> LogWeight -> Seq LogWeight
forall a. Int -> a -> Seq a
Seq.replicate (StrictSeq Double -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length StrictSeq Double
samplePositions) (Float -> LogWeight
LogWeight Float
0)

normalizeLikelihood :: Likelihood -> Likelihood
normalizeLikelihood :: Likelihood -> Likelihood
normalizeLikelihood (Likelihood StrictSeq LogWeight
xs) = StrictSeq LogWeight -> Likelihood
Likelihood (StrictSeq LogWeight -> Likelihood)
-> StrictSeq LogWeight -> Likelihood
forall a b. (a -> b) -> a -> b
$ (\LogWeight
x -> LogWeight
x LogWeight -> LogWeight -> LogWeight
forall a. Num a => a -> a -> a
- LogWeight
m) (LogWeight -> LogWeight)
-> StrictSeq LogWeight -> StrictSeq LogWeight
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictSeq LogWeight
xs
  where
    m :: LogWeight
m = StrictSeq LogWeight -> LogWeight
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum StrictSeq LogWeight
xs

instance ToCBOR Likelihood where
  toCBOR :: Likelihood -> Encoding
toCBOR (Likelihood StrictSeq LogWeight
logweights) = StrictSeq LogWeight -> Encoding
forall a (f :: * -> *). (ToCBOR a, Foldable f) => f a -> Encoding
encodeFoldable StrictSeq LogWeight
logweights

instance FromCBOR Likelihood where
  fromCBOR :: Decoder s Likelihood
fromCBOR = StrictSeq LogWeight -> Likelihood
Likelihood (StrictSeq LogWeight -> Likelihood)
-> (Seq LogWeight -> StrictSeq LogWeight)
-> Seq LogWeight
-> Likelihood
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq LogWeight -> StrictSeq LogWeight
forall a. Seq a -> StrictSeq a
StrictSeq.forceToStrict (Seq LogWeight -> Likelihood)
-> Decoder s (Seq LogWeight) -> Decoder s Likelihood
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s LogWeight -> Decoder s (Seq LogWeight)
forall s a. Decoder s a -> Decoder s (Seq a)
decodeSeq Decoder s LogWeight
forall a s. FromCBOR a => Decoder s a
fromCBOR

leaderProbability :: ActiveSlotCoeff -> Rational -> UnitInterval -> Double
leaderProbability :: ActiveSlotCoeff -> Rational -> UnitInterval -> Double
leaderProbability ActiveSlotCoeff
activeSlotCoeff Rational
relativeStake UnitInterval
decentralizationParameter =
  (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
asc) Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Double
s) Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
d')
  where
    d' :: Double
d' = Rational -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Rational -> Double)
-> (UnitInterval -> Rational) -> UnitInterval -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitInterval -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational (UnitInterval -> Double) -> UnitInterval -> Double
forall a b. (a -> b) -> a -> b
$ UnitInterval
decentralizationParameter
    asc :: Double
asc = Rational -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Rational -> Double)
-> (ActiveSlotCoeff -> Rational) -> ActiveSlotCoeff -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositiveUnitInterval -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational (PositiveUnitInterval -> Rational)
-> (ActiveSlotCoeff -> PositiveUnitInterval)
-> ActiveSlotCoeff
-> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActiveSlotCoeff -> PositiveUnitInterval
activeSlotVal (ActiveSlotCoeff -> Double) -> ActiveSlotCoeff -> Double
forall a b. (a -> b) -> a -> b
$ ActiveSlotCoeff
activeSlotCoeff
    s :: Double
s = Rational -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Rational
relativeStake

samplePositions :: StrictSeq Double
samplePositions :: StrictSeq Double
samplePositions = (\Double
x -> (Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
0.5) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
100.0) (Double -> Double) -> StrictSeq Double -> StrictSeq Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double] -> StrictSeq Double
forall a. [a] -> StrictSeq a
StrictSeq.fromList [Double
0.0 .. Double
99.0]

likelihood ::
  Natural -> -- number of blocks produced this epoch
  Double -> -- chance we're allowed to produce a block in this slot
  EpochSize ->
  Likelihood
likelihood :: Natural -> Double -> EpochSize -> Likelihood
likelihood Natural
blocks Double
t EpochSize
slotsPerEpoch =
  StrictSeq LogWeight -> Likelihood
Likelihood (StrictSeq LogWeight -> Likelihood)
-> StrictSeq LogWeight -> Likelihood
forall a b. (a -> b) -> a -> b
$
    Double -> LogWeight
sample (Double -> LogWeight) -> StrictSeq Double -> StrictSeq LogWeight
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictSeq Double
samplePositions
  where
    -- The likelihood function L(x) is the probability of observing the data we got
    -- under the assumption that the underlying pool performance is equal to x.
    -- L(x) = C(n,m) * (tx)^n * (1-tx)^m
    -- where
    -- t is the chance we're allowed to produce a block
    -- n is the number of slots in which a block was produced
    -- m is the number of slots in which a block was not produced
    --      (slots per epoch minus n)
    -- C(n,m) is a coefficient that will be irrelevant
    -- Since the likelihood function only matters up to a scalar multiple, we will
    -- will divide out C(n,m) t^n and use the following instead:
    -- L(x) = x^n * (1-tx)^m
    -- We represent this function using 100 sample points, but to avoid very
    -- large exponents, we store the log of the value instead of the value itself.
    -- log(L(x)) = log [ x^n * (1-tx)^m ]
    --           = n * log(x) + m * log(1 - tx)
    -- TODO: worry more about loss of floating point precision
    --
    -- example:
    -- a pool has relative stake of 1 / 1,000,000 (~ 30k ada of 35b ada)
    -- f = active slot coefficient = 1/20
    -- t = 1 - (1-f)^(1/1,000,000)
    n :: Double
n = Natural -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
blocks
    m :: Double
m = EpochSize -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (EpochSize -> Double) -> EpochSize -> Double
forall a b. (a -> b) -> a -> b
$ EpochSize
slotsPerEpoch EpochSize -> EpochSize -> EpochSize
forall a. Num a => a -> a -> a
- Natural -> EpochSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
blocks
    l :: Double -> Double
    l :: Double -> Double
l Double
x = Double
n Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double
forall a. Floating a => a -> a
log Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
m Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double
forall a. Floating a => a -> a
log (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
t Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
x)
    sample :: Double -> LogWeight
sample Double
position = Float -> LogWeight
LogWeight (Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Double -> Float) -> Double -> Float
forall a b. (a -> b) -> a -> b
$ Double -> Double
l Double
position)

-- | Decay previous likelihood
applyDecay :: Float -> Likelihood -> Likelihood
applyDecay :: Float -> Likelihood -> Likelihood
applyDecay Float
decay (Likelihood StrictSeq LogWeight
logWeights) = StrictSeq LogWeight -> Likelihood
Likelihood (StrictSeq LogWeight -> Likelihood)
-> StrictSeq LogWeight -> Likelihood
forall a b. (a -> b) -> a -> b
$ Float -> LogWeight -> LogWeight
mul Float
decay (LogWeight -> LogWeight)
-> StrictSeq LogWeight -> StrictSeq LogWeight
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictSeq LogWeight
logWeights
  where
    mul :: Float -> LogWeight -> LogWeight
mul Float
x (LogWeight Float
f) = Float -> LogWeight
LogWeight (Float
x Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
f)

posteriorDistribution :: Histogram -> Likelihood -> Histogram
posteriorDistribution :: Histogram -> Likelihood -> Histogram
posteriorDistribution (Histogram StrictSeq LogWeight
points) (Likelihood StrictSeq LogWeight
likelihoods) =
  Histogram -> Histogram
normalize (Histogram -> Histogram) -> Histogram -> Histogram
forall a b. (a -> b) -> a -> b
$
    StrictSeq LogWeight -> Histogram
Histogram (StrictSeq LogWeight -> Histogram)
-> StrictSeq LogWeight -> Histogram
forall a b. (a -> b) -> a -> b
$ (LogWeight -> LogWeight -> LogWeight)
-> StrictSeq LogWeight
-> StrictSeq LogWeight
-> StrictSeq LogWeight
forall a b c.
(a -> b -> c) -> StrictSeq a -> StrictSeq b -> StrictSeq c
StrictSeq.zipWith LogWeight -> LogWeight -> LogWeight
forall a. Num a => a -> a -> a
(+) StrictSeq LogWeight
points StrictSeq LogWeight
likelihoods

-- | Normalize the histogram so that the total area is 1
normalize :: Histogram -> Histogram
normalize :: Histogram -> Histogram
normalize (Histogram StrictSeq LogWeight
values) = StrictSeq LogWeight -> Histogram
Histogram (StrictSeq LogWeight -> Histogram)
-> StrictSeq LogWeight -> Histogram
forall a b. (a -> b) -> a -> b
$ (\LogWeight
x -> LogWeight
x LogWeight -> LogWeight -> LogWeight
forall a. Num a => a -> a -> a
- LogWeight
logArea) (LogWeight -> LogWeight)
-> StrictSeq LogWeight -> StrictSeq LogWeight
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictSeq LogWeight
values'
  where
    m :: LogWeight
m = StrictSeq LogWeight -> LogWeight
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum StrictSeq LogWeight
values
    values' :: StrictSeq LogWeight
values' = (\LogWeight
x -> LogWeight
x LogWeight -> LogWeight -> LogWeight
forall a. Num a => a -> a -> a
- LogWeight
m) (LogWeight -> LogWeight)
-> StrictSeq LogWeight -> StrictSeq LogWeight
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictSeq LogWeight
values
    logArea :: LogWeight
logArea = Double -> LogWeight
toLogWeight Double
area
    area :: Double
area = Double -> StrictSeq Double -> Double
forall (f :: * -> *).
(Functor f, Foldable f) =>
Double -> f Double -> Double
reimannSum Double
0.01 (LogWeight -> Double
fromLogWeight (LogWeight -> Double) -> StrictSeq LogWeight -> StrictSeq Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictSeq LogWeight
values')

-- | Calculate the k percentile for this distribution.
-- k is a value between 0 and 1. The 0 percentile is 0 and the 1 percentile is 1
percentile :: Double -> Histogram -> Likelihood -> PerformanceEstimate
percentile :: Double -> Histogram -> Likelihood -> PerformanceEstimate
percentile Double
p Histogram
prior Likelihood
likelihoods =
  Double -> PerformanceEstimate
PerformanceEstimate (Double -> PerformanceEstimate)
-> ((Double, Double) -> Double)
-> (Double, Double)
-> PerformanceEstimate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double, Double) -> Double
forall a b. (a, b) -> a
fst ((Double, Double) -> PerformanceEstimate)
-> (Double, Double) -> PerformanceEstimate
forall a b. (a -> b) -> a -> b
$
    (Double, Double) -> Maybe (Double, Double) -> (Double, Double)
forall a. a -> Maybe a -> a
fromMaybe (Double
1, Double
1) (Maybe (Double, Double) -> (Double, Double))
-> Maybe (Double, Double) -> (Double, Double)
forall a b. (a -> b) -> a -> b
$
      ((Double, Double) -> Bool)
-> Seq (Double, Double) -> Maybe (Double, Double)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\(Double
_x, Double
fx) -> Double
fx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
p) Seq (Double, Double)
cdf
  where
    (Histogram StrictSeq LogWeight
values) = Histogram -> Likelihood -> Histogram
posteriorDistribution Histogram
prior Likelihood
likelihoods
    cdf :: Seq (Double, Double)
cdf =
      Seq Double -> Seq Double -> Seq (Double, Double)
forall a b. Seq a -> Seq b -> Seq (a, b)
Seq.zip
        (StrictSeq Double -> Seq Double
forall a. StrictSeq a -> Seq a
StrictSeq.fromStrict StrictSeq Double
samplePositions)
        (StrictSeq Double -> Seq Double
forall a. StrictSeq a -> Seq a
StrictSeq.fromStrict ((Double -> Double -> Double)
-> Double -> StrictSeq Double -> StrictSeq Double
forall a b. (a -> b -> a) -> a -> StrictSeq b -> StrictSeq a
StrictSeq.scanl Double -> Double -> Double
forall a. Num a => a -> a -> a
(+) Double
0 (LogWeight -> Double
fromLogWeight (LogWeight -> Double) -> StrictSeq LogWeight -> StrictSeq Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictSeq LogWeight
values)))

percentile' :: Likelihood -> PerformanceEstimate
percentile' :: Likelihood -> PerformanceEstimate
percentile' = Double -> Histogram -> Likelihood -> PerformanceEstimate
percentile Double
0.5 Histogram
h
  where
    h :: Histogram
h = Histogram -> Histogram
normalize (Histogram -> Histogram)
-> (StrictSeq LogWeight -> Histogram)
-> StrictSeq LogWeight
-> Histogram
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq LogWeight -> Histogram
Histogram (StrictSeq LogWeight -> Histogram)
-> StrictSeq LogWeight -> Histogram
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double -> LogWeight
forall a. (Real a, Floating a) => a -> a -> a -> LogWeight
logBeta Double
40 Double
1 (Double -> LogWeight) -> StrictSeq Double -> StrictSeq LogWeight
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictSeq Double
samplePositions
    -- Beta(n,m)(x) = C * x^(n-1)*(1-x)^(m-1)
    -- log( Beta(n,m)(x) ) = (n-1) * log x + (m-1) * log (1-x)
    logBeta :: a -> a -> a -> LogWeight
logBeta a
n a
m a
x = Float -> LogWeight
LogWeight (Float -> LogWeight) -> (a -> Float) -> a -> LogWeight
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac (a -> LogWeight) -> a -> LogWeight
forall a b. (a -> b) -> a -> b
$ (a
n a -> a -> a
forall a. Num a => a -> a -> a
- a
1) a -> a -> a
forall a. Num a => a -> a -> a
* a -> a
forall a. Floating a => a -> a
log a
x a -> a -> a
forall a. Num a => a -> a -> a
+ (a
m a -> a -> a
forall a. Num a => a -> a -> a
- a
1) a -> a -> a
forall a. Num a => a -> a -> a
* a -> a
forall a. Floating a => a -> a
log (a
1 a -> a -> a
forall a. Num a => a -> a -> a
- a
x)

reimannSum :: (Functor f, Foldable f) => Double -> f Double -> Double
reimannSum :: Double -> f Double -> Double
reimannSum Double
width f Double
heights = f Double -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (f Double -> Double) -> f Double -> Double
forall a b. (a -> b) -> a -> b
$ (Double -> Double) -> f Double -> f Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Double
width Double -> Double -> Double
forall a. Num a => a -> a -> a
*) f Double
heights

-- | This is a estimate of the proportion of allowed blocks a pool will
-- make in the future. It is used for ranking pools in delegation.
newtype PerformanceEstimate = PerformanceEstimate {PerformanceEstimate -> Double
unPerformanceEstimate :: Double}
  deriving (Int -> PerformanceEstimate -> ShowS
[PerformanceEstimate] -> ShowS
PerformanceEstimate -> String
(Int -> PerformanceEstimate -> ShowS)
-> (PerformanceEstimate -> String)
-> ([PerformanceEstimate] -> ShowS)
-> Show PerformanceEstimate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PerformanceEstimate] -> ShowS
$cshowList :: [PerformanceEstimate] -> ShowS
show :: PerformanceEstimate -> String
$cshow :: PerformanceEstimate -> String
showsPrec :: Int -> PerformanceEstimate -> ShowS
$cshowsPrec :: Int -> PerformanceEstimate -> ShowS
Show, PerformanceEstimate -> PerformanceEstimate -> Bool
(PerformanceEstimate -> PerformanceEstimate -> Bool)
-> (PerformanceEstimate -> PerformanceEstimate -> Bool)
-> Eq PerformanceEstimate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceEstimate -> PerformanceEstimate -> Bool
$c/= :: PerformanceEstimate -> PerformanceEstimate -> Bool
== :: PerformanceEstimate -> PerformanceEstimate -> Bool
$c== :: PerformanceEstimate -> PerformanceEstimate -> Bool
Eq, (forall x. PerformanceEstimate -> Rep PerformanceEstimate x)
-> (forall x. Rep PerformanceEstimate x -> PerformanceEstimate)
-> Generic PerformanceEstimate
forall x. Rep PerformanceEstimate x -> PerformanceEstimate
forall x. PerformanceEstimate -> Rep PerformanceEstimate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PerformanceEstimate x -> PerformanceEstimate
$cfrom :: forall x. PerformanceEstimate -> Rep PerformanceEstimate x
Generic, Context -> PerformanceEstimate -> IO (Maybe ThunkInfo)
Proxy PerformanceEstimate -> String
(Context -> PerformanceEstimate -> IO (Maybe ThunkInfo))
-> (Context -> PerformanceEstimate -> IO (Maybe ThunkInfo))
-> (Proxy PerformanceEstimate -> String)
-> NoThunks PerformanceEstimate
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy PerformanceEstimate -> String
$cshowTypeOf :: Proxy PerformanceEstimate -> String
wNoThunks :: Context -> PerformanceEstimate -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> PerformanceEstimate -> IO (Maybe ThunkInfo)
noThunks :: Context -> PerformanceEstimate -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> PerformanceEstimate -> IO (Maybe ThunkInfo)
NoThunks)

instance ToCBOR PerformanceEstimate where
  toCBOR :: PerformanceEstimate -> Encoding
toCBOR = Double -> Encoding
encodeDouble (Double -> Encoding)
-> (PerformanceEstimate -> Double)
-> PerformanceEstimate
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PerformanceEstimate -> Double
unPerformanceEstimate

instance FromCBOR PerformanceEstimate where
  fromCBOR :: Decoder s PerformanceEstimate
fromCBOR = Double -> PerformanceEstimate
PerformanceEstimate (Double -> PerformanceEstimate)
-> Decoder s Double -> Decoder s PerformanceEstimate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Double
forall s. Decoder s Double
decodeDouble

data NonMyopic crypto = NonMyopic
  { NonMyopic crypto -> Map (KeyHash 'StakePool crypto) Likelihood
likelihoodsNM :: !(Map (KeyHash 'StakePool crypto) Likelihood),
    NonMyopic crypto -> Coin
rewardPotNM :: !Coin
  }
  deriving (Int -> NonMyopic crypto -> ShowS
[NonMyopic crypto] -> ShowS
NonMyopic crypto -> String
(Int -> NonMyopic crypto -> ShowS)
-> (NonMyopic crypto -> String)
-> ([NonMyopic crypto] -> ShowS)
-> Show (NonMyopic crypto)
forall crypto. Int -> NonMyopic crypto -> ShowS
forall crypto. [NonMyopic crypto] -> ShowS
forall crypto. NonMyopic crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonMyopic crypto] -> ShowS
$cshowList :: forall crypto. [NonMyopic crypto] -> ShowS
show :: NonMyopic crypto -> String
$cshow :: forall crypto. NonMyopic crypto -> String
showsPrec :: Int -> NonMyopic crypto -> ShowS
$cshowsPrec :: forall crypto. Int -> NonMyopic crypto -> ShowS
Show, NonMyopic crypto -> NonMyopic crypto -> Bool
(NonMyopic crypto -> NonMyopic crypto -> Bool)
-> (NonMyopic crypto -> NonMyopic crypto -> Bool)
-> Eq (NonMyopic crypto)
forall crypto. NonMyopic crypto -> NonMyopic crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonMyopic crypto -> NonMyopic crypto -> Bool
$c/= :: forall crypto. NonMyopic crypto -> NonMyopic crypto -> Bool
== :: NonMyopic crypto -> NonMyopic crypto -> Bool
$c== :: forall crypto. NonMyopic crypto -> NonMyopic crypto -> Bool
Eq, (forall x. NonMyopic crypto -> Rep (NonMyopic crypto) x)
-> (forall x. Rep (NonMyopic crypto) x -> NonMyopic crypto)
-> Generic (NonMyopic crypto)
forall x. Rep (NonMyopic crypto) x -> NonMyopic crypto
forall x. NonMyopic crypto -> Rep (NonMyopic crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (NonMyopic crypto) x -> NonMyopic crypto
forall crypto x. NonMyopic crypto -> Rep (NonMyopic crypto) x
$cto :: forall crypto x. Rep (NonMyopic crypto) x -> NonMyopic crypto
$cfrom :: forall crypto x. NonMyopic crypto -> Rep (NonMyopic crypto) x
Generic)

instance Default (NonMyopic crypto) where
  def :: NonMyopic crypto
def = Map (KeyHash 'StakePool crypto) Likelihood
-> Coin -> NonMyopic crypto
forall crypto.
Map (KeyHash 'StakePool crypto) Likelihood
-> Coin -> NonMyopic crypto
NonMyopic Map (KeyHash 'StakePool crypto) Likelihood
forall k a. Map k a
Map.empty (Integer -> Coin
Coin Integer
0)

instance NoThunks (NonMyopic crypto)

instance NFData (NonMyopic crypto)

instance CC.Crypto crypto => ToCBOR (NonMyopic crypto) where
  toCBOR :: NonMyopic crypto -> Encoding
toCBOR
    NonMyopic
      { likelihoodsNM :: forall crypto.
NonMyopic crypto -> Map (KeyHash 'StakePool crypto) Likelihood
likelihoodsNM = Map (KeyHash 'StakePool crypto) Likelihood
aps,
        rewardPotNM :: forall crypto. NonMyopic crypto -> Coin
rewardPotNM = Coin
rp
      } =
      Word -> Encoding
encodeListLen Word
2
        Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Map (KeyHash 'StakePool crypto) Likelihood -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Map (KeyHash 'StakePool crypto) Likelihood
aps
        Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Coin -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Coin
rp

instance CC.Crypto crypto => FromSharedCBOR (NonMyopic crypto) where
  type Share (NonMyopic crypto) = Interns (KeyHash 'StakePool crypto)
  fromSharedPlusCBOR :: StateT (Share (NonMyopic crypto)) (Decoder s) (NonMyopic crypto)
fromSharedPlusCBOR = do
    Text
-> (NonMyopic crypto -> Int)
-> StateT
     (Interns (KeyHash 'StakePool crypto))
     (Decoder s)
     (NonMyopic crypto)
-> StateT
     (Interns (KeyHash 'StakePool crypto))
     (Decoder s)
     (NonMyopic crypto)
forall (m :: (* -> *) -> * -> *) s a.
(MonadTrans m, Monad (m (Decoder s))) =>
Text -> (a -> Int) -> m (Decoder s) a -> m (Decoder s) a
decodeRecordNamedT Text
"NonMyopic" (Int -> NonMyopic crypto -> Int
forall a b. a -> b -> a
const Int
2) (StateT
   (Interns (KeyHash 'StakePool crypto))
   (Decoder s)
   (NonMyopic crypto)
 -> StateT
      (Interns (KeyHash 'StakePool crypto))
      (Decoder s)
      (NonMyopic crypto))
-> StateT
     (Interns (KeyHash 'StakePool crypto))
     (Decoder s)
     (NonMyopic crypto)
-> StateT
     (Interns (KeyHash 'StakePool crypto))
     (Decoder s)
     (NonMyopic crypto)
forall a b. (a -> b) -> a -> b
$ do
      Map (KeyHash 'StakePool crypto) Likelihood
likelihoodsNM <- Lens'
  (Interns (KeyHash 'StakePool crypto))
  (Share (Map (KeyHash 'StakePool crypto) Likelihood))
-> StateT
     (Interns (KeyHash 'StakePool crypto))
     (Decoder s)
     (Map (KeyHash 'StakePool crypto) Likelihood)
forall b bs s.
FromSharedCBOR b =>
Lens' bs (Share b) -> StateT bs (Decoder s) b
fromSharedPlusLensCBOR (Lens'
  (Interns (KeyHash 'StakePool crypto), Interns Likelihood)
  (Interns (KeyHash 'StakePool crypto))
-> Lens'
     (Interns (KeyHash 'StakePool crypto))
     (Interns (KeyHash 'StakePool crypto))
-> Lens'
     (Interns (KeyHash 'StakePool crypto))
     (Interns (KeyHash 'StakePool crypto), Interns Likelihood)
forall a b c. Monoid a => Lens' a b -> Lens' c b -> Lens' c a
toMemptyLens forall s t a b. Field1 s t a b => Lens s t a b
Lens'
  (Interns (KeyHash 'StakePool crypto), Interns Likelihood)
  (Interns (KeyHash 'StakePool crypto))
_1 forall a. a -> a
Lens'
  (Interns (KeyHash 'StakePool crypto))
  (Interns (KeyHash 'StakePool crypto))
id)
      Coin
rewardPotNM <- Decoder s Coin
-> StateT (Interns (KeyHash 'StakePool crypto)) (Decoder s) Coin
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s Coin
forall a s. FromCBOR a => Decoder s a
fromCBOR
      NonMyopic crypto
-> StateT
     (Interns (KeyHash 'StakePool crypto))
     (Decoder s)
     (NonMyopic crypto)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NonMyopic crypto
 -> StateT
      (Interns (KeyHash 'StakePool crypto))
      (Decoder s)
      (NonMyopic crypto))
-> NonMyopic crypto
-> StateT
     (Interns (KeyHash 'StakePool crypto))
     (Decoder s)
     (NonMyopic crypto)
forall a b. (a -> b) -> a -> b
$ NonMyopic :: forall crypto.
Map (KeyHash 'StakePool crypto) Likelihood
-> Coin -> NonMyopic crypto
NonMyopic {Map (KeyHash 'StakePool crypto) Likelihood
likelihoodsNM :: Map (KeyHash 'StakePool crypto) Likelihood
likelihoodsNM :: Map (KeyHash 'StakePool crypto) Likelihood
likelihoodsNM, Coin
rewardPotNM :: Coin
rewardPotNM :: Coin
rewardPotNM}

-- | Desirability calculation for non-myopic utility,
-- corresponding to f^~ in section 5.6.1 of
-- "Design Specification for Delegation and Incentives in Cardano"
desirability ::
  (NonNegativeInterval, Natural) ->
  Coin ->
  PoolParams c ->
  PerformanceEstimate ->
  Coin ->
  Double
desirability :: (NonNegativeInterval, Natural)
-> Coin -> PoolParams c -> PerformanceEstimate -> Coin -> Double
desirability (NonNegativeInterval
a0, Natural
nOpt) Coin
r PoolParams c
pool (PerformanceEstimate Double
p) (Coin Integer
totalStake) =
  if Double
fTilde Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
cost
    then Double
0
    else (Double
fTilde Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
cost) Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
margin)
  where
    fTilde :: Double
fTilde = Double
fTildeNumer Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
fTildeDenom
    fTildeNumer :: Double
fTildeNumer = Double
p Double -> Double -> Double
forall a. Num a => a -> a -> a
* Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Coin -> Rational
coinToRational Coin
r Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* (Rational
z0 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Rational -> Rational -> Rational
forall a. Ord a => a -> a -> a
min Rational
s Rational
z0 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* NonNegativeInterval -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational NonNegativeInterval
a0))
    fTildeDenom :: Double
fTildeDenom = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double) -> Rational -> Double
forall a b. (a -> b) -> a -> b
$ Rational
1 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ NonNegativeInterval -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational NonNegativeInterval
a0
    cost :: Double
cost = (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double)
-> (PoolParams c -> Rational) -> PoolParams c -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coin -> Rational
coinToRational (Coin -> Rational)
-> (PoolParams c -> Coin) -> PoolParams c -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PoolParams c -> Coin
forall crypto. PoolParams crypto -> Coin
_poolCost) PoolParams c
pool
    margin :: Double
margin = (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double)
-> (PoolParams c -> Rational) -> PoolParams c -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitInterval -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational (UnitInterval -> Rational)
-> (PoolParams c -> UnitInterval) -> PoolParams c -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PoolParams c -> UnitInterval
forall crypto. PoolParams crypto -> UnitInterval
_poolMargin) PoolParams c
pool
    tot :: Integer
tot = Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
max Integer
1 (Integer -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
totalStake)
    Coin Integer
pledge = PoolParams c -> Coin
forall crypto. PoolParams crypto -> Coin
_poolPledge PoolParams c
pool
    s :: Rational
s = Integer -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
pledge Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
tot
    z0 :: Rational
z0 = Integer
1 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
max Integer
1 (Natural -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
nOpt)

-- | Computes the top ranked stake pools
-- corresponding to section 5.6.1 of
-- "Design Specification for Delegation and Incentives in Cardano"
getTopRankedPools ::
  (HasField "_a0" pp NonNegativeInterval, HasField "_nOpt" pp Natural) =>
  Coin ->
  Coin ->
  pp ->
  Map (KeyHash 'StakePool crypto) (PoolParams crypto) ->
  Map (KeyHash 'StakePool crypto) PerformanceEstimate ->
  Set (KeyHash 'StakePool crypto)
getTopRankedPools :: Coin
-> Coin
-> pp
-> Map (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Map (KeyHash 'StakePool crypto) PerformanceEstimate
-> Set (KeyHash 'StakePool crypto)
getTopRankedPools Coin
rPot Coin
totalStake pp
pp Map (KeyHash 'StakePool crypto) (PoolParams crypto)
poolParams Map (KeyHash 'StakePool crypto) PerformanceEstimate
aps =
  let pdata :: [(KeyHash 'StakePool crypto,
  (PoolParams crypto, PerformanceEstimate))]
pdata = Map
  (KeyHash 'StakePool crypto)
  (PoolParams crypto, PerformanceEstimate)
-> [(KeyHash 'StakePool crypto,
     (PoolParams crypto, PerformanceEstimate))]
forall k a. Map k a -> [(k, a)]
Map.toAscList (Map
   (KeyHash 'StakePool crypto)
   (PoolParams crypto, PerformanceEstimate)
 -> [(KeyHash 'StakePool crypto,
      (PoolParams crypto, PerformanceEstimate))])
-> Map
     (KeyHash 'StakePool crypto)
     (PoolParams crypto, PerformanceEstimate)
-> [(KeyHash 'StakePool crypto,
     (PoolParams crypto, PerformanceEstimate))]
forall a b. (a -> b) -> a -> b
$ (PoolParams crypto
 -> PerformanceEstimate -> (PoolParams crypto, PerformanceEstimate))
-> Map (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Map (KeyHash 'StakePool crypto) PerformanceEstimate
-> Map
     (KeyHash 'StakePool crypto)
     (PoolParams crypto, PerformanceEstimate)
forall k a b c.
Ord k =>
(a -> b -> c) -> Map k a -> Map k b -> Map k c
Map.intersectionWith (,) Map (KeyHash 'StakePool crypto) (PoolParams crypto)
poolParams Map (KeyHash 'StakePool crypto) PerformanceEstimate
aps
   in Coin
-> Coin
-> pp
-> [(KeyHash 'StakePool crypto,
     (PoolParams crypto, PerformanceEstimate))]
-> Set (KeyHash 'StakePool crypto)
forall pp crypto.
(HasField "_a0" pp NonNegativeInterval,
 HasField "_nOpt" pp Natural) =>
Coin
-> Coin
-> pp
-> [(KeyHash 'StakePool crypto,
     (PoolParams crypto, PerformanceEstimate))]
-> Set (KeyHash 'StakePool crypto)
getTopRankedPoolsInternal Coin
rPot Coin
totalStake pp
pp [(KeyHash 'StakePool crypto,
  (PoolParams crypto, PerformanceEstimate))]
pdata

getTopRankedPoolsVMap ::
  (HasField "_a0" pp NonNegativeInterval, HasField "_nOpt" pp Natural) =>
  Coin ->
  Coin ->
  pp ->
  VMap.VMap VMap.VB VMap.VB (KeyHash 'StakePool crypto) (PoolParams crypto) ->
  Map (KeyHash 'StakePool crypto) PerformanceEstimate ->
  Set (KeyHash 'StakePool crypto)
getTopRankedPoolsVMap :: Coin
-> Coin
-> pp
-> VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Map (KeyHash 'StakePool crypto) PerformanceEstimate
-> Set (KeyHash 'StakePool crypto)
getTopRankedPoolsVMap Coin
rPot Coin
totalStake pp
pp VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
poolParams Map (KeyHash 'StakePool crypto) PerformanceEstimate
aps =
  let pdata :: [(KeyHash 'StakePool crypto,
  (PoolParams crypto, PerformanceEstimate))]
pdata = [(KeyHash 'StakePool crypto
kh, (PoolParams crypto
pps, PerformanceEstimate
a)) | (KeyHash 'StakePool crypto
kh, PerformanceEstimate
a) <- Map (KeyHash 'StakePool crypto) PerformanceEstimate
-> [(KeyHash 'StakePool crypto, PerformanceEstimate)]
forall k a. Map k a -> [(k, a)]
Map.toAscList Map (KeyHash 'StakePool crypto) PerformanceEstimate
aps, Just PoolParams crypto
pps <- [KeyHash 'StakePool crypto
-> VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Maybe (PoolParams crypto)
forall k (kv :: * -> *) (vv :: * -> *) v.
(Ord k, Vector kv k, Vector vv v) =>
k -> VMap kv vv k v -> Maybe v
VMap.lookup KeyHash 'StakePool crypto
kh VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
poolParams]]
   in Coin
-> Coin
-> pp
-> [(KeyHash 'StakePool crypto,
     (PoolParams crypto, PerformanceEstimate))]
-> Set (KeyHash 'StakePool crypto)
forall pp crypto.
(HasField "_a0" pp NonNegativeInterval,
 HasField "_nOpt" pp Natural) =>
Coin
-> Coin
-> pp
-> [(KeyHash 'StakePool crypto,
     (PoolParams crypto, PerformanceEstimate))]
-> Set (KeyHash 'StakePool crypto)
getTopRankedPoolsInternal Coin
rPot Coin
totalStake pp
pp [(KeyHash 'StakePool crypto,
  (PoolParams crypto, PerformanceEstimate))]
pdata

getTopRankedPoolsInternal ::
  (HasField "_a0" pp NonNegativeInterval, HasField "_nOpt" pp Natural) =>
  Coin ->
  Coin ->
  pp ->
  [(KeyHash 'StakePool crypto, (PoolParams crypto, PerformanceEstimate))] ->
  Set (KeyHash 'StakePool crypto)
getTopRankedPoolsInternal :: Coin
-> Coin
-> pp
-> [(KeyHash 'StakePool crypto,
     (PoolParams crypto, PerformanceEstimate))]
-> Set (KeyHash 'StakePool crypto)
getTopRankedPoolsInternal Coin
rPot Coin
totalStake pp
pp [(KeyHash 'StakePool crypto,
  (PoolParams crypto, PerformanceEstimate))]
pdata =
  [KeyHash 'StakePool crypto] -> Set (KeyHash 'StakePool crypto)
forall a. Ord a => [a] -> Set a
Set.fromList ([KeyHash 'StakePool crypto] -> Set (KeyHash 'StakePool crypto))
-> [KeyHash 'StakePool crypto] -> Set (KeyHash 'StakePool crypto)
forall a b. (a -> b) -> a -> b
$
    (KeyHash 'StakePool crypto, Double) -> KeyHash 'StakePool crypto
forall a b. (a, b) -> a
fst
      ((KeyHash 'StakePool crypto, Double) -> KeyHash 'StakePool crypto)
-> [(KeyHash 'StakePool crypto, Double)]
-> [KeyHash 'StakePool crypto]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int
-> [(KeyHash 'StakePool crypto, Double)]
-> [(KeyHash 'StakePool crypto, Double)]
forall a. Int -> [a] -> [a]
take (Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Natural -> Int) -> Natural -> Int
forall a b. (a -> b) -> a -> b
$ pp -> Natural
forall k (x :: k) r a. HasField x r a => r -> a
getField @"_nOpt" pp
pp) (((KeyHash 'StakePool crypto, Double)
 -> (KeyHash 'StakePool crypto, Double) -> Ordering)
-> [(KeyHash 'StakePool crypto, Double)]
-> [(KeyHash 'StakePool crypto, Double)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((Double -> Double -> Ordering) -> Double -> Double -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Double -> Double -> Ordering)
-> ((KeyHash 'StakePool crypto, Double) -> Double)
-> (KeyHash 'StakePool crypto, Double)
-> (KeyHash 'StakePool crypto, Double)
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (KeyHash 'StakePool crypto, Double) -> Double
forall a b. (a, b) -> b
snd) [(KeyHash 'StakePool crypto, Double)]
rankings)
  where
    rankings :: [(KeyHash 'StakePool crypto, Double)]
rankings =
      [ ( KeyHash 'StakePool crypto
hk,
          (NonNegativeInterval, Natural)
-> Coin
-> PoolParams crypto
-> PerformanceEstimate
-> Coin
-> Double
forall c.
(NonNegativeInterval, Natural)
-> Coin -> PoolParams c -> PerformanceEstimate -> Coin -> Double
desirability (pp -> NonNegativeInterval
forall k (x :: k) r a. HasField x r a => r -> a
getField @"_a0" pp
pp, pp -> Natural
forall k (x :: k) r a. HasField x r a => r -> a
getField @"_nOpt" pp
pp) Coin
rPot PoolParams crypto
pool PerformanceEstimate
ap Coin
totalStake
        )
        | (KeyHash 'StakePool crypto
hk, (PoolParams crypto
pool, PerformanceEstimate
ap)) <- [(KeyHash 'StakePool crypto,
  (PoolParams crypto, PerformanceEstimate))]
pdata
      ]

-- | Compute the Non-Myopic Pool Stake
--
--   This function implements non-myopic stake calculation in section 5.6.2
--   of "Design Specification for Delegation and Incentives in Cardano".
--   Note that the protocol parameters are implicit in the design document.
--   Additionally, instead of passing a rank r to compare with k,
--   we pass the top k desirable pools and check for membership.
nonMyopicStake ::
  HasField "_nOpt" pp Natural =>
  pp ->
  StakeShare ->
  StakeShare ->
  StakeShare ->
  KeyHash 'StakePool c ->
  Set (KeyHash 'StakePool c) ->
  StakeShare
nonMyopicStake :: pp
-> StakeShare
-> StakeShare
-> StakeShare
-> KeyHash 'StakePool c
-> Set (KeyHash 'StakePool c)
-> StakeShare
nonMyopicStake pp
pp (StakeShare Rational
s) (StakeShare Rational
sigma) (StakeShare Rational
t) KeyHash 'StakePool c
kh Set (KeyHash 'StakePool c)
topPools =
  let z0 :: Rational
z0 = Integer
1 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
max Integer
1 (Natural -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (pp -> Natural
forall k (x :: k) r a. HasField x r a => r -> a
getField @"_nOpt" pp
pp))
   in if KeyHash 'StakePool c
kh KeyHash 'StakePool c -> Set (KeyHash 'StakePool c) -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set (KeyHash 'StakePool c)
topPools
        then Rational -> StakeShare
StakeShare (Rational -> Rational -> Rational
forall a. Ord a => a -> a -> a
max (Rational
sigma Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Rational
t) Rational
z0)
        else Rational -> StakeShare
StakeShare (Rational
s Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Rational
t)

-- | Compute the Non-Myopic Pool Member Reward
--
--   This function implements equation (3) in section 5.6.4
--   of "Design Specification for Delegation and Incentives in Cardano".
--   Note that the protocol parameters and the reward pot are implicit
--   in the design document. Additionally, instead of passing a rank
--   r to compare with k, we pass the top k desirable pools and
--   check for membership.
nonMyopicMemberRew ::
  ( HasField "_a0" pp NonNegativeInterval,
    HasField "_nOpt" pp Natural
  ) =>
  pp ->
  Coin ->
  PoolParams c ->
  StakeShare ->
  StakeShare ->
  StakeShare ->
  Set (KeyHash 'StakePool c) ->
  PerformanceEstimate ->
  Coin
nonMyopicMemberRew :: pp
-> Coin
-> PoolParams c
-> StakeShare
-> StakeShare
-> StakeShare
-> Set (KeyHash 'StakePool c)
-> PerformanceEstimate
-> Coin
nonMyopicMemberRew
  pp
pp
  Coin
rPot
  PoolParams c
pool
  StakeShare
s
  StakeShare
sigma
  StakeShare
t
  Set (KeyHash 'StakePool c)
topPools
  (PerformanceEstimate Double
p) =
    let nm :: StakeShare
nm = pp
-> StakeShare
-> StakeShare
-> StakeShare
-> KeyHash 'StakePool c
-> Set (KeyHash 'StakePool c)
-> StakeShare
forall pp c.
HasField "_nOpt" pp Natural =>
pp
-> StakeShare
-> StakeShare
-> StakeShare
-> KeyHash 'StakePool c
-> Set (KeyHash 'StakePool c)
-> StakeShare
nonMyopicStake pp
pp StakeShare
s StakeShare
sigma StakeShare
t (PoolParams c -> KeyHash 'StakePool c
forall crypto. PoolParams crypto -> KeyHash 'StakePool crypto
_poolId PoolParams c
pool) Set (KeyHash 'StakePool c)
topPools
        f :: Coin
f = pp -> Coin -> Rational -> Rational -> Coin
forall pp.
(HasField "_a0" pp NonNegativeInterval,
 HasField "_nOpt" pp Natural) =>
pp -> Coin -> Rational -> Rational -> Coin
maxPool pp
pp Coin
rPot (StakeShare -> Rational
unStakeShare StakeShare
nm) (StakeShare -> Rational
unStakeShare StakeShare
s)
        fHat :: Integer
fHat = Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor (Double
p Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double) -> (Coin -> Rational) -> Coin -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coin -> Rational
coinToRational) Coin
f)
     in Coin -> PoolParams c -> StakeShare -> StakeShare -> Coin
forall crypto.
Coin -> PoolParams crypto -> StakeShare -> StakeShare -> Coin
memberRew (Integer -> Coin
Coin Integer
fHat) PoolParams c
pool StakeShare
t StakeShare
nm