summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Main.hs53
-rw-r--r--src/Sequence/Types.hs20
2 files changed, 62 insertions, 11 deletions
diff --git a/src/Main.hs b/src/Main.hs
index f4a863f..8d74def 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -1,4 +1,4 @@
1{-# LANGUAGE ViewPatterns, RecordWildCards #-} 1{-# LANGUAGE ViewPatterns, RecordWildCards, OverloadedStrings, FlexibleContexts #-}
2 2
3import Control.Monad 3import Control.Monad
4 4
@@ -43,6 +43,12 @@ import Text.Layout.Table
43 43
44import Text.Read (readMaybe) 44import Text.Read (readMaybe)
45 45
46import Data.Text (Text)
47import qualified Data.Text as Text
48import qualified Data.Text.Lazy as Lazy (Text)
49import qualified Data.Text.Lazy as Lazy.Text
50import Data.Text.Template
51
46main :: IO () 52main :: IO ()
47main = do 53main = do
48 historyFile <- getUserCacheFile "sequence" "history" 54 historyFile <- getUserCacheFile "sequence" "history"
@@ -65,7 +71,10 @@ main = do
65 , cmd "align" alignEntity "Align the focused entity to a faction – creating it, if necessary" 71 , cmd "align" alignEntity "Align the focused entity to a faction – creating it, if necessary"
66 , cmd "name" nameEntity "Name the current entity overriding previous name assignments" 72 , cmd "name" nameEntity "Name the current entity overriding previous name assignments"
67 , cmd "spawn" spawnEntity "Create a new entity from an archetype focusing on it" 73 , cmd "spawn" spawnEntity "Create a new entity from an archetype focusing on it"
68 , cmd "roll" rollTest "Roll a test using the stats of the currently focused entity" 74 , cmd "spawn'" spawnFaction "Create a new faction and spawn multiple copies of an archetype in it"
75 , cmd "test" rollTest "Roll a test using the stats of the currently focused entity"
76 , cmd "combat" entitySeqVal "Roll sequence value for the current focus and enter combat"
77 , cmd "combat'" factionSeqVal "Roll sequence values for all members of a faction and have them enter combat"
69 ] 78 ]
70 } 79 }
71 void $ runShell description haskelineBackend (def :: GameState) 80 void $ runShell description haskelineBackend (def :: GameState)
@@ -81,11 +90,11 @@ stateOutline st
81 faction id = fromJust $ view eFaction <$> Map.lookup id (st ^. gEntities) 90 faction id = fromJust $ view eFaction <$> Map.lookup id (st ^. gEntities)
82 factionIndex id = fromJust $ elemIndex (view faction' $ faction id) factions 91 factionIndex id = fromJust $ elemIndex (view faction' $ faction id) factions
83 rowGs = do 92 rowGs = do
84 rowGroup'@((seqVal', _):_) <- protoRows 93 rowGroup'@((review seqVal' -> seqVal, _):_) <- protoRows
85 let 94 let
86 rowGroup = map snd rowGroup' 95 rowGroup = map snd rowGroup'
87 factionColumn i = [evalState ?? st $ toName x | x <- rowGroup, factionIndex x == i ] 96 factionColumn i = [evalState ?? st $ toName x | x <- rowGroup, factionIndex x == i ]
88 return . colsAllG top $ [show (seqVal' ^. seqVal)] : map factionColumn [0..(length factions - 1)] 97 return . colsAllG top $ [seqVal] : map factionColumn [0..(length factions - 1)]
89 98
90-- Query state 99-- Query state
91listFactions, listEntities :: Sh GameState () 100listFactions, listEntities :: Sh GameState ()
@@ -127,6 +136,27 @@ nameEntity :: String -> Sh GameState ()
127nameEntity ('#':_) = shellPutErrLn "We do not allow names that might shadow explicit access to entities via their number (‘#<n>’)" 136nameEntity ('#':_) = shellPutErrLn "We do not allow names that might shadow explicit access to entities via their number (‘#<n>’)"
128nameEntity name = withFocus $ \ident -> modifying gEntityNames $ Bimap.insert ident (name ^. entityName) 137nameEntity name = withFocus $ \ident -> modifying gEntityNames $ Bimap.insert ident (name ^. entityName)
129 138
139spawnFaction :: Completable Faction -> Integer -> Completable Entity -> String -> Sh GameState ()
140spawnFaction cFaction num cEntity nameTemplate
141 | ('#':_) <- nameTemplate = shellPutErrLn "We do not allow names that might shadow explicit access to entities via their number (‘#<n>’)"
142 | otherwise = do
143 let nameTemplate' = templateSafe $ Text.pack nameTemplate
144 case nameTemplate' of
145 Left _ -> shellPutErrLn "Invalid template – ‘$n’ gets replaced by [1..<n>], ‘$faction’ gets replaced by name of faction, and ‘$i’ gets replaced by a numerical identifier – quote ‘$’ as ‘$$’"
146 Right nameTemplate -> withArg (\faction -> withArg (\entity -> mapM_ (spawnFaction' faction entity nameTemplate) [1..num]) cEntity) cFaction
147 where
148 spawnFaction' faction entity nameTemplate num = do
149 identifier <- use gNextId'
150 let name = Lazy.Text.unpack <$> renderA nameTemplate (context num)
151 context num "i" = Just . Text.pack $ review entityId' identifier
152 context num "n" = Just . Text.pack $ show num
153 context num "faction" = Just . Text.pack $ faction ^. faction'
154 context num _ = Nothing
155 modify $ insertEntity entity
156 maybe (return ()) (nameEntity identifier) name
157 gEntities %= Map.adjust (set eFaction faction) identifier
158 nameEntity identifier name = modifying gEntityNames $ Bimap.insert identifier (name ^. entityName)
159
130-- Dice rolls 160-- Dice rolls
131rollTest :: Completable (FormulaM Stats Test) -> Sh GameState () 161rollTest :: Completable (FormulaM Stats Test) -> Sh GameState ()
132rollTest = withArg $ enactTest' >=> maybe (return ()) (shellPutStrLn . ppResult) 162rollTest = withArg $ enactTest' >=> maybe (return ()) (shellPutStrLn . ppResult)
@@ -150,3 +180,18 @@ enactTest' test = withFocus' $ \focus -> do
150 gFocus' .= newFocus 180 gFocus' .= newFocus
151 return result 181 return result
152 182
183entitySeqVal :: Sh GameState ()
184entitySeqVal = withFocus entitySeqVal'
185
186factionSeqVal :: Completable Faction -> Sh GameState ()
187factionSeqVal = withArg $ \qFaction -> use gEntities >>= mapM_ (entitySeqVal') . Map.keys . Map.filter ((==) qFaction . view eFaction)
188
189entitySeqVal' :: EntityIdentifier -> Sh GameState ()
190entitySeqVal' ident = do
191 entity <- preuse (gEntities . ix ident)
192 let sVal = preview (eStats . sSeqVal) =<< entity
193 case (,) <$> entity <*> sVal of
194 Nothing -> return ()
195 Just (entity, sVal) -> do
196 (newEntity, view (seqVal . re _Just) -> val) <- evalFormula entity sVal
197 gEntities . at ident .= Just (newEntity & set eSeqVal val)
diff --git a/src/Sequence/Types.hs b/src/Sequence/Types.hs
index 3d95b9a..02389a1 100644
--- a/src/Sequence/Types.hs
+++ b/src/Sequence/Types.hs
@@ -3,7 +3,7 @@
3module Sequence.Types 3module Sequence.Types
4 ( GameState, gEntities, gEntityNames, gFocus, gNextId' 4 ( GameState, gEntities, gEntityNames, gFocus, gNextId'
5 , Faction, faction, faction' 5 , Faction, faction, faction'
6 , SeqVal(..), seqVal 6 , SeqVal(..), seqVal, seqVal'
7 , Entity(..), eFaction, eSeqVal, eStats 7 , Entity(..), eFaction, eSeqVal, eStats
8 , EntityName(..), entityName 8 , EntityName(..), entityName
9 , EntityIdentifier(..), entityId, entityId' 9 , EntityIdentifier(..), entityId, entityId'
@@ -61,8 +61,13 @@ faction' = lens (CI.original . fromMaybe unaligned . view faction) (\s a -> s {
61 61
62newtype SeqVal = SeqVal { _seqVal :: Int } 62newtype SeqVal = SeqVal { _seqVal :: Int }
63 deriving (Show, Ord, Eq, Num, Integral, Enum, Real) 63 deriving (Show, Ord, Eq, Num, Integral, Enum, Real)
64makeLenses ''SeqVal 64
65 65seqVal :: Integral a => Iso' a SeqVal
66seqVal = iso (SeqVal . fromIntegral) (fromIntegral . _seqVal)
67
68seqVal' :: Prism' String SeqVal
69seqVal' = _Show . seqVal
70
66 71
67data Entity = Entity 72data Entity = Entity
68 { _eSeqVal :: Maybe SeqVal 73 { _eSeqVal :: Maybe SeqVal
@@ -90,11 +95,12 @@ entityName = iso (EntityName . CI.mk) (CI.original . _entityName)
90newtype EntityIdentifier = EntityIdentifier { _entityId :: Integer } 95newtype EntityIdentifier = EntityIdentifier { _entityId :: Integer }
91 deriving (Show, Eq, Ord, Enum) 96 deriving (Show, Eq, Ord, Enum)
92 97
93entityId :: Iso' Integer EntityIdentifier 98entityId :: Integral a => Iso' a EntityIdentifier
94entityId = iso EntityIdentifier _entityId 99entityId = iso (EntityIdentifier . fromIntegral) (fromIntegral . _entityId)
95 100
96entityId' :: Prism' String EntityIdentifier 101entityId' :: Prism' String EntityIdentifier
97entityId' = prism' (show . _entityId) (fmap EntityIdentifier . readMaybe) 102entityId' = _Show . entityId
103
98 104
99data GameState = GameState 105data GameState = GameState
100 { _gEntities :: Map EntityIdentifier Entity 106 { _gEntities :: Map EntityIdentifier Entity
@@ -118,7 +124,7 @@ inhabitedFactions = to $ nub . sort . Map.elems . fmap (view eFaction) . view gE
118priorityQueue :: Getter GameState [(SeqVal, EntityIdentifier)] 124priorityQueue :: Getter GameState [(SeqVal, EntityIdentifier)]
119priorityQueue = to priorityQueue' 125priorityQueue = to priorityQueue'
120 where 126 where
121 priorityQueue' (Map.toAscList . view gEntities -> entities) = sortBy (comparing $ Down . snd) . concat . map filter . map (over _1 $ view eSeqVal) . map swap $ entities 127 priorityQueue' (Map.toAscList . view gEntities -> entities) = sortBy (comparing $ Down . fst) . concat . map filter . map (over _1 $ view eSeqVal) . map swap $ entities
122 filter (Nothing, _) = mempty 128 filter (Nothing, _) = mempty
123 filter (Just val, id) = pure (val, id) 129 filter (Just val, id) = pure (val, id)
124 130