Skip to content

Instantly share code, notes, and snippets.

@cherryblossom000
Last active August 9, 2021 08:02
Show Gist options
  • Save cherryblossom000/c025fa8cca86f5a9fc1ca2046d82e437 to your computer and use it in GitHub Desktop.
Save cherryblossom000/c025fa8cca86f5a9fc1ca2046d82e437 to your computer and use it in GitHub Desktop.
module Main where
import Control.Arrow ((&&&))
import Data.List (group, sort)
import Text.Printf (printf)
type EnchantmentLevel = Int
levelProbs :: [(EnchantmentLevel, Double)]
levelProbs = (head &&& (/total) . fromIntegral . length)
<$> group (sort combs)
where
combs = [b + r1 + r2 + 1 | b <- [5..19], r1 <- [0..2], r2 <- [0..2]]
total = fromIntegral $ length combs
bonusCdf :: Double -> Double -> Double
bonusCdf a b = f b - f a
where
-- https://en.wikipedia.org/wiki/Irwin%E2%80%93Hall_distribution#Special_cases (n = 2)
-- ∫(x if 0 <= x < 1, 2-x if 1 <= x <= 2, 0 otherwise)dx = ∫(1-|x-1| if 0 <= x <= 2, 0 otherwise)dx
f x | x <= 0 = 0
f x | x < 2 = -(x - 1) * abs (x - 1) / 2 + x - 0.5
f _ = 1
finalLevelProbs :: [(EnchantmentLevel, Double)]
finalLevelProbs =
(\l2 ->
( l2
, sum
$ (\(l1, p) -> p * bonusProb (fromIntegral l1) (fromIntegral l2))
<$> levelProbs
)
)
<$> [24..65]
where
-- undo the stuff done to the randomFloat() + randomFloat() for the bonus
f x = (x - 1) / 0.15 + 1
-- The final probability gets rounded, so the value before rounding ∈ [final level - 0.5, final level + 0.5)
bonusProb base final = bonusCdf (f ((final - 0.5) / base)) (f ((final + 0.5) / base))
data Enchantment = Sharpness
| Smite
| BaneOfArthropods
| Knockback
| FireAspect
| Looting
| SweepingEdge
| Unbreaking
deriving (Eq, Show)
allEnchantments :: [Enchantment]
allEnchantments =
[ Sharpness
, Smite
, BaneOfArthropods
, Knockback
, FireAspect
, Looting
, SweepingEdge
, Unbreaking
]
weight :: Enchantment -> Int
weight Sharpness = 10
weight Smite = 5
weight BaneOfArthropods = 5
weight Knockback = 5
weight FireAspect = 2
weight Looting = 2
weight SweepingEdge = 2
weight Unbreaking = 5
conflicts :: Enchantment -> Bool
conflicts Sharpness = True
conflicts Smite = True
conflicts BaneOfArthropods = True
conflicts _ = False
-- | Gets the available enchantments given the enchantments already on the sword.
available :: [Enchantment] -> [Enchantment]
available done = filter
(not . if any conflicts done
then uncurry (||) . ((`elem` done) &&& conflicts)
else (`elem` done)
)
allEnchantments
-- | Calculates the probability of getting sharpness, fire aspect, and looting,
-- given the enchantments that are already on the sword.
pr :: [Enchantment] -> Double -> EnchantmentLevel -> Double
-- This could probably be done a lot more efficiently but whatever it worked
pr done p _ | all (`elem` done) [Sharpness, FireAspect, Looting] = p
pr done p l = case available done of
[] -> 0
avail ->
p * keepGoing * sum
((\e -> pr (e:done) (fromIntegral (weight e) / totalWeights) l')
<$> avail
)
where
totalWeights = fromIntegral . sum $ weight <$> avail
-- whether to try to add another enchantment
keepGoing = (fromIntegral l + 1) / 50
-- half level for next iteration
l' = l `div` 2
result :: Double
result = sum $ (\(l, p) -> p * pr [] 1 l) <$> finalLevelProbs
main :: IO ()
main = printf "%.6f%%\n" $ result * 100
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment