Huge dangling commit

This commit is contained in:
Nox Sluijtman 2024-12-01 17:35:24 +01:00
parent 3597b2b7cf
commit c24768c5c6
Signed by: Egg
SSH key fingerprint: SHA256:2sG9X3C7Xvq2svGumz1/k7cm8l4G9+qAtAeugqB4J9M
12 changed files with 118 additions and 40 deletions

View file

@ -2,4 +2,13 @@
## Maps ## Maps
Consider thinking about using the `Data.Map.Map` datatype instead of `[Skill]` and `[Stat]`. Consider thinking about using the `Data.Map.Map` datatype instead of `[Skill]` and `[Stat]`.
## Familiar
Figure out how to implement these fuckers as well
## Rules
hit = d20 + ability mod + proficiency mod
damage = hit dice + ability mod

3
README.md Normal file
View file

@ -0,0 +1,3 @@
# Sheet Parser
A D&D 5e character sheet parser written in Haskell.

View file

@ -1,6 +1,7 @@
module Main where module Main where
import DND.Sheet.Parser import DND.Sheet.Parser
import DND.Sheet.Pretty
import DND.Dice import DND.Dice
testfile :: FilePath testfile :: FilePath
@ -8,7 +9,6 @@ testfile = "./example.json"
main :: IO () main :: IO ()
main = do main = do
createExample testfile
sheet <- parseSheet testfile sheet <- parseSheet testfile
putStrLn $ "wrote example character named \"" ++ getName sheet ++ "\" to: " ++ testfile putStrLn $ "Loaded character named " ++ getName sheet
mapM_ putStrLn . getSkillNames $ sheet print =<< rollCheck 2 Advantage

View file

@ -1 +1 @@
{"feats":[{"featInfo":{"featDescription":"allows you to ride a 'fiets'","featName":"fiets"},"tag":"Roleplay"}],"preamble":{"charClass":"Fighter","charLevel":5,"charName":"Bob","charRace":"Elf","jackOfAllTrades":false},"skills":[{"skillMod":"None","skillName":"Athletics","skillStat":"Strength"},{"skillMod":"None","skillName":"Acrobatics","skillStat":"Dexterity"},{"skillMod":"None","skillName":"Sleight of Hand","skillStat":"Dexterity"},{"skillMod":"None","skillName":"Stealth","skillStat":"Dexterity"},{"skillMod":"None","skillName":"Arcana","skillStat":"Intelligence"},{"skillMod":"None","skillName":"History","skillStat":"Intelligence"},{"skillMod":"None","skillName":"Investigation","skillStat":"Intelligence"},{"skillMod":"None","skillName":"Nature","skillStat":"Intelligence"},{"skillMod":"None","skillName":"Religion","skillStat":"Intelligence"},{"skillMod":"Proficient","skillName":"Animal Handling","skillStat":"Wisdom"},{"skillMod":"Expertise","skillName":"Insight","skillStat":"Wisdom"},{"skillMod":"None","skillName":"Medicine","skillStat":"Wisdom"},{"skillMod":"None","skillName":"Perception","skillStat":"Wisdom"},{"skillMod":"None","skillName":"Survival","skillStat":"Wisdom"},{"skillMod":"None","skillName":"Deception","skillStat":"Charisma"},{"skillMod":"None","skillName":"Intimidation","skillStat":"Charisma"},{"skillMod":"None","skillName":"Performance","skillStat":"Charisma"},{"skillMod":"None","skillName":"Persuasion","skillStat":"Charisma"}],"spells":[{"atHighLevel":"Cast more of the sodding things","attackSave":"Dexterity","castingTime":"3 Minutes","components":["Verbal","Somatic"],"damageEffect":"Fire","description":"Shoots a huge testicle shaped fireball","duration":"Instant","range":50,"school":"Conjuration","spellLevel":3,"spellName":"Firetesticle"}],"stats":[{"proficient":false,"statName":"Strength","statScore":10},{"proficient":false,"statName":"Dexterity","statScore":10},{"proficient":false,"statName":"Constitution","statScore":10},{"proficient":false,"statName":"Intelligence","statScore":10},{"proficient":false,"statName":"Wisdom","statScore":20},{"proficient":false,"statName":"Charisma","statScore":10}],"trivia":{"background":"farmer","bonds":"yay","flaws":"all","ideals":"I me likey fun things","personalityTrait":"none","quirk":"idk"}} {"feats":[{"featInfo":{"featDescription":"allows you to ride a 'fiets'","featName":"fiets"},"tag":"Roleplay"}],"preamble":{"charClass":"Fighter","charLevel":1,"charName":"Bob","charRace":"Elf","jackOfAllTrades":false},"skills":[{"skillMod":"None","skillName":"Athletics","skillStat":"Strength"},{"skillMod":"None","skillName":"Acrobatics","skillStat":"Dexterity"},{"skillMod":"None","skillName":"Sleight of Hand","skillStat":"Dexterity"},{"skillMod":"None","skillName":"Stealth","skillStat":"Dexterity"},{"skillMod":"None","skillName":"Arcana","skillStat":"Intelligence"},{"skillMod":"None","skillName":"History","skillStat":"Intelligence"},{"skillMod":"None","skillName":"Investigation","skillStat":"Intelligence"},{"skillMod":"None","skillName":"Nature","skillStat":"Intelligence"},{"skillMod":"None","skillName":"Religion","skillStat":"Intelligence"},{"skillMod":"Proficient","skillName":"Animal Handling","skillStat":"Wisdom"},{"skillMod":"Expertise","skillName":"Insight","skillStat":"Wisdom"},{"skillMod":"None","skillName":"Medicine","skillStat":"Wisdom"},{"skillMod":"None","skillName":"Perception","skillStat":"Wisdom"},{"skillMod":"None","skillName":"Survival","skillStat":"Wisdom"},{"skillMod":"None","skillName":"Deception","skillStat":"Charisma"},{"skillMod":"None","skillName":"Intimidation","skillStat":"Charisma"},{"skillMod":"None","skillName":"Performance","skillStat":"Charisma"},{"skillMod":"None","skillName":"Persuasion","skillStat":"Charisma"}],"spells":[{"atHighLevel":"Cast more of the sodding things","attackSave":"Dexterity","castingTime":"3 Minutes","components":["Verbal","Somatic"],"damageEffect":"Fire","description":"Shoots a huge testicle shaped fireball","duration":"Instant","range":50,"school":"Conjuration","spellLevel":3,"spellName":"Firetesticle"}],"stats":[{"statName":"Strength","statProf":false,"statScore":10},{"statName":"Dexterity","statProf":false,"statScore":10},{"statName":"Constitution","statProf":false,"statScore":10},{"statName":"Intelligence","statProf":false,"statScore":10},{"statName":"Wisdom","statProf":true,"statScore":20},{"statName":"Charisma","statProf":false,"statScore":10}],"trivia":{"background":"farmer","bonds":"yay","flaws":"all","ideals":"I me likey fun things","personalityTrait":"none","quirk":"idk"}}

View file

@ -9,3 +9,4 @@ import DND.Bob
import DND.Dice import DND.Dice
import DND.Sheet.Content import DND.Sheet.Content
import DND.Sheet.Parser import DND.Sheet.Parser
import DND.Sheet.Pretty

View file

@ -3,14 +3,20 @@ module DND.Bob (bob) where
import DND.Sheet.Content import DND.Sheet.Content
bob :: Character bob :: Character
bob = Character {skills = testSkills, trivia = testTrivia, stats = testStats, spells = Just testSpells, preamble = testPreamble, feats = Just testFeatures} bob = Character { skills = testSkills
, trivia = testTrivia
, stats = testStats
, spells = Just testSpells
, preamble = testPreamble
, feats = Just testFeatures
}
testStats :: [Stat] testStats :: [Stat]
testStats = [strStat, dexStat, conStat, intStat, wisStat, chaStat] testStats = [strStat, dexStat, conStat, intStat, wisStat, chaStat]
testPreamble :: Preamble testPreamble :: Preamble
testPreamble = Preamble testPreamble = Preamble
{ charLevel = 5 { charLevel = 1
, charName = "Bob" , charName = "Bob"
, charRace = "Elf" , charRace = "Elf"
, charClass = "Fighter" , charClass = "Fighter"
@ -50,7 +56,7 @@ intSkills = [ Skill "Arcana" None "Intelligence"
] ]
wisStat :: Stat wisStat :: Stat
wisStat = Stat "Wisdom" 20 False wisStat = Stat "Wisdom" 20 True
wisSkills :: [Skill] wisSkills :: [Skill]
wisSkills = [ Skill "Animal Handling" Proficient "Wisdom" wisSkills = [ Skill "Animal Handling" Proficient "Wisdom"

View file

@ -1,16 +1,34 @@
module DND.Dice module DND.Dice
( rolls ( rolls
, d20 , d20
, advantage , rollCheck
, rollAttackDamage
, RollMod(..)
) where ) where
import Prelude hiding (mod)
import System.Random import System.Random
rolls :: RandomGen a => Int -> Int -> a -> [Int] data RollMod = Advantage | Disadvantage | Neutral
rolls x y = take x . randomRs (1, y)
rolls :: RandomGen a => a -> Int -> Int -> [Int]
rolls rnd x y = take x . randomRs (1, y) $ rnd
d20 :: RandomGen a => a -> Int d20 :: RandomGen a => a -> Int
d20 = minimum . rolls 1 20 d20 rnd = minimum $ rolls rnd 1 20
advantage :: RandomGen a => a -> Int rollCheck :: Int -> RollMod -> IO (Int, [Int])
advantage = maximum . rolls 2 20 rollCheck scoreMod rollMod = do
rnd <- getStdGen
let dice = rolls rnd 2 20
mod = (+) scoreMod $ case rollMod of
Advantage -> maximum dice
Disadvantage -> minimum dice
Neutral -> head dice
return (mod,dice)
rollAttackDamage :: Int -> Int -> Int -> IO Int
-- dmgMod is proficiency in normal DND rules
rollAttackDamage sides count dmgMod = do
rnd <- getStdGen
return $ (+) dmgMod . sum $ rolls rnd sides count

View file

@ -1,7 +1,9 @@
module DND.Sheet module DND.Sheet
( module DND.Sheet.Content ( module DND.Sheet.Content
, module DND.Sheet.Parser , module DND.Sheet.Parser
, module DND.Sheet.Pretty
) where ) where
import DND.Sheet.Content import DND.Sheet.Content
import DND.Sheet.Parser import DND.Sheet.Parser
import DND.Sheet.Pretty

View file

@ -76,7 +76,7 @@ data Trivia = Trivia
, bonds :: String , bonds :: String
, flaws :: String , flaws :: String
, quirk :: String , quirk :: String
} deriving ( Show, Eq, Ord, Generic) } deriving (Show, Eq, Ord, Generic)
data Skill = Skill data Skill = Skill
{ skillName :: String { skillName :: String
@ -85,9 +85,9 @@ data Skill = Skill
} deriving ( Show, Eq, Ord, Generic) } deriving ( Show, Eq, Ord, Generic)
data Stat = Stat data Stat = Stat
{ statName :: String { statName :: String
, statScore :: Int , statScore :: Int
, proficient :: Bool , statProf :: Bool
} deriving ( Show, Eq, Ord, Generic) } deriving ( Show, Eq, Ord, Generic)
data Spell = Spell data Spell = Spell

View file

@ -1,19 +1,19 @@
module DND.Sheet.Parser module DND.Sheet.Parser
( parseSheet ( parseSheet
, createExample , createExample
, getName
, getStat , getStat
, getSkill , getSkill
, getSkillNames , getSkillMod
, getStatNames , getStatMod
, getSkillScore , getSaveMod
, getProficiency , getProficiency
, scoreMod
) where ) where
import Control.Monad --import Control.Monad
import Data.Aeson import Data.Aeson
import qualified Data.ByteString.Lazy as B import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.UTF8 as BSU --import qualified Data.ByteString.Lazy.UTF8 as BSU
import Data.Maybe (fromJust) import Data.Maybe (fromJust)
import DND.Bob (bob) import DND.Bob (bob)
import DND.Sheet.Content import DND.Sheet.Content
@ -27,25 +27,17 @@ parseSheet x = unwrap . decode =<< B.readFile x
createExample :: FilePath -> IO () createExample :: FilePath -> IO ()
createExample = flip encodeFile bob createExample = flip encodeFile bob
getName :: Character -> String
getName = charName . preamble
getStat :: Character -> String -> Stat getStat :: Character -> String -> Stat
getStat char s = head . filter (\a -> statName a == s) . stats $ char getStat char s = head . filter (\a -> statName a == s) . stats $ char
getSkill :: Character -> String -> Skill getSkill :: Character -> String -> Skill
getSkill char s = head . filter (\a -> skillName a == s) . skills $ char getSkill char s = head . filter (\a -> skillName a == s) . skills $ char
getSkillNames :: Character -> [String]
getSkillNames = map skillName . skills
getStatNames :: Character -> [String]
getStatNames = map statName . stats
getProficiency :: Character -> Int getProficiency :: Character -> Int
getProficiency = fromJust . flip Map.lookup profTable . charLevel . preamble getProficiency = fromJust . flip Map.lookup profTable . charLevel . preamble
-- https://www.nerdsandscoundrels.com/how-to-calculate-proficiency-bonus-5e/ -- https://www.nerdsandscoundrels.com/how-to-calculate-proficiency-bonus-5e/
-- for some fucking reason there appears to be no simple mathematical way to get a character's proficiency bonus -- for some fucking reason there appears to be no simple mathematical way to
-- get a character's proficiency bonus
where profTable = Map.fromList where profTable = Map.fromList
[ (1,2), (2,2), (3,2), (4,2) [ (1,2), (2,2), (3,2), (4,2)
, (5,3), (6,3), (7,3), (8,3) , (5,3), (6,3), (7,3), (8,3)
@ -56,16 +48,26 @@ getProficiency = fromJust . flip Map.lookup profTable . charLevel . preamble
-- https://worldbuildersjunction.com/dungeon-and-dragons-ability-scores-explained-for-beginners/ -- https://worldbuildersjunction.com/dungeon-and-dragons-ability-scores-explained-for-beginners/
-- from the Go implementation -- from the Go implementation
-- return (stat.Score - 10) / 2 -- (stat.Score - 10) / 2
scoreMod :: Int -> Int
scoreMod x = div (x - 10) 2
getSkillScore :: Character -> String -> Int getSkillMod :: Character -> String -> Int
getSkillScore char skillString = let getSkillMod char skillString = let
skill = getSkill char skillString skill = getSkill char skillString
stat = getStat char $ skillStat skill stat = getStat char $ skillStat skill
prof = getProficiency char prof = getProficiency char
modifier = case skillMod skill of modifier = case skillMod skill of
Proficient -> prof Proficient -> prof
Expertise -> prof * 2 Expertise -> prof * 2
Half -> div prof 2 Half -> div prof 2
None -> 0 None -> 0
in (modifier +) . (`div` 2) $ statScore stat - 10 in (modifier +) . scoreMod . statScore $ stat
getStatMod :: Character -> String -> Int
getStatMod char statString = scoreMod $ statScore (getStat char statString)
getSaveMod :: Character -> String -> Int
getSaveMod char statString = let stat = getStat char statString
modifier = if statProf stat then getProficiency char else 0
in (modifier +) . scoreMod . statScore $ stat

36
lib/DND/Sheet/Pretty.hs Normal file
View file

@ -0,0 +1,36 @@
module DND.Sheet.Pretty
( getName
, getTrivia
, statFunctions
, getStats
) where
import DND.Sheet.Content
getName :: Character -> String
getName = charName . preamble
getTrivia :: Character -> [String]
getTrivia char = map (\a -> a $ trivia char) functions
where functions = [ background
, personalityTrait
, ideals
, bonds
, flaws
, quirk
]
--getStats :: Character -> [String]
--getStats =
getStats :: Character -> [String]
getStats char = let
statList = map (\a -> map a (stats char)) statFunctions
name = head statList
score = statList !! 1
proficiency = statList !! 2
in zipWith3 format name score proficiency
where format a b c = a ++ " score: " ++ b ++ " Proficient: " ++ c
statFunctions :: [Stat -> String]
statFunctions = [ statName, show . statScore, show . statProf ]

View file

@ -62,6 +62,7 @@ library
, DND.Sheet , DND.Sheet
, DND.Sheet.Content , DND.Sheet.Content
, DND.Sheet.Parser , DND.Sheet.Parser
, DND.Sheet.Pretty
build-depends: base build-depends: base
, aeson , aeson