diff options
Diffstat (limited to 'src/Main.hs')
| -rw-r--r-- | src/Main.hs | 81 |
1 files changed, 59 insertions, 22 deletions
diff --git a/src/Main.hs b/src/Main.hs index e8e0a49..f409a04 100644 --- a/src/Main.hs +++ b/src/Main.hs | |||
| @@ -36,6 +36,7 @@ import Data.Function | |||
| 36 | 36 | ||
| 37 | import Control.Monad.State.Strict | 37 | import Control.Monad.State.Strict |
| 38 | import Control.Monad.Trans.Maybe | 38 | import Control.Monad.Trans.Maybe |
| 39 | import Control.Monad.List | ||
| 39 | 40 | ||
| 40 | import Sequence.Types | 41 | import Sequence.Types |
| 41 | import Sequence.Contact.Types | 42 | import Sequence.Contact.Types |
| @@ -54,6 +55,8 @@ import qualified Data.Text.Lazy as Lazy (Text) | |||
| 54 | import qualified Data.Text.Lazy as Lazy.Text | 55 | import qualified Data.Text.Lazy as Lazy.Text |
| 55 | import Data.Text.Template | 56 | import Data.Text.Template |
| 56 | 57 | ||
| 58 | import Debug.Trace | ||
| 59 | |||
| 57 | main :: IO () | 60 | main :: IO () |
| 58 | main = do | 61 | main = do |
| 59 | historyFile <- getUserCacheFile "sequence" "history" | 62 | historyFile <- getUserCacheFile "sequence" "history" |
| @@ -63,7 +66,8 @@ main = do | |||
| 63 | { historyFile = Just historyFile | 66 | { historyFile = Just historyFile |
| 64 | , prompt = \st -> return $ maybe "" (++ " ") ((evalState ?? st) . toName <$> view gFocus st) ++ "→ " | 67 | , prompt = \st -> return $ maybe "" (++ " ") ((evalState ?? st) . toName <$> view gFocus st) ++ "→ " |
| 65 | , beforePrompt = do | 68 | , beforePrompt = do |
| 66 | { gets stateOutline >>= (\str -> if null str then return () else shellPutStr str) | 69 | { stateMaintenance |
| 70 | ; stateOutline >>= (\str -> if null str then return () else shellPutStr str) | ||
| 67 | ; gets focusNotes >>= (\str -> if null str then return () else shellPutStr str) | 71 | ; gets focusNotes >>= (\str -> if null str then return () else shellPutStr str) |
| 68 | } | 72 | } |
| 69 | , commandStyle = OnlyCommands | 73 | , commandStyle = OnlyCommands |
| @@ -94,27 +98,38 @@ main = do | |||
| 94 | } | 98 | } |
| 95 | void $ runShell description haskelineBackend (def :: GameState) | 99 | void $ runShell description haskelineBackend (def :: GameState) |
| 96 | 100 | ||
| 97 | stateOutline :: GameState -> String | 101 | stateOutline :: Sh GameState String |
| 98 | stateOutline st | 102 | stateOutline = do |
| 99 | | null (st ^. priorityQueue) = "" | 103 | st <- get |
| 100 | | otherwise = unlines . map table $ st ^. gRounds' | 104 | case st of |
| 105 | st | null (st ^. priorityQueue) -> return "" | ||
| 106 | | otherwise -> unlines <$> mapM table (st ^. gRounds') | ||
| 101 | where | 107 | where |
| 102 | table round = layoutTableToString rowGs (Just (roundStr round : factions, repeat def)) (repeat def) unicodeBoldHeaderS | 108 | table :: Int -> Sh GameState String |
| 103 | where | 109 | table round = do |
| 104 | pQueue = filter (\(v, _) -> round == v ^. seqRound . _Wrapped)$ st ^. priorityQueue | 110 | factions <- map (view faction') <$> use inhabitedFactions |
| 111 | st <- get | ||
| 112 | let | ||
| 113 | roundStr 0 = "Current Round" | ||
| 114 | roundStr 1 = "Next Round" | ||
| 115 | roundStr n = show n ++ " Rounds later" | ||
| 116 | |||
| 117 | pQueue = filter (\(v, _) -> round == v ^. seqRound . _Wrapped) $ st ^. priorityQueue | ||
| 105 | protoRows = groupBy ((==) `on` fst) pQueue | 118 | protoRows = groupBy ((==) `on` fst) pQueue |
| 106 | faction id = fromJust $ view eFaction <$> Map.lookup id (st ^. gEntities) | 119 | faction id = fromJust $ view eFaction <$> Map.lookup id (st ^. gEntities) |
| 107 | factionIndex id = fromJust $ elemIndex (view faction' $ faction id) factions | 120 | |
| 108 | rowGs = do | 121 | rowGs :: Sh GameState [RowGroup] |
| 109 | rowGroup'@((seq, _):_) <- protoRows | 122 | rowGs = runListT $ do |
| 123 | rowGroup'@((seq, _):_) <- ListT $ return protoRows | ||
| 110 | let | 124 | let |
| 111 | rowGroup = map snd rowGroup' | 125 | rowGroup = map snd rowGroup' |
| 112 | factionColumn i = [evalState ?? st $ toName x | x <- rowGroup, factionIndex x == i ] | 126 | factionColumn i = runListT $ do |
| 113 | return . colsAllG top $ [maybe "" show $ view seqVal seq] : map factionColumn [0..(length factions - 1)] | 127 | x <- ListT $ return rowGroup |
| 114 | roundStr 0 = "Current Round" | 128 | guard $ factionIndex x == i |
| 115 | roundStr 1 = "Next Round" | 129 | toDesc x |
| 116 | roundStr n = show n ++ " Rounds later" | 130 | factionIndex id = fromJust $ elemIndex (view faction' $ faction id) factions |
| 117 | factions = map (view faction') $ st ^. inhabitedFactions | 131 | colsAllG top . ([maybe "" show $ view seqVal seq] :) <$> mapM factionColumn [0..(length factions - 1)] |
| 132 | layoutTableToString <$> rowGs <*> pure (Just (roundStr round : factions, repeat def)) <*> pure (repeat def) <*> pure unicodeBoldHeaderS | ||
| 118 | 133 | ||
| 119 | focusNotes :: GameState -> String | 134 | focusNotes :: GameState -> String |
| 120 | focusNotes = maybe "" (unlines . map dotted) . preview (gFocus' . eNotes) | 135 | focusNotes = maybe "" (unlines . map dotted) . preview (gFocus' . eNotes) |
| @@ -125,6 +140,27 @@ focusNotes = maybe "" (unlines . map dotted) . preview (gFocus' . eNotes) | |||
| 125 | | fstL : tailL <- lines str = " • " ++ fstL ++ "\n" ++ unlines (map (" " ++ ) tailL) | 140 | | fstL : tailL <- lines str = " • " ++ fstL ++ "\n" ++ unlines (map (" " ++ ) tailL) |
| 126 | | otherwise = "" | 141 | | otherwise = "" |
| 127 | 142 | ||
| 143 | stateMaintenance :: Sh GameState () | ||
| 144 | stateMaintenance = do | ||
| 145 | void . runMaybeT $ do | ||
| 146 | focusId <- MaybeT $ use gFocus | ||
| 147 | name <- lift $ toName focusId | ||
| 148 | let | ||
| 149 | lStats :: Traversal' GameState Stats | ||
| 150 | lStats = gEntities . ix focusId . eStats | ||
| 151 | evalF formula = do | ||
| 152 | stats <- MaybeT $ preuse lStats | ||
| 153 | (nStats, x) <- (evalFormula name :: Stats -> FormulaM Stats a -> MaybeT (Sh GameState) (Stats, a)) stats formula | ||
| 154 | lStats .= nStats | ||
| 155 | return x | ||
| 156 | isDead <- evalF =<< MaybeT (preuse $ lStats . sDead) | ||
| 157 | isUnconscious <- evalF =<< MaybeT (preuse $ lStats . sUnconscious) | ||
| 158 | guard $ isDead || isUnconscious | ||
| 159 | when isDead . lift . shellPutStrLn $ name ++ " died" | ||
| 160 | when isUnconscious . lift . shellPutStrLn $ name ++ " is unconscious" | ||
| 161 | gFocus' . eSeqVal .= Nothing | ||
| 162 | gFocus .= Nothing | ||
| 163 | |||
| 128 | -- Query state | 164 | -- Query state |
| 129 | listFactions, listEntities :: Sh GameState () | 165 | listFactions, listEntities :: Sh GameState () |
| 130 | listFactions = use inhabitedFactions >>= mapM_ (shellPutStrLn . view faction') | 166 | listFactions = use inhabitedFactions >>= mapM_ (shellPutStrLn . view faction') |
| @@ -259,11 +295,12 @@ doShock dmg efLens = withFocus $ \focusId -> do | |||
| 259 | name <- toName focusId | 295 | name <- toName focusId |
| 260 | void . runMaybeT $ do | 296 | void . runMaybeT $ do |
| 261 | cripple <- MaybeT . preuse $ lStats . efLens | 297 | cripple <- MaybeT . preuse $ lStats . efLens |
| 262 | let evalF formula = do | 298 | let -- evalF formula = do |
| 263 | stats <- MaybeT $ preuse lStats | 299 | -- stats <- MaybeT $ preuse lStats |
| 264 | (nStats, x) <- (evalFormula name :: Stats -> FormulaM Stats a -> MaybeT (Sh GameState) (Stats, a)) stats formula | 300 | -- (nStats, x) <- (evalFormula name :: Stats -> FormulaM Stats a -> MaybeT (Sh GameState) (Stats, a)) stats formula |
| 265 | lStats .= nStats | 301 | -- lStats .= nStats |
| 266 | return x | 302 | -- return x |
| 303 | evalF = MaybeT . focusState lStats . evalFormula' name | ||
| 267 | cVar cLens = evalF =<< MaybeT (preuse $ lStats . (cripple ^. cLens)) | 304 | cVar cLens = evalF =<< MaybeT (preuse $ lStats . (cripple ^. cLens)) |
| 268 | bar <- cVar seBar | 305 | bar <- cVar seBar |
| 269 | val <- cVar seVal | 306 | val <- cVar seVal |
