summaryrefslogtreecommitdiff
path: root/src/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Main.hs')
-rw-r--r--src/Main.hs77
1 files changed, 76 insertions, 1 deletions
diff --git a/src/Main.hs b/src/Main.hs
index e9e1deb..639673c 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -1,2 +1,77 @@
1{-# LANGUAGE ViewPatterns #-}
2
3import Control.Monad
4
5import Control.Lens
6
7import System.Console.Shell
8import System.Console.Shell.ShellMonad
9import System.Console.Shell.Backend.Haskeline
10
11import System.Environment.XDG.BaseDir
12import System.FilePath
13import System.Directory
14
15import Data.Default
16import Data.CaseInsensitive (CI)
17import qualified Data.CaseInsensitive
18
19import Data.Map.Strict (Map)
20import qualified Data.Map.Strict as Map
21
22import Data.List
23import Data.Maybe
24
25import Data.Function
26
27import Control.Monad.State.Strict
28
29import Sequence.Types
30import Sequence.Utils
31
32import Text.Layout.Table
33
1main :: IO () 34main :: IO ()
2main = undefined 35main = do
36 historyFile <- getUserCacheFile "sequence" "history"
37 createDirectoryIfMissing True $ takeDirectory historyFile
38 let
39 description = initialShellDescription
40 { historyFile = Just historyFile
41 , prompt = \st -> return $ maybe "" (++ " ") ((evalState ?? st) . toName . snd <$> (listToMaybe $ view priorityQueue st)) ++ "→ "
42 , beforePrompt = gets stateOutline >>= (\str -> if null str then return () else shellPutStrLn str)
43 , commandStyle = OnlyCommands
44 , shellCommands = [ exitCommand "exit"
45 , helpCommand "help"
46 , cmd "factions" listFactions "List all inhabited factions"
47 , cmd "members" listFaction "List all members of a faction"
48 , cmd "entities" listEntities "List all entities"
49 ]
50 }
51 void $ runShell description haskelineBackend (def :: GameState)
52
53stateOutline :: GameState -> String
54stateOutline st
55 | null pQueue = ""
56 | otherwise = layoutTableToString rowGs (Just ("" : factions, repeat def)) (repeat def) unicodeBoldHeaderS
57 where
58 factions = map (view faction') $ st ^. inhabitedFactions
59 pQueue = st ^. priorityQueue
60 protoRows = groupBy ((==) `on` fst) pQueue
61 faction id = fromJust $ view eFaction <$> Map.lookup id (st ^. gEntities)
62 factionIndex id = fromJust $ elemIndex (view faction' $ faction id) factions
63 rowGs = do
64 rowGroup'@((seqVal', _):_) <- protoRows
65 let
66 rowGroup = map snd rowGroup'
67 factionColumn i = [evalState ?? st $ toName x | x <- rowGroup, factionIndex x == i ]
68 return . colsAllG top $ [show (seqVal' ^. seqVal)] : map factionColumn [0..(length factions - 1)]
69
70listFaction :: Completable Faction -> Sh GameState ()
71listFaction (Completable (flip (set faction') def -> qFaction)) = use gEntities >>= mapM_ (shellPutStrLn <=< toName) . Map.keys . Map.filter ((==) qFaction . view eFaction)
72
73listFactions :: Sh GameState ()
74listFactions = use inhabitedFactions >>= mapM_ (shellPutStrLn . view faction')
75
76listEntities :: Sh GameState ()
77listEntities = use (gEntities . to Map.keys) >>= mapM_ (shellPutStrLn <=< toName)