summaryrefslogtreecommitdiff
path: root/src/Sequence
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2016-06-12 03:44:53 +0200
committerGregor Kleen <gkleen@yggdrasil.li>2016-06-12 03:44:53 +0200
commit0802edda630246a0ff9f82196e55f09780ffa965 (patch)
treefe85c33b11afd69fa4ead5cba7a74c18b092ca9a /src/Sequence
parentbf24ff9ffd25841da5e20386548fb63ff191ed9a (diff)
download2017-01-16_17:13:37-0802edda630246a0ff9f82196e55f09780ffa965.tar
2017-01-16_17:13:37-0802edda630246a0ff9f82196e55f09780ffa965.tar.gz
2017-01-16_17:13:37-0802edda630246a0ff9f82196e55f09780ffa965.tar.bz2
2017-01-16_17:13:37-0802edda630246a0ff9f82196e55f09780ffa965.tar.xz
2017-01-16_17:13:37-0802edda630246a0ff9f82196e55f09780ffa965.zip
Armour
Diffstat (limited to 'src/Sequence')
-rw-r--r--src/Sequence/Contact/Types.hs56
-rw-r--r--src/Sequence/Contact/Types/Internal.hs22
-rw-r--r--src/Sequence/Utils.hs9
3 files changed, 65 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
3module Sequence.Contact.Types 3module Sequence.Contact.Types
4 ( module Sequence.Contact.Types 4 ( module Sequence.Contact.Types
@@ -38,18 +38,10 @@ instance IsString Hitzone where
38 38
39makePrisms ''Hitzone 39makePrisms ''Hitzone
40 40
41makeLenses ''Armor 41makePrisms ''DamageType
42 42
43instance Default Armor where 43instance {-# 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
54makeLenses ''TestResult 46makeLenses ''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
184absorb :: Armor -> DamageType -> Int -> FormulaM Stats (Map DamageType Int)
185absorb 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)
17newtype Hitzone = Hitzone { _hitzone :: CI String } 17newtype Hitzone = Hitzone { _hitzone :: CI String }
18 deriving (Eq, Ord) 18 deriving (Eq, Ord)
19 19
20data Armor = Armor 20type Armor = DamageType -> Formula Stats
21 { _aBallistic 21
22 , _aPiercing 22data 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
30data TestResult = CritSuccess { _rWith, _rBy :: Int } 34data TestResult = CritSuccess { _rWith, _rBy :: Int }
31 | Success { _rWith, _rBy :: Int } 35 | Success { _rWith, _rBy :: Int }
diff --git a/src/Sequence/Utils.hs b/src/Sequence/Utils.hs
index 1b52630..dc6657a 100644
--- a/src/Sequence/Utils.hs
+++ b/src/Sequence/Utils.hs
@@ -131,3 +131,12 @@ instance Argument (Set Hitzone) GameState where
131 hitzones <- Set.map (view _Hitzone) . Map.keysSet <$> MaybeT (preuse $ gFocus' . eStats . sHitzones) 131 hitzones <- Set.map (view _Hitzone) . Map.keysSet <$> MaybeT (preuse $ gFocus' . eStats . sHitzones)
132 guard (hasGlob || ws `Set.isSubsetOf` hitzones) 132 guard (hasGlob || ws `Set.isSubsetOf` hitzones)
133 return . Set.map (review _Hitzone) $ if hasGlob then hitzones else ws 133 return . Set.map (review _Hitzone) $ if hasGlob then hitzones else ws
134
135instance Completion DamageType GameState where
136 completableLabel _ = "<damageType>"
137 complete _ _ prefix = return . filter ((isPrefixOf `on` CI.foldCase) prefix) $ map show ([minBound .. maxBound] :: [DamageType])
138
139instance Argument DamageType GameState where
140 arg (CI.mk -> word) = return $ Map.lookup word types
141 where
142 types = Map.fromList [(CI.mk $ show dType, dType) | dType <- [minBound .. maxBound]]