summaryrefslogtreecommitdiff
path: root/src/Sequence
diff options
context:
space:
mode:
Diffstat (limited to 'src/Sequence')
-rw-r--r--src/Sequence/Contact/Archetypes.hs4
-rw-r--r--src/Sequence/Contact/Types.hs15
-rw-r--r--src/Sequence/Contact/Types/Internal.hs8
-rw-r--r--src/Sequence/Types.hs44
-rw-r--r--src/Sequence/Utils.hs25
5 files changed, 88 insertions, 8 deletions
diff --git a/src/Sequence/Contact/Archetypes.hs b/src/Sequence/Contact/Archetypes.hs
index 1973b97..f8d4c9d 100644
--- a/src/Sequence/Contact/Archetypes.hs
+++ b/src/Sequence/Contact/Archetypes.hs
@@ -119,6 +119,7 @@ prop = Prop
119 , _sFatigueShock = def 119 , _sFatigueShock = def
120 120
121 , _sSequence = Nothing 121 , _sSequence = Nothing
122 , _sTimer = Nothing
122 123
123 , _sExtraSkills = [] 124 , _sExtraSkills = []
124 , _sModifiers = [] 125 , _sModifiers = []
@@ -230,6 +231,7 @@ human = Humanoid
230 , _sFatigue = 0 231 , _sFatigue = 0
231 232
232 , _sSequence = Nothing 233 , _sSequence = Nothing
234 , _sTimer = Nothing
233 235
234 , _sPainShock = def 236 , _sPainShock = def
235 & set seReBar (vitBar 0.75) 237 & set seReBar (vitBar 0.75)
@@ -351,6 +353,7 @@ dog = Quadruped
351 , _sFatigue = 0 353 , _sFatigue = 0
352 354
353 , _sSequence = Nothing 355 , _sSequence = Nothing
356 , _sTimer = Nothing
354 357
355 , _sPainShock = def 358 , _sPainShock = def
356 , _sFatigueShock = def 359 , _sFatigueShock = def
@@ -440,6 +443,7 @@ dolphin = Dolphin
440 , _sFatigue = 0 443 , _sFatigue = 0
441 444
442 , _sSequence = Nothing 445 , _sSequence = Nothing
446 , _sTimer = Nothing
443 447
444 , _sPainShock = def 448 , _sPainShock = def
445 , _sFatigueShock = def 449 , _sFatigueShock = def
diff --git a/src/Sequence/Contact/Types.hs b/src/Sequence/Contact/Types.hs
index 5f8808d..c69a698 100644
--- a/src/Sequence/Contact/Types.hs
+++ b/src/Sequence/Contact/Types.hs
@@ -123,6 +123,20 @@ instance Default SeqVal where
123 } 123 }
124 124
125makeLenses ''ShockEffect 125makeLenses ''ShockEffect
126
127absTime :: Lens' Timer Rational
128absTime = lens get set
129 where
130 get (Constant n) = n
131 get (Scaled n) = n
132 set (Constant _) n = Constant n
133 set (Scaled _) n = Scaled n
134
135instance Eq Timer where
136 (==) = (==) `on` view absTime
137
138instance Ord Timer where
139 compare = comparing $ view absTime
126 140
127instance Default ShockEffect where 141instance Default ShockEffect where
128 def = ShockEffect { _seApplied = False 142 def = ShockEffect { _seApplied = False
@@ -148,6 +162,7 @@ instance Default Stats where
148 , _sFatigue = 0 162 , _sFatigue = 0
149 163
150 , _sSequence = Nothing 164 , _sSequence = Nothing
165 , _sTimer = Nothing
151 166
152 , _sPainShock = def 167 , _sPainShock = def
153 , _sFatigueShock = def 168 , _sFatigueShock = def
diff --git a/src/Sequence/Contact/Types/Internal.hs b/src/Sequence/Contact/Types/Internal.hs
index 7938a06..11116e9 100644
--- a/src/Sequence/Contact/Types/Internal.hs
+++ b/src/Sequence/Contact/Types/Internal.hs
@@ -83,6 +83,10 @@ data SeqVal = SeqVal
83 } 83 }
84 deriving (Show, Eq, Ord) 84 deriving (Show, Eq, Ord)
85 85
86data Timer = Scaled Rational
87 | Constant Rational
88 deriving (Show)
89
86data ShockEffect = ShockEffect 90data ShockEffect = ShockEffect
87 { _seApplied :: Bool 91 { _seApplied :: Bool
88 , _seVal 92 , _seVal
@@ -107,6 +111,7 @@ data Stats = Prop
107 , _sFatigueShock :: ShockEffect 111 , _sFatigueShock :: ShockEffect
108 112
109 , _sSequence :: Maybe SeqVal 113 , _sSequence :: Maybe SeqVal
114 , _sTimer :: Maybe Timer
110 115
111 , _sExtraSkills :: Map (CI String) (FormulaM Stats Test) 116 , _sExtraSkills :: Map (CI String) (FormulaM Stats Test)
112 , _sModifiers :: Set Modifier 117 , _sModifiers :: Set Modifier
@@ -171,6 +176,7 @@ data Stats = Prop
171 , _sFatigue :: Int 176 , _sFatigue :: Int
172 177
173 , _sSequence :: Maybe SeqVal 178 , _sSequence :: Maybe SeqVal
179 , _sTimer :: Maybe Timer
174 180
175 , _sPainShock :: ShockEffect 181 , _sPainShock :: ShockEffect
176 , _sFatigueShock :: ShockEffect 182 , _sFatigueShock :: ShockEffect
@@ -213,6 +219,7 @@ data Stats = Prop
213 , _sFatigue :: Int 219 , _sFatigue :: Int
214 220
215 , _sSequence :: Maybe SeqVal 221 , _sSequence :: Maybe SeqVal
222 , _sTimer :: Maybe Timer
216 223
217 , _sPainShock :: ShockEffect 224 , _sPainShock :: ShockEffect
218 , _sFatigueShock :: ShockEffect 225 , _sFatigueShock :: ShockEffect
@@ -255,6 +262,7 @@ data Stats = Prop
255 , _sFatigue :: Int 262 , _sFatigue :: Int
256 263
257 , _sSequence :: Maybe SeqVal 264 , _sSequence :: Maybe SeqVal
265 , _sTimer :: Maybe Timer
258 266
259 , _sPainShock :: ShockEffect 267 , _sPainShock :: ShockEffect
260 , _sFatigueShock :: ShockEffect 268 , _sFatigueShock :: ShockEffect
diff --git a/src/Sequence/Types.hs b/src/Sequence/Types.hs
index b5f6b4b..f2c08ac 100644
--- a/src/Sequence/Types.hs
+++ b/src/Sequence/Types.hs
@@ -1,12 +1,12 @@
1{-# LANGUAGE FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, TypeSynonymInstances, ViewPatterns, OverloadedStrings, TemplateHaskell, GeneralizedNewtypeDeriving, TypeOperators, UndecidableInstances #-} 1{-# LANGUAGE FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, TypeSynonymInstances, ViewPatterns, OverloadedStrings, TemplateHaskell, GeneralizedNewtypeDeriving, TypeOperators, UndecidableInstances, RankNTypes #-}
2 2
3module Sequence.Types 3module Sequence.Types
4 ( GameState, gEntities, gEntityNames, gFocus, gNextId', gLog 4 ( GameState, gEntities, gEntityNames, gFocus, gNextId', gLog, gTimer, gLastCount
5 , Faction, faction, faction' 5 , Faction, faction, faction'
6 , Entity(..), eFaction, eSeqVal, eStats, eNotes 6 , Entity(..), eFaction, eSeqVal, eStats, eNotes
7 , EntityName(..), entityName 7 , EntityName(..), entityName
8 , EntityIdentifier(..), entityId, entityId' 8 , EntityIdentifier(..), entityId, entityId'
9 , inhabitedFactions, priorityQueue, tip, insertEntity, gFocus', gRounds, gRounds', gRound 9 , inhabitedFactions, combatFactions, combatFactions', priorityQueue, timers, tip, insertEntity, gFocus', gRounds, gRounds', gRound, eTimer
10 ) where 10 ) where
11 11
12import Control.Lens 12import Control.Lens
@@ -81,6 +81,9 @@ instance Default Entity where
81eSeqVal :: Lens' Entity (Maybe SeqVal) 81eSeqVal :: Lens' Entity (Maybe SeqVal)
82eSeqVal = eStats . sSequence 82eSeqVal = eStats . sSequence
83 83
84eTimer :: Lens' Entity (Maybe Timer)
85eTimer = eStats . sTimer
86
84instance Stats :<: Entity where 87instance Stats :<: Entity where
85 ctx' = eStats 88 ctx' = eStats
86 89
@@ -102,24 +105,36 @@ entityId' = _Show . entityId
102 105
103data GameState = GameState 106data GameState = GameState
104 { _gEntities :: Map EntityIdentifier Entity 107 { _gEntities :: Map EntityIdentifier Entity
108 , _gLastCount :: Int
105 , _gEntityNames :: Bimap EntityIdentifier EntityName 109 , _gEntityNames :: Bimap EntityIdentifier EntityName
106 , _gFocus :: Maybe EntityIdentifier 110 , _gFocus :: Maybe EntityIdentifier
107 , _gNextId :: EntityIdentifier 111 , _gNextId :: EntityIdentifier
108 , _gLog :: Seq (EntityIdentifier, String) 112 , _gLog :: Seq (EntityIdentifier, String)
113 , _gTimer :: Int
109 } 114 }
110makeLenses ''GameState 115makeLenses ''GameState
111 116
112instance Default GameState where 117instance Default GameState where
113 def = GameState 118 def = GameState
114 { _gEntities = def 119 { _gEntities = def
120 , _gLastCount = 0
115 , _gEntityNames = Bimap.empty 121 , _gEntityNames = Bimap.empty
116 , _gFocus = Nothing 122 , _gFocus = Nothing
117 , _gNextId = toEnum 0 123 , _gNextId = toEnum 0
118 , _gLog = Seq.empty 124 , _gLog = Seq.empty
125 , _gTimer = 0
119 } 126 }
120 127
121inhabitedFactions :: Getter GameState [Faction] 128inhabitedFactions, combatFactions, combatFactions' :: Getter GameState [Faction]
122inhabitedFactions = to $ nub . sort . Map.elems . fmap (view eFaction) . view gEntities 129inhabitedFactions = factionList $ \_ _ -> True
130combatFactions = factionList $ \f st -> let
131 cFactions = map (view eFaction . fromJust . flip Map.lookup (st ^. gEntities) . snd) $ st ^. priorityQueue
132 in f `elem` cFactions
133combatFactions' = factionList $ \f st -> let
134 cFactions = map (view eFaction . fromJust . flip Map.lookup (st ^. gEntities) . snd) $ st ^. timers
135 in f `elem` cFactions
136factionList :: (Faction -> GameState -> Bool) -> Getter GameState [Faction]
137factionList pred = to $ \st -> filter (flip pred st) . nub . sort . Map.elems . fmap (view eFaction) . view gEntities $ st
123 138
124priorityQueue :: Getter GameState [(SeqVal, EntityIdentifier)] 139priorityQueue :: Getter GameState [(SeqVal, EntityIdentifier)]
125priorityQueue = to priorityQueue' 140priorityQueue = to priorityQueue'
@@ -128,8 +143,23 @@ priorityQueue = to priorityQueue'
128 filter (Nothing, _) = mempty 143 filter (Nothing, _) = mempty
129 filter (Just val, id) = pure (val, id) 144 filter (Just val, id) = pure (val, id)
130 145
146timers :: Getter GameState [(Timer, EntityIdentifier)]
147timers = to timers'
148 where
149 timers' state = sortBy (comparing fst) . concat . map filter . map (over _1 $ view eTimer) . map swap $ entities
150 where
151 entities = Map.toAscList $ view gEntities state
152 time = fromIntegral $ view gTimer state
153 filter (Nothing, _) = mempty
154 filter (Just v, id) = pure (v, id)
155
131tip :: Fold GameState EntityIdentifier 156tip :: Fold GameState EntityIdentifier
132tip = priorityQueue . folding (fmap snd . listToMaybe) 157tip = folding $ runReaderT tip'
158 where
159 tip' :: ReaderT GameState First EntityIdentifier
160 tip' = do
161 join . fmap (lift . First) . preview $ timers . folding (fmap snd . listToMaybe)
162 join . fmap (lift . First) . preview $ priorityQueue . folding (fmap snd . listToMaybe)
133 163
134gFocus' :: Traversal' GameState Entity 164gFocus' :: Traversal' GameState Entity
135gFocus' modifyFocus st = (flip runReader st) . (maybe (asks pure) return =<<) . runMaybeT $ do 165gFocus' modifyFocus st = (flip runReader st) . (maybe (asks pure) return =<<) . runMaybeT $ do
@@ -158,7 +188,7 @@ insertEntity entity = execState $ do
158 gNextId %= succ 188 gNextId %= succ
159 189
160gRounds :: Traversal' GameState Int 190gRounds :: Traversal' GameState Int
161gRounds = gEntities . each . eStats . sSequence . _Just . seqRound . _Wrapped 191gRounds = gEntities . each . eSeqVal . _Just . seqRound . _Wrapped
162 192
163gRounds' :: Getter GameState [Int] 193gRounds' :: Getter GameState [Int]
164gRounds' = to $ nub . sort . toListOf gRounds 194gRounds' = to $ nub . sort . toListOf gRounds
diff --git a/src/Sequence/Utils.hs b/src/Sequence/Utils.hs
index fbf3c7d..bb29b86 100644
--- a/src/Sequence/Utils.hs
+++ b/src/Sequence/Utils.hs
@@ -1,10 +1,12 @@
1{-# LANGUAGE ViewPatterns, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, OverloadedStrings, OverloadedLists, RankNTypes #-} 1{-# LANGUAGE ViewPatterns, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, OverloadedStrings, OverloadedLists, RankNTypes #-}
2 2
3module Sequence.Utils 3module Sequence.Utils
4 ( withArg, withFocus, withFocus' 4 ( TimerLength(..), TimerOrigin(..)
5 , withArg, withFocus, withFocus'
5 , focusState 6 , focusState
6 , toName, toDesc 7 , toName, toDesc
7 , outputLogged 8 , outputLogged
9 , scaleTimer
8 , Argument(..) 10 , Argument(..)
9 , Completion(..) 11 , Completion(..)
10 , module Sequence.Utils.Ask 12 , module Sequence.Utils.Ask
@@ -50,6 +52,10 @@ import Sequence.Formula
50 52
51import Text.Regex (mkRegex, subRegex) 53import Text.Regex (mkRegex, subRegex)
52 54
55data TimerLength = TimerLength TimerOrigin Int
56
57data TimerOrigin = Absolute | Now
58
53class Argument a st | a -> st where 59class Argument a st | a -> st where
54 arg :: String -> Sh st (Maybe a) 60 arg :: String -> Sh st (Maybe a)
55 61
@@ -93,6 +99,23 @@ outputLogged id str = gLog <>= pure (id, clean str) >> shellPutStrLn str
93 where 99 where
94 clean str = subRegex (mkRegex "(\x9B|\x1B\\[)[0-?]*[ -/]*[@-~]") str "" -- remove ANSI escapes 100 clean str = subRegex (mkRegex "(\x9B|\x1B\\[)[0-?]*[ -/]*[@-~]") str "" -- remove ANSI escapes
95 101
102scaleTimer :: Int -> Rational -> Timer -> Timer
103scaleTimer _ _ t@(Constant _) = t
104scaleTimer (fromIntegral -> now) factor (Scaled r) = Scaled $ ((max 0 $ r - now) * factor) + now
105
106instance Completion TimerLength GameState where
107 completableLabel _ = "<timer offset>"
108 complete _ st prefix = return []
109
110instance Argument TimerLength GameState where
111 arg str
112 | ('+':cs) <- str
113 , (Just n) <- readMaybe cs
114 , n >= 0 = return . Just $ TimerLength Now n
115 | (Just n) <- readMaybe str
116 , n >= 0 = return . Just $ TimerLength Absolute n
117 | otherwise = return Nothing
118
96instance Completion EntityIdentifier GameState where 119instance Completion EntityIdentifier GameState where
97 completableLabel _ = "<entity>" 120 completableLabel _ = "<entity>"
98 complete _ st prefix = return . filter ((isPrefixOf `on` CI.foldCase) prefix) . map ((evalState ?? st) . toName) . Map.keys $ st ^. gEntities 121 complete _ st prefix = return . filter ((isPrefixOf `on` CI.foldCase) prefix) . map ((evalState ?? st) . toName) . Map.keys $ st ^. gEntities