-- | Magic hunit tests -- (c) JP Moresmau 2009 module MoresmauJP.Rpg.MagicTests where import MoresmauJP.Rpg.Character import MoresmauJP.Rpg.CharacterTests import MoresmauJP.Rpg.Magic import MoresmauJP.Util.Random import Test.HUnit magicTests=TestList [testSpellsToMyself,testSpellToOpponentSuccess,testSpellToOpponentFailure,testSpellToOpponentFumble] testSpellsToMyself= TestLabel "Test spells to myself" (TestCase (do let jp=(createTestChar "jp"){spells=[Spell "Nimble Fingers" Dexterity Positive Temporary]} let spellsToMe1=spellsToMyself jp assertEqual "not one spell" 1 (length spellsToMe1) assertEqual "not nimble fingers" "Nimble Fingers" (spellName $ head spellsToMe1) (jp2,msg)<-evalRandT (spellToMyself jp (head spellsToMe1) 1) (TestRandom [9]) assertEqual "not Fire Ball message" "The spell Nimble Fingers worked" (show msg) assertEqual "dex is not 11" 11 (getCharacteristic' jp2 Current Dexterity) let spellsToMe2=spellsToMyself jp2 assertEqual "not zero spell2" 0 (length spellsToMe2) let (jp3,_)=expireAffects jp2 4 let spellsToMe3=spellsToMyself jp3 assertEqual "not zero spell3" 0 (length spellsToMe3) let (jp4,_)=expireAffects jp2 5 let spellsToMe4=spellsToMyself jp4 assertEqual "not one spell4" 1 (length spellsToMe4) )) testSpellToOpponentSuccess= TestLabel "Test spell to opponent success " (TestCase (do let jp=(createTestChar "JP") {spells=[Spell "Fire Ball" Physical Negative Permanent]} let troll=createTestChar "Troll" ((_,troll1),isDead,msgs)<-evalRandT (spellToOpponent jp troll (head $ spells jp) 0) (TestRandom [9]) assertBool "dead" (not isDead) assertEqual "not physical 9" 9 (getCharacteristic' troll1 Current Physical) assertEqual "not 1 message" 1 (length msgs) assertEqual "not Fire Ball message" "JP casts Fire Ball" (show $ head msgs) )) testSpellToOpponentFailure= TestLabel "Test spells to opponent failure" (TestCase (do let jp=(createTestChar "JP") {spells=[Spell "Fire Ball" Physical Negative Permanent]} let troll=createTestChar "Troll" ((_,troll1),isDead,msgs)<-evalRandT (spellToOpponent jp troll (head $ spells jp) 0) (TestRandom [11]) assertBool "dead" (not isDead) assertEqual "not physical 10" 10 (getCharacteristic' troll1 Current Physical) assertEqual "not 1 message" 1 (length msgs) assertEqual "not Fire Ball message" "The spell Fire Ball fails" (show $ head msgs) )) testSpellToOpponentFumble= TestLabel "Test spells to opponent fumble" (TestCase (do let jp=(createTestChar "JP") {spells=[Spell "Fire Ball" Physical Negative Permanent]} let troll=createTestChar "Troll" ((jp1,troll1),isDead,msgs)<-evalRandT (spellToOpponent jp troll (head $ spells jp) 0) (TestRandom [20]) assertBool "dead" (not isDead) assertEqual "not physical 10" 10 (getCharacteristic' troll1 Current Physical) assertEqual "not 1 message" 1 (length msgs) assertEqual "not Fire Ball message" "The spell Fire Ball backfires on you" (show $ head msgs) assertEqual "Mental must be 9" 9 (getCharacteristic' jp1 Current Mental) ))