-- | Character handling unit tests -- (c) JP Moresmau 2009 module MoresmauJP.Rpg.CharacterTests where import Data.Array.IArray import MoresmauJP.Rpg.Character import MoresmauJP.Rpg.Inventory import MoresmauJP.Rpg.Profile import MoresmauJP.Util.Random import Test.HUnit import System.Random characterTests=TestList [testLevel,testSetOOS,testExperience,testAffects] createTestChar :: String -> Character createTestChar name=Character name Male (array (Strength,Mental) (map (\x->(x,(Rating (array (Normal,Experience) [(Normal,10),(Current,10),(Experience,0)]) ))) [Strength .. Mental] ) ) mkEmptyInventory [] [] mkEmptyInventory=(makeEmptyInventory 10 0) testLevel= TestLabel "Test Level" (TestCase (do let jp=createTestChar "JP" assertEqual "Level is not 10" 10 (characterLevel jp) let jp2=Character "jp2" Male (array (Strength,Mental) (map (\x->(x,(Rating (array (Normal,Experience) [(Normal,15),(Current,10),(Experience,5)]) ))) [Strength .. Mental] ) ) mkEmptyInventory [] [] assertEqual "Level is not 15" 15 (characterLevel jp2) )) testSetOOS = TestLabel "Test Out Of Service" ( TestCase (do sg<-getStdGen mt<-evalRandT(generateTraits $ head $ profiles) (ProductionRandom sg) let c=Character "Test" Male (getDefaultHealth mt) mkEmptyInventory [] [] assertBool "Character is not OK" (isOK c) assertBool "Character is out of service" (not (isOutOfService c)) let c2=setCharacteristic' c Current Physical 0 assertBool "Character is not dead" (isDead c2) assertBool "Character is mad" (not (isMad c2)) assertBool "Character is ok" (not (isOK c2)) assertBool "Character is not out of service" (isOutOfService c2) let c3=setCharacteristic' c2 Current Physical 10 let c4=setCharacteristic' c3 Current Mental 0 assertBool "Character is not mad" (isMad c4) assertBool "Character is dead" (not (isDead c4)) assertBool "Character is ok" (not (isOK c4)) assertBool "Character is not out of service" (isOutOfService c4) let c5=setCharacteristic' c4 Current Physical 0 assertBool "Character is not mad" (isMad c5) assertBool "Character is not dead" (isDead c5) assertBool "Character is ok" (not (isOK c5)) assertBool "Character is not out of service" (isOutOfService c5) )) testExperience = TestLabel "Test Experience" (TestCase (do let jp=createTestChar "JP" assertEqual "current dexterity is not 10" 10 (getCharacteristic' jp Current Dexterity) assertEqual "normal dexterity is not 11" 10 (getCharacteristic' jp Normal Dexterity) assertEqual "experience dexterity is not 0" 0 (getCharacteristic' jp Experience Dexterity) let jp2=setCharacteristic' jp Experience Dexterity 334 assertEqual "current dexterity is not 10" 11 (getCharacteristic' jp2 Current Dexterity) assertEqual "normal dexterity is not 10" 11 (getCharacteristic' jp2 Normal Dexterity) assertEqual "experience dexterity is not 10" 1 (getCharacteristic' jp2 Experience Dexterity) )) testAffects= TestLabel "Test Affects" (TestCase (do let jp=createTestChar "JP" (jp',descs)=expireAffects jp 1 assertEqual "jp has changed" jp jp' assertEqual "descs found while no affect" 0 (length descs) let aff1=Affect Strength (-3) 5 "weakness" "under a spell of weakness" "you feel stronger" aff2=Affect Dexterity 2 10 "nimble fingers" "under a spell of nimble fingers" "you feel as clumsy as usual" jp2=addAffect (addAffect jp aff1) aff2 (jp3,descs1)=expireAffects jp2 1 (jp4,descs2)=expireAffects jp3 5 (jp5,descs3)=expireAffects jp4 11 assertEqual "jp2 has changed" jp2 jp3 assertEqual "descs found while tick is <" 0 (length descs1) assertEqual "strength is not 7" 7 (getCharacteristic' jp3 Current Strength) assertEqual "dexterity is not 12" 12 (getCharacteristic' jp3 Current Dexterity) assertEqual "descs2 not found while tick is >" 1 (length descs2) assertEqual "not feel stronger" "you feel stronger" (head descs2) assertEqual "jp4 has not 1 affect left" 1 (length $ affects jp4) assertEqual "jp4 does not have dexterity affect left" aff2 (head $ affects jp4) assertEqual "descs3 not found while tick is >" 1 (length descs3) assertEqual "not feel clumsy" "you feel as clumsy as usual" (head descs3) assertEqual "jp5 has not 0 affect left" 0 (length $ affects jp5) ))