module Game.LambdaHack.Core.Random
(
Rnd
, randomR, random, oneOf, shuffle, frequency
, Chance, chance
, castDice, oddsDice, castDiceXY
, foldrM, foldlM'
#ifdef EXPOSE_INTERNAL
, rollFreq
#endif
) where
import Prelude ()
import Game.LambdaHack.Core.Prelude
import qualified Control.Monad.Trans.State.Strict as St
import Data.Ratio
import qualified System.Random as R
import qualified Game.LambdaHack.Core.Dice as Dice
import Game.LambdaHack.Core.Frequency
type Rnd a = St.State R.StdGen a
randomR :: (R.Random a) => (a, a) -> Rnd a
{-# INLINE randomR #-}
randomR = St.state . R.randomR
random :: (R.Random a) => Rnd a
{-# INLINE random #-}
random = St.state R.random
oneOf :: [a] -> Rnd a
oneOf [] = error $ "oneOf []" `showFailure` ()
oneOf [x] = return x
oneOf xs = do
r <- randomR (0, length xs - 1)
return $! xs !! r
shuffle :: Eq a => [a] -> Rnd [a]
shuffle [] = return []
shuffle l = do
x <- oneOf l
(x :) <$> shuffle (delete x l)
frequency :: Show a => Frequency a -> Rnd a
{-# INLINE frequency #-}
frequency = St.state . rollFreq
rollFreq :: Show a => Frequency a -> R.StdGen -> (a, R.StdGen)
rollFreq fr g = case runFrequency fr of
[] -> error $ "choice from an empty frequency"
`showFailure` nameFrequency fr
[(n, x)] | n <= 0 -> error $ "singleton void frequency"
`showFailure` (nameFrequency fr, n, x)
[(_, x)] -> (x, g)
fs -> let sumf = foldl' (\ !acc (!n, _) -> acc + n) 0 fs
(r, ng) = R.randomR (1, sumf) g
frec :: Int -> [(Int, a)] -> a
frec !m [] = error $ "impossible roll"
`showFailure` (nameFrequency fr, fs, m)
frec m ((n, x) : _) | m <= n = x
frec m ((n, _) : xs) = frec (m - n) xs
in assert (sumf > 0 `blame` "frequency with nothing to pick"
`swith` (nameFrequency fr, fs))
(frec r fs, ng)
type Chance = Rational
chance :: Chance -> Rnd Bool
chance r = do
let n = numerator r
d = denominator r
k <- randomR (1, d)
return (k <= n)
castDice :: Dice.AbsDepth -> Dice.AbsDepth -> Dice.Dice -> Rnd Int
castDice = Dice.castDice randomR
oddsDice :: Dice.AbsDepth -> Dice.AbsDepth -> Dice.Dice -> Rnd Bool
oddsDice ldepth totalDepth dice = do
c <- castDice ldepth totalDepth dice
return $! c > 50
castDiceXY :: Dice.AbsDepth -> Dice.AbsDepth -> Dice.DiceXY -> Rnd (Int, Int)
castDiceXY ldepth totalDepth (Dice.DiceXY dx dy) = do
x <- castDice ldepth totalDepth dx
y <- castDice ldepth totalDepth dy
return (x, y)
foldrM :: Foldable t => (a -> b -> Rnd b) -> b -> t a -> Rnd b
foldrM f z0 xs = let f' x (z, g) = St.runState (f x z) g
in St.state $ \g -> foldr f' (z0, g) xs
foldlM' :: Foldable t => (b -> a -> Rnd b) -> b -> t a -> Rnd b
foldlM' f z0 xs = let f' (z, g) x = St.runState (f z x) g
in St.state $ \g -> foldl' f' (z0, g) xs