diff options
Diffstat (limited to 'src/Sequence/Utils.hs')
-rw-r--r-- | src/Sequence/Utils.hs | 24 |
1 files changed, 20 insertions, 4 deletions
diff --git a/src/Sequence/Utils.hs b/src/Sequence/Utils.hs index 7d28b83..aa92081 100644 --- a/src/Sequence/Utils.hs +++ b/src/Sequence/Utils.hs | |||
@@ -1,7 +1,7 @@ | |||
1 | {-# LANGUAGE ViewPatterns, FlexibleContexts, MultiParamTypeClasses #-} | 1 | {-# LANGUAGE ViewPatterns, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances #-} |
2 | 2 | ||
3 | module Sequence.Utils | 3 | module Sequence.Utils |
4 | ( toName, fromName | 4 | ( withArg, toName, fromName |
5 | ) where | 5 | ) where |
6 | 6 | ||
7 | import Sequence.Types | 7 | import Sequence.Types |
@@ -22,11 +22,21 @@ import qualified Data.Map.Strict as Map | |||
22 | import Data.Function | 22 | import Data.Function |
23 | import Data.Default | 23 | import Data.Default |
24 | import Data.Maybe | 24 | import Data.Maybe |
25 | import Text.Read | 25 | import Text.Read (readMaybe) |
26 | 26 | ||
27 | import Data.List | 27 | import Data.List |
28 | 28 | ||
29 | import System.Console.Shell | 29 | import System.Console.Shell |
30 | import System.Console.Shell.ShellMonad | ||
31 | |||
32 | |||
33 | class Argument a st | a -> st where | ||
34 | arg :: String -> Sh st (Maybe a) | ||
35 | |||
36 | withArg :: Argument a st => (a -> Sh st ()) -> (Completable a -> Sh st ()) | ||
37 | withArg f (Completable str) = arg str >>= \a -> case a of | ||
38 | Nothing -> shellPutErrLn $ "Could not parse ‘" ++ str ++ "’" | ||
39 | Just a -> f a | ||
30 | 40 | ||
31 | unaligned = view faction' def | 41 | unaligned = view faction' def |
32 | 42 | ||
@@ -34,13 +44,19 @@ toName :: MonadState GameState m => EntityIdentifier -> m String | |||
34 | toName id = fromMaybe (show $ id ^. entityId) . fmap (CI.original . view entityName) . Bimap.lookup id <$> use gEntityNames | 44 | toName id = fromMaybe (show $ id ^. entityId) . fmap (CI.original . view entityName) . Bimap.lookup id <$> use gEntityNames |
35 | 45 | ||
36 | fromName :: MonadState GameState m => String -> m (Maybe EntityIdentifier) | 46 | fromName :: MonadState GameState m => String -> m (Maybe EntityIdentifier) |
37 | fromName (readMaybe -> n@(Just _)) = return $ EntityIdentifier <$> n | 47 | fromName (readMaybe -> (Just (EntityIdentifier -> n))) = (n <$) . guard . Map.member n <$> use gEntities |
38 | fromName (EntityName . CI.mk -> name) = Bimap.lookupR name <$> use gEntityNames | 48 | fromName (EntityName . CI.mk -> name) = Bimap.lookupR name <$> use gEntityNames |
39 | 49 | ||
40 | instance Completion EntityIdentifier GameState where | 50 | instance Completion EntityIdentifier GameState where |
41 | completableLabel _ = "<entity>" | 51 | completableLabel _ = "<entity>" |
42 | complete _ st prefix = return . filter ((isPrefixOf `on` CI.foldCase) prefix) . map ((evalState ?? st) . toName) . Map.keys $ st ^. gEntities | 52 | complete _ st prefix = return . filter ((isPrefixOf `on` CI.foldCase) prefix) . map ((evalState ?? st) . toName) . Map.keys $ st ^. gEntities |
43 | 53 | ||
54 | instance Argument EntityIdentifier GameState where | ||
55 | arg = fromName | ||
56 | |||
44 | instance Completion Faction GameState where | 57 | instance Completion Faction GameState where |
45 | completableLabel _ = "<faction>" | 58 | completableLabel _ = "<faction>" |
46 | complete _ st prefix = return . filter ((isPrefixOf `on` CI.foldCase) prefix) . nub . sort $ unaligned : map (view faction') (st ^. inhabitedFactions) | 59 | complete _ st prefix = return . filter ((isPrefixOf `on` CI.foldCase) prefix) . nub . sort $ unaligned : map (view faction') (st ^. inhabitedFactions) |
60 | |||
61 | instance Argument Faction GameState where | ||
62 | arg = return . Just . flip (set faction') def | ||