diff --git a/Notes.md b/Notes.md index 8f03685..e1b970c 100644 --- a/Notes.md +++ b/Notes.md @@ -2,4 +2,13 @@ ## Maps -Consider thinking about using the `Data.Map.Map` datatype instead of `[Skill]` and `[Stat]`. \ No newline at end of file +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 diff --git a/README.md b/README.md new file mode 100644 index 0000000..b022c91 --- /dev/null +++ b/README.md @@ -0,0 +1,3 @@ +# Sheet Parser + +A D&D 5e character sheet parser written in Haskell. diff --git a/app/Main.hs b/app/Main.hs index 876aaa7..be2f74e 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -1,6 +1,7 @@ module Main where import DND.Sheet.Parser +import DND.Sheet.Pretty import DND.Dice testfile :: FilePath @@ -8,7 +9,6 @@ testfile = "./example.json" main :: IO () main = do - createExample testfile sheet <- parseSheet testfile - putStrLn $ "wrote example character named \"" ++ getName sheet ++ "\" to: " ++ testfile - mapM_ putStrLn . getSkillNames $ sheet + putStrLn $ "Loaded character named " ++ getName sheet + print =<< rollCheck 2 Advantage diff --git a/example.json b/example.json index 2dfd012..1cb4cf8 100644 --- a/example.json +++ b/example.json @@ -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"}} \ No newline at end of file +{"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"}} \ No newline at end of file diff --git a/lib/DND.hs b/lib/DND.hs index c933afb..cbe6f62 100644 --- a/lib/DND.hs +++ b/lib/DND.hs @@ -9,3 +9,4 @@ import DND.Bob import DND.Dice import DND.Sheet.Content import DND.Sheet.Parser +import DND.Sheet.Pretty diff --git a/lib/DND/Bob.hs b/lib/DND/Bob.hs index 012cb85..15cfa91 100644 --- a/lib/DND/Bob.hs +++ b/lib/DND/Bob.hs @@ -3,14 +3,20 @@ module DND.Bob (bob) where import DND.Sheet.Content 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 = [strStat, dexStat, conStat, intStat, wisStat, chaStat] testPreamble :: Preamble testPreamble = Preamble - { charLevel = 5 + { charLevel = 1 , charName = "Bob" , charRace = "Elf" , charClass = "Fighter" @@ -50,7 +56,7 @@ intSkills = [ Skill "Arcana" None "Intelligence" ] wisStat :: Stat -wisStat = Stat "Wisdom" 20 False +wisStat = Stat "Wisdom" 20 True wisSkills :: [Skill] wisSkills = [ Skill "Animal Handling" Proficient "Wisdom" diff --git a/lib/DND/Dice.hs b/lib/DND/Dice.hs index c0f142e..b2d8096 100644 --- a/lib/DND/Dice.hs +++ b/lib/DND/Dice.hs @@ -1,16 +1,34 @@ module DND.Dice ( rolls , d20 -, advantage +, rollCheck +, rollAttackDamage +, RollMod(..) ) where +import Prelude hiding (mod) import System.Random -rolls :: RandomGen a => Int -> Int -> a -> [Int] -rolls x y = take x . randomRs (1, y) +data RollMod = Advantage | Disadvantage | Neutral + +rolls :: RandomGen a => a -> Int -> Int -> [Int] +rolls rnd x y = take x . randomRs (1, y) $ rnd d20 :: RandomGen a => a -> Int -d20 = minimum . rolls 1 20 +d20 rnd = minimum $ rolls rnd 1 20 -advantage :: RandomGen a => a -> Int -advantage = maximum . rolls 2 20 +rollCheck :: Int -> RollMod -> IO (Int, [Int]) +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 diff --git a/lib/DND/Sheet.hs b/lib/DND/Sheet.hs index a6d1e37..2cf686e 100644 --- a/lib/DND/Sheet.hs +++ b/lib/DND/Sheet.hs @@ -1,7 +1,9 @@ module DND.Sheet ( module DND.Sheet.Content , module DND.Sheet.Parser +, module DND.Sheet.Pretty ) where import DND.Sheet.Content import DND.Sheet.Parser +import DND.Sheet.Pretty diff --git a/lib/DND/Sheet/Content.hs b/lib/DND/Sheet/Content.hs index c87701a..05dc8ea 100644 --- a/lib/DND/Sheet/Content.hs +++ b/lib/DND/Sheet/Content.hs @@ -76,7 +76,7 @@ data Trivia = Trivia , bonds :: String , flaws :: String , quirk :: String - } deriving ( Show, Eq, Ord, Generic) + } deriving (Show, Eq, Ord, Generic) data Skill = Skill { skillName :: String @@ -85,9 +85,9 @@ data Skill = Skill } deriving ( Show, Eq, Ord, Generic) data Stat = Stat - { statName :: String - , statScore :: Int - , proficient :: Bool + { statName :: String + , statScore :: Int + , statProf :: Bool } deriving ( Show, Eq, Ord, Generic) data Spell = Spell diff --git a/lib/DND/Sheet/Parser.hs b/lib/DND/Sheet/Parser.hs index 2a75e68..71120d0 100644 --- a/lib/DND/Sheet/Parser.hs +++ b/lib/DND/Sheet/Parser.hs @@ -1,19 +1,19 @@ module DND.Sheet.Parser ( parseSheet , createExample -, getName , getStat , getSkill -, getSkillNames -, getStatNames -, getSkillScore +, getSkillMod +, getStatMod +, getSaveMod , getProficiency +, scoreMod ) where -import Control.Monad +--import Control.Monad import Data.Aeson 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 DND.Bob (bob) import DND.Sheet.Content @@ -27,25 +27,17 @@ parseSheet x = unwrap . decode =<< B.readFile x createExample :: FilePath -> IO () createExample = flip encodeFile bob -getName :: Character -> String -getName = charName . preamble - getStat :: Character -> String -> Stat getStat char s = head . filter (\a -> statName a == s) . stats $ char getSkill :: Character -> String -> Skill 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 = fromJust . flip Map.lookup profTable . charLevel . preamble -- 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 [ (1,2), (2,2), (3,2), (4,2) , (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/ -- 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 -getSkillScore char skillString = let +getSkillMod :: Character -> String -> Int +getSkillMod char skillString = let skill = getSkill char skillString - stat = getStat char $ skillStat skill - prof = getProficiency char + stat = getStat char $ skillStat skill + prof = getProficiency char modifier = case skillMod skill of Proficient -> prof Expertise -> prof * 2 Half -> div prof 2 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 diff --git a/lib/DND/Sheet/Pretty.hs b/lib/DND/Sheet/Pretty.hs new file mode 100644 index 0000000..e576180 --- /dev/null +++ b/lib/DND/Sheet/Pretty.hs @@ -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 ] diff --git a/sheet-parser-hs.cabal b/sheet-parser-hs.cabal index 22028a1..77c0404 100644 --- a/sheet-parser-hs.cabal +++ b/sheet-parser-hs.cabal @@ -62,6 +62,7 @@ library , DND.Sheet , DND.Sheet.Content , DND.Sheet.Parser + , DND.Sheet.Pretty build-depends: base , aeson