-- | Fight resolution hunit tests -- (c) JP Moresmau 2009 module MoresmauJP.Rpg.FightTests where import MoresmauJP.Rpg.Character import MoresmauJP.Rpg.CharacterTests import MoresmauJP.Rpg.Fight import MoresmauJP.Util.Random import Test.HUnit fightTests = TestList [testFightRoundNormal, testFightRoundFumble,testFightRoundKill] testFightRoundNormal=TestLabel "Test Fight Round Normal Hit" (TestCase (do --let jpChars=unlines (map (\x-> (show x) ++ " 10/10(0)") [Strength .. Mental]) let jp=createTestChar "JP" assertBool "JP is not OK" (isOK jp) let troll=createTestChar "Troll" assertBool "Troll is not OK" (isOK troll) let ((jp2,troll2),dead,msgs)=evalRand (giveBlow jp troll) (mkTestWrapper[8])--processFightRound jp troll [11,8,11] assertBool "somebody is dead!" (not dead) assertEqual "jp2 is not jp" (name jp2) (name jp) assertEqual "troll2 is not troll" (name troll2) (name troll) assertBool "JP is not OK" (isOK jp2) assertBool "Troll is not OK" (isOK troll2) assertEqual "jp2 physical is not jp physical" (getCharacteristic' jp2 Current Physical) (getCharacteristic' jp Current Physical) assertEqual "troll didn't lose 2 physical" (getCharacteristic' troll2 Current Physical) ((getCharacteristic' troll Current Physical)-2) assertEqual "Not 1 message" 1 (length msgs) assertEqual "Msg1" "JP hits and causes 2 damages" (show $ head msgs) --assertEqual "Msg2" "Troll misses" (head $ tail msgs) )) testFightRoundFumble=TestLabel "Test Fight Round Fumbles" (TestCase (do --let jpChars=unlines (map (\x-> (show x) ++ " 10/10(0)") [Strength .. Mental]) let jp=createTestChar "JP" assertBool "JP is not OK" (isOK jp) let troll=createTestChar "Troll" assertBool "Troll is not OK" (isOK troll) let ((troll2,jp2),dead,msgs)=evalRand (giveBlow troll jp) (mkTestWrapper [20]) --processFightRound jp troll [11,11,20] assertBool "somebody is dead!" (not dead) assertEqual "jp2 is not jp" (name jp2) (name jp) assertEqual "troll2 is not troll" (name troll2) (name troll) assertBool "JP is not OK" (isOK jp2) assertBool "Troll is not OK" (isOK troll2) assertEqual "jp2 physical is not jp physical" (getCharacteristic' jp2 Current Physical) (getCharacteristic' jp Current Physical) assertEqual "troll didn't lose 2 physical" ((getCharacteristic' troll Current Physical)-2) (getCharacteristic' troll2 Current Physical) assertEqual "Not 1 message" 1 (length msgs) --assertEqual "Msg1" "JP misses" (head msgs) assertEqual "Msg2" "Troll fumbles and gives himself 2 damages" (show $ head msgs) )) testFightRoundKill=TestLabel "Test Fight Round Kill" (TestCase (do --let jpChars=unlines (map (\x-> (show x) ++ " 10/10(0)") [Strength .. Mental]) let jp=createTestChar "JP" assertBool "JP is not OK" (isOK jp) let troll1=createTestChar "Troll" let troll=setCharacteristic' troll1 Current Physical 2 assertBool "Troll is not OK" (isOK troll) let ((jp2,troll2),dead,msgs)=evalRand (giveBlow jp troll) (mkTestWrapper [8]) -- processFightRound jp troll [11,8,11] assertBool "nobody is dead!" dead assertEqual "jp2 is not jp" (name jp2) (name jp) assertEqual "troll2 is not troll" (name troll2) (name troll) assertBool "JP is not OK" (isOK jp2) assertBool "Troll is OK" (not (isOK troll2)) assertBool "Troll is not dead" (isDead troll2) assertBool "Troll is not oos" (isOutOfService troll2) assertEqual "jp2 physical is not jp physical" (getCharacteristic' jp2 Current Physical) (getCharacteristic' jp Current Physical) assertEqual "troll didn't lose 2 physical" ((getCharacteristic' troll Current Physical)-2) (getCharacteristic' troll2 Current Physical) assertEqual "Not 1 message" (length msgs) 1 assertEqual "Msg1" "JP hits and causes 2 damages" (show $ head msgs) ))