-- | Items hunit tests -- (c) JP Moresmau 2009 module MoresmauJP.Rpg.ItemsTests where import Data.Maybe import MoresmauJP.Rpg.Character import MoresmauJP.Rpg.CharacterTests import MoresmauJP.Rpg.Inventory import MoresmauJP.Rpg.Items import MoresmauJP.Util.Random import Test.HUnit itemTests=TestList [testUsePotion,testUseWeapon,testUseScrollSuccess,testUseScrollFailure,testUseScrollFumble] testUsePotion = TestLabel "Test Use Potion" (TestCase (do let jp=createTestChar "JP" assertEqual "Physical must be 10" 10 (getCharacteristic' jp Current Physical) let jp2=setCharacteristic' jp Current Physical 5 (Just (_,jp3,remove1))<-evalRandT (useItemEffect minorHealingPotion jp2) (mkTestWrapper [8]) assertEqual "Physical must be 8 after potion" 8 (getCharacteristic' jp3 Current Physical) assertBool "not remove1" remove1 (Just (_,jp4,remove2))<-evalRandT (useItemEffect minorHealingPotion jp3) (mkTestWrapper [8]) assertEqual "Physical must be 10 after potion" 10 (getCharacteristic' jp4 Current Physical) assertBool "not remove2" remove2 )) testUseWeapon = TestLabel "Test Use Weapon" (TestCase (do let jp=createTestChar "JP" assertEqual "Physical must be 10" 10 (getCharacteristic' jp Current Physical) let jp2=setCharacteristic' jp Current Physical 5 r<-evalRandT (useItemEffect battleaxe jp2) (mkTestWrapper [10]) assertBool "result is not Nothing" (isNothing r) )) testUseScrollSuccess = TestLabel "Test Use Scroll Success" (TestCase (do let jp=createTestChar "JP" assertEqual "spells must be empty" 0 (length $ spells jp) let sc=Scroll "Scroll of nimble fingers" "Nimble Fingers" 5 (Just (s,jp2,remove1))<-evalRandT (useItemEffect sc jp) (mkTestWrapper [7]) assertBool "not remove1" remove1 assertEqual "not success message" "You learn the spell Nimble Fingers" s assertEqual "spells2 must be one" 1 (length $ spells jp2) assertEqual "spell is not Nimble Fingers" "Nimble Fingers" (spellName $ head $ spells jp2) (Just (s,jp3,remove2))<-evalRandT (useItemEffect sc jp2) (mkTestWrapper [9]) assertBool "remove2" (not remove2) assertEqual "not already message" "You already know that spell" s assertEqual "spells2 must be one" 1 (length $ spells jp3) assertEqual "spell is not Nimble Fingers" "Nimble Fingers" (spellName $ head $ spells jp3) )) testUseScrollFailure = TestLabel "Test Use Scroll Failure" (TestCase (do let jp=createTestChar "JP" assertEqual "spells must be empty" 0 (length $ spells jp) let sc=Scroll "Scroll of nimble fingers" "Nimble Fingers" 5 (Just (s,jp2,remove1))<-evalRandT (useItemEffect sc jp) (mkTestWrapper [8]) assertBool "not remove1" remove1 assertEqual "not success message" "You fail to learn that spell" s assertEqual "spells2 must be empty" 0 (length $ spells jp2) )) testUseScrollFumble = TestLabel "Test Use Scroll Failure" (TestCase (do let jp=createTestChar "JP" assertEqual "spells must be empty" 0 (length $ spells jp) let sc=Scroll "Scroll of nimble fingers" "Nimble Fingers" 5 (Just (s,jp2,remove1))<-evalRandT (useItemEffect sc jp) (mkTestWrapper [20]) assertBool "not remove1" remove1 assertEqual "not success message" "You fail badly to learn that spell" s assertEqual "spells2 must be empty" 0 (length $ spells jp2) assertEqual "Mental must be 9" 9 (getCharacteristic' jp2 Current Mental) ))