Last active
September 21, 2024 04:15
-
-
Save Zolomon/10056219 to your computer and use it in GitHub Desktop.
Calculate best rearrange in Discworld MUD.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| module Rearrange where | |
| import Control.Applicative | |
| import Data.List | |
| main :: IO () | |
| main = do | |
| putStrLn $ show (getMaxStats maPo) | |
| data Stats = Stats { str :: Int, | |
| dex :: Int, | |
| con :: Int, | |
| int :: Int, | |
| wis :: Int | |
| } deriving (Show) | |
| data StatDistr = StatDistr {s1 :: Int, | |
| s2 :: Int, | |
| s3 :: Int, | |
| s4 :: Int, | |
| s5 :: Int | |
| } deriving (Show) | |
| -- All possible stats, with the specified constraints, str >= 14, or gpRegen == 3 for example. | |
| stats :: (Stats -> StatDistr) -> [Stats] | |
| stats gpSkill = map (\(s,d,c,i,w) -> Stats { str=s,dex=d,con=c,int=i,wis=w}) $ | |
| filter (\(a, b, c, d, e) -> | |
| a+b+c+d+e == 65 && | |
| (gpRegen Stats {str=a,dex=b,con=c,int=d,wis=e} gpSkill) == 3 && a >= 14) | |
| ( (,,,,) <$> [8..23] <*> [8..23] <*> [8..23] <*> [8..23] <*> [8..23] ) | |
| gpRegen :: Integral b => t -> (t -> StatDistr) -> b | |
| gpRegen stats gpSkill = floor $ sqrt (175 * m(gpSkill stats)) - 10 | |
| -- http://bonuses.irreducible.org/formulas.php | |
| m :: StatDistr -> Float | |
| m (StatDistr { s1=s,s2=d,s3=c,s4=i,s5=w}) = (1.0/9.8) * log((fromIntegral s) * | |
| (fromIntegral d) * | |
| (fromIntegral c) * | |
| (fromIntegral i) * | |
| (fromIntegral w)) - 0.25 | |
| r :: Int -> Int | |
| r levels | |
| | 0 <= levels, levels <= 20 = 5 * levels | |
| | 21 <= levels, levels <= 40 = (floor $ 2.5 * (fromIntegral $ levels-20)) + 100 | |
| | 41 <= levels, levels <= 60 = 1 * (levels-40) + 150 | |
| | 61 <= levels = (floor $ 0.5 * (fromIntegral $ levels-60)) + 170 | |
| bonus :: Int -> StatDistr -> Int | |
| bonus level stats = round $ m stats * (fromIntegral $ r level) | |
| -- Skills to balance stats after | |
| skills :: [(String, Stats -> StatDistr)] | |
| --skills = [("daggers", fiMeDa), ("dodge", fiDeDo), ("shields", faDeSe)] | |
| skills = [("heavy-sword", fiMeHs), ("parry", fiDePa)] | |
| --faDeSe, fiMeDa, fiDeDo :: Stats -> StatDistr | |
| --faDeSe Stats {str=s,dex=d,con=c,int=i,wis=w} = StatDistr {s1=d,s2=d,s3=i,s4=w,s5=w} | |
| --faPo Stats {str=s,dex=d,con=c,int=i,wis=w} = StatDistr {s1=c,s2=i,s3=i,s4=w,s5=w} | |
| fiMeHs Stats {str=s,dex=d,con=c,int=i,wis=w} = StatDistr {s1=c,s2=d,s3=s,s4=s,s5=s} | |
| fiDePa Stats {str=s,dex=d,con=c,int=i,wis=w} = StatDistr {s1=d,s2=d,s3=d,s4=d,s5=s} | |
| --fiMeDa Stats {str=s,dex=d,con=c,int=i,wis=w} = StatDistr {s1=d,s2=d,s3=d,s4=d,s5=s} | |
| --fiDeDo Stats {str=s,dex=d,con=c,int=i,wis=w} = StatDistr {s1=d,s2=d,s3=d,s4=d,s5=w} | |
| --faPo Stats {str=s,dex=d,con=c,int=i,wis=w} = StatDistr {s1=c,s2=i,s3=i,s4=w,s5=w} | |
| maPo Stats {str=s,dex=d,con=c,int=i,wis=w} = StatDistr {s1=i,s2=i,s3=s,s4=w,s5=w} | |
| getBonuses :: [(String, (Stats -> StatDistr))] -> Stats -> ([Int], Stats) | |
| getBonuses skills stats = ( map (\skill -> bonus 800 $ ((snd skill) stats)) skills, stats) | |
| -- Call this to get the best stats for the chosen skills and constraints. | |
| getMaxStats gpSkill = maximumBy (\lhs rhs -> (fst lhs) `compare` (fst rhs)) $ | |
| map (\myStats -> getBonuses skills myStats) (stats gpSkill) |
Author
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
Added so you can easily change which GP skill should be used, maPo for example is currently specified in the main function, but now you can change to fiPo if you want.