-- | Magic spells casting resolution -- (c) JP Moresmau 2009 module MoresmauJP.Rpg.Magic where import MoresmauJP.Rpg.Actions import MoresmauJP.Rpg.Character import MoresmauJP.Util.Random import Text.Printf type MagicStatus a= ((a,a),Bool,[Message]) allSpells :: [Spell] allSpells= [ Spell "Feel Better" Physical Recovery Permanent ,Spell "Fire Ball" Physical Negative Permanent ,Spell "Nimble Fingers" Dexterity Positive Temporary ,Spell "Greasy Fingers" Dexterity Negative Temporary ,Spell "Madness" Mental Negative Permanent ,Spell "Sanity" Mental Recovery Permanent ,Spell "Focus... Focus... Focus..." Willpower Positive Temporary ,Spell "Think! Think! Think!" Intelligence Positive Temporary ,Spell "Doh!" Intelligence Negative Temporary ,Spell "Ox Strength" Strength Positive Temporary ,Spell "Troll Face" Charisma Negative Temporary ] spellToAffect :: Spell -> RollResult -> Int -> Affect spellToAffect spell rr tc=Affect (impactedChar spell) (diff rr) (tc + (((diff rr)+1) ^ 2)) (spellName spell) (printf "Under the influence of %s" (spellName spell)) (printf "Spell %s is lifting" (spellName spell)) spellsToMyself :: Character -> [Spell] spellsToMyself c=removedAlreadyAffecting c $ filter ((Negative /=) . impact) (spells c) spellsToOpponent :: Character -> Character -> [Spell] spellsToOpponent c opponent=removedAlreadyAffecting opponent $ filter ((Negative ==) . impact) (spells c) removedAlreadyAffecting :: Character -> [Spell] -> [Spell] removedAlreadyAffecting c spells=let affectSources=map source (affects c) in filter (\x-> notElem (spellName x) affectSources) spells spellToMyself :: (MonadRandom m) => Character -> Spell -> Int -> m (Character,Message) spellToMyself c s tc=do (c2,rr)<-action c spellcasting (toIntLevel Neutral) return $ spellToMyselfEffect c2 s tc rr spellToMyselfEffect :: Character -> Spell -> Int -> RollResult -> (Character,Message) spellToMyselfEffect c s _ (Failure {grade=Exceptional})=(addCharacteristic' c Current Mental (-1),Message (c,s,Fumble)) spellToMyselfEffect c s _ (Failure {})=(c,Message (c,s,Fail)) spellToMyselfEffect c s tc rr@(Success {})= case spellDuration s of Temporary->(addAffect c (spellToAffect s rr tc),Message (c,s,Myself)) Permanent->((fst $ recover c (impactedChar s) (diff rr)),Message (c,s,Myself)) spellToOpponent ::(MonadRandom m)=> Character -> Character -> Spell -> Int -> m (MagicStatus Character) spellToOpponent c1 c2 s tc= do ((c1b,c2b),rr) <- compete c1 c2 melee return $ spellToOpponentEffect c1b c2b s tc rr spellToOpponentEffect :: Character -> Character -> Spell -> Int -> RollResult -> MagicStatus Character spellToOpponentEffect c1 c2 s _ (Failure {grade=Exceptional})=((addCharacteristic' c1 Current Mental (-1),c2),isOutOfService c1,[Message (c1,s,Fumble)]) spellToOpponentEffect c1 c2 s _ (Failure {})=((c1,c2),False,[Message (c1,s,Fail)]) spellToOpponentEffect c1 c2 s tc rr@(Success {})= case spellDuration s of Temporary->((c1,addAffect c2 (spellToAffect s rr tc)),isOutOfService c2,[Message (c1,s,Opponent) ]) Permanent->((c1,(addCharacteristic' c2 Current (impactedChar s) (-(diff rr)))),isOutOfService c2,[Message (c1,s,Opponent) ]) -- complexity -- danger -- curse: add difficulty to all actions -- need a time counter to evaluate when spell is finished newtype Message=Message (Character,Spell,MessageType) data MessageType=Fumble | Fail |Myself | Opponent instance Show Message where showsPrec _ (Message (_,s,Fumble))=showString $printf "The spell %s backfires on you" (spellName s) showsPrec _ (Message (_,s,Fail))=showString $printf "The spell %s fails" (spellName s) showsPrec _ (Message (_,s,Myself))=showString $printf "The spell %s worked" (spellName s) showsPrec _ (Message (c,s,Opponent))=showString $printf "%s casts %s" (name c) (spellName s)