diff options
Diffstat (limited to 'src/Sequence/Contact')
-rw-r--r-- | src/Sequence/Contact/Types.hs | 56 | ||||
-rw-r--r-- | src/Sequence/Contact/Types/Internal.hs | 22 |
2 files changed, 56 insertions, 22 deletions
diff --git a/src/Sequence/Contact/Types.hs b/src/Sequence/Contact/Types.hs index 80d4360..9bb9903 100644 --- a/src/Sequence/Contact/Types.hs +++ b/src/Sequence/Contact/Types.hs | |||
@@ -1,4 +1,4 @@ | |||
1 | {-# LANGUAGE TemplateHaskell, RecordWildCards, OverloadedStrings, OverloadedLists, ViewPatterns, RankNTypes, ImpredicativeTypes, FlexibleContexts #-} | 1 | {-# LANGUAGE TemplateHaskell, RecordWildCards, OverloadedStrings, OverloadedLists, ViewPatterns, RankNTypes, ImpredicativeTypes, FlexibleContexts, TypeSynonymInstances, FlexibleInstances #-} |
2 | 2 | ||
3 | module Sequence.Contact.Types | 3 | module Sequence.Contact.Types |
4 | ( module Sequence.Contact.Types | 4 | ( module Sequence.Contact.Types |
@@ -38,18 +38,10 @@ instance IsString Hitzone where | |||
38 | 38 | ||
39 | makePrisms ''Hitzone | 39 | makePrisms ''Hitzone |
40 | 40 | ||
41 | makeLenses ''Armor | 41 | makePrisms ''DamageType |
42 | 42 | ||
43 | instance Default Armor where | 43 | instance {-# OVERLAPS #-} Default Armor where |
44 | def = Armor | 44 | def = const 0 |
45 | { _aBallistic = 0 | ||
46 | , _aPiercing = 0 | ||
47 | , _aBlunt = 0 | ||
48 | , _aHeat = 0 | ||
49 | , _aCold = 0 | ||
50 | , _aToxic = 0 | ||
51 | , _aExplosive = 0 | ||
52 | } | ||
53 | 45 | ||
54 | makeLenses ''TestResult | 46 | makeLenses ''TestResult |
55 | 47 | ||
@@ -188,3 +180,41 @@ sUnconscious = folding $ do | |||
188 | maxVitality <- preview sMaxVitality | 180 | maxVitality <- preview sMaxVitality |
189 | damage <- view sFatigue | 181 | damage <- view sFatigue |
190 | return $ liftM2 (>=) <$> Just (return damage) <*> maxVitality | 182 | return $ liftM2 (>=) <$> Just (return damage) <*> maxVitality |
183 | |||
184 | absorb :: Armor -> DamageType -> Int -> FormulaM Stats (Map DamageType Int) | ||
185 | absorb armor = absorb' Map.empty | ||
186 | where | ||
187 | absorb' :: Map DamageType Int -> DamageType -> Int -> FormulaM Stats (Map DamageType Int) | ||
188 | absorb' old dType dmg = do | ||
189 | mass <- maybe (return (Nothing :: Maybe Int)) (fmap Just) =<< preview (ctx . sAMass) | ||
190 | armor' <- wArmor dType | ||
191 | let | ||
192 | current = transmit mass dType $ min dmg armor' | ||
193 | new <- Map.unionsWith (+) <$> (sequence . Map.elems $ Map.mapWithKey (absorb' current) current) | ||
194 | return . Map.unionWith (+) (leftover mass dType . clamp $ dmg - armor') $ if old /= current then new else current | ||
195 | |||
196 | wArmor :: DamageType -> Formula Stats | ||
197 | wArmor Passthrough = return $ 0 | ||
198 | wArmor Electric = (2 *) . maximum <$> mapM wArmor ([minBound..maxBound] \\ [Electric] :: [DamageType]) | ||
199 | wArmor x = armor x | ||
200 | |||
201 | clamp n | ||
202 | | n <= 0 = 0 | ||
203 | | otherwise = n | ||
204 | |||
205 | transmit, leftover :: Maybe Int -> DamageType -> Int -> Map DamageType Int | ||
206 | transmit _ Ballistic n = [ (Blunt, n) ] | ||
207 | transmit _ Piercing n = [ (Blunt, n) ] | ||
208 | transmit _ _ _ = [] | ||
209 | |||
210 | |||
211 | leftover (Just m) Blunt n = [ (Fatigue, min n m) | ||
212 | , (Blunt, clamp $ n - m) | ||
213 | ] | ||
214 | leftover (Just m) Cold n = [ (Fatigue, min n $ m * 2) | ||
215 | , (Cold, clamp $ n - m * 2) | ||
216 | ] | ||
217 | leftover _ Explosive n = [ (Fatigue, n) | ||
218 | , (Explosive, n) | ||
219 | ] | ||
220 | leftover _ dType n = [ (dType, n) ] | ||
diff --git a/src/Sequence/Contact/Types/Internal.hs b/src/Sequence/Contact/Types/Internal.hs index 0fe6266..6fde09d 100644 --- a/src/Sequence/Contact/Types/Internal.hs +++ b/src/Sequence/Contact/Types/Internal.hs | |||
@@ -17,15 +17,19 @@ import Data.CaseInsensitive (CI) | |||
17 | newtype Hitzone = Hitzone { _hitzone :: CI String } | 17 | newtype Hitzone = Hitzone { _hitzone :: CI String } |
18 | deriving (Eq, Ord) | 18 | deriving (Eq, Ord) |
19 | 19 | ||
20 | data Armor = Armor | 20 | type Armor = DamageType -> Formula Stats |
21 | { _aBallistic | 21 | |
22 | , _aPiercing | 22 | data DamageType = Ballistic |
23 | , _aBlunt | 23 | | Piercing |
24 | , _aHeat | 24 | | Blunt |
25 | , _aCold | 25 | | Heat |
26 | , _aToxic | 26 | | Cold |
27 | , _aExplosive :: Int | 27 | | Toxic |
28 | } | 28 | | Explosive |
29 | | Fatigue | ||
30 | | Electric | ||
31 | | Passthrough | ||
32 | deriving (Eq, Ord, Enum, Bounded, Show) | ||
29 | 33 | ||
30 | data TestResult = CritSuccess { _rWith, _rBy :: Int } | 34 | data TestResult = CritSuccess { _rWith, _rBy :: Int } |
31 | | Success { _rWith, _rBy :: Int } | 35 | | Success { _rWith, _rBy :: Int } |