diff options
author | Gregor Kleen <gkleen@yggdrasil.li> | 2016-06-04 18:06:36 +0200 |
---|---|---|
committer | Gregor Kleen <gkleen@yggdrasil.li> | 2016-06-04 18:06:36 +0200 |
commit | fbaf4d9da45f714c32f410d3b5785fd06504325a (patch) | |
tree | 053712472ca7e73f70a43c66b8d4b718591c8584 /src/Sequence | |
parent | 048779ac250b0cb463839edd8f46d9785fb3f9e5 (diff) | |
download | 2017-01-16_17:13:37-fbaf4d9da45f714c32f410d3b5785fd06504325a.tar 2017-01-16_17:13:37-fbaf4d9da45f714c32f410d3b5785fd06504325a.tar.gz 2017-01-16_17:13:37-fbaf4d9da45f714c32f410d3b5785fd06504325a.tar.bz2 2017-01-16_17:13:37-fbaf4d9da45f714c32f410d3b5785fd06504325a.tar.xz 2017-01-16_17:13:37-fbaf4d9da45f714c32f410d3b5785fd06504325a.zip |
archetypes & cleanup
Diffstat (limited to 'src/Sequence')
-rw-r--r-- | src/Sequence/Contact/Archetypes.hs | 90 | ||||
-rw-r--r-- | src/Sequence/Contact/Types.hs | 12 | ||||
-rw-r--r-- | src/Sequence/Types.hs | 40 | ||||
-rw-r--r-- | src/Sequence/Utils.hs | 30 |
4 files changed, 154 insertions, 18 deletions
diff --git a/src/Sequence/Contact/Archetypes.hs b/src/Sequence/Contact/Archetypes.hs new file mode 100644 index 0000000..94addce --- /dev/null +++ b/src/Sequence/Contact/Archetypes.hs | |||
@@ -0,0 +1,90 @@ | |||
1 | {-# LANGUAGE OverloadedStrings, OverloadedLists, ViewPatterns, MultiParamTypeClasses #-} | ||
2 | |||
3 | module Sequence.Contact.Archetypes where | ||
4 | |||
5 | import Control.Lens | ||
6 | |||
7 | import Sequence.Contact.Types | ||
8 | import Sequence.Formula | ||
9 | |||
10 | import Sequence.Types | ||
11 | import Sequence.Utils | ||
12 | |||
13 | import Data.Map (Map) | ||
14 | import qualified Data.Map as Map | ||
15 | |||
16 | import Data.Default | ||
17 | |||
18 | import Data.List | ||
19 | |||
20 | import Data.CaseInsensitive (CI) | ||
21 | import qualified Data.CaseInsensitive as CI | ||
22 | |||
23 | |||
24 | instance Completion Entity GameState where | ||
25 | completableLabel _ = "<archetype>" | ||
26 | complete _ _ (CI.foldCase -> prefix) = return . filter (prefix `isPrefixOf`) . map CI.foldedCase $ Map.keys archetypes | ||
27 | |||
28 | instance Argument Entity GameState where | ||
29 | arg = return . fmap (flip (set eStats) def) . flip Map.lookup archetypes . CI.mk | ||
30 | |||
31 | archetypes :: Map (CI String) Stats | ||
32 | archetypes = [ ("Mensch", human) | ||
33 | , ("Kind von Mu", childOfMu) | ||
34 | ] | ||
35 | |||
36 | |||
37 | human = Humanoid | ||
38 | { _sAStrength = vStrength | ||
39 | , _sAEndurance = vEndurance | ||
40 | , _sAMass = vMass | ||
41 | , _sAReflexes = vReflexes | ||
42 | , _sAMobility = vMobility | ||
43 | , _sADexterity = vDexterity | ||
44 | , _sAIntelligence = vIntelligence | ||
45 | , _sACharisma = vCharisma | ||
46 | , _sAPerception = vPerception | ||
47 | , _sAWillpower = vWillpower | ||
48 | |||
49 | , _sSArchaicRanged = 20 + vStrength `quot'` 2 + vDexterity `quot'` 2 + vPerception | ||
50 | , _sSFirearms = 15 + vMobility `quot'` 2 + vDexterity `quot'` 2 + vPerception | ||
51 | , _sSHeavyWeapons = vStrength `quot'` 2 + vPerception | ||
52 | , _sSEnergyWeapons = 10 + vMobility `quot'` 2 + vDexterity `quot'` 2 + vPerception | ||
53 | , _sSUnarmedMelee = 30 + vReflexes + vMobility `quot'` 2 | ||
54 | , _sSArmedMelee = 25 + vReflexes + vMobility `quot'` 2 | ||
55 | , _sSThrownWeapons = 25 + vMobility `quot'` 2 + vPerception | ||
56 | , _sSStealth = 5 + vMobility + vDexterity | ||
57 | , _sSThievery = 5 + vDexterity * 2 + vIntelligence | ||
58 | , _sSLockpicking = vDexterity + vIntelligence | ||
59 | , _sSTrapping = vDexterity + vIntelligence + vPerception `quot'` 2 | ||
60 | , _sSSciences = 10 + vIntelligence * 4 | ||
61 | , _sSFirstAid = 10 + vDexterity + vIntelligence * 2 | ||
62 | , _sSMedicine = 5 + vDexterity `quot'` 2 + vIntelligence * 3 | ||
63 | , _sSHumanities = 20 + vIntelligence * 3 | ||
64 | , _sSEngineering = 5 + vDexterity + vIntelligence * 2 | ||
65 | , _sSCraft = 25 + vDexterity * 2 | ||
66 | , _sSInterface = 5 + vIntelligence * 2 + vPerception `quot'` 2 | ||
67 | , _sSSpeech = vIntelligence + vCharisma * 2 + vWillpower `quot'` 2 | ||
68 | , _sSLeadership = 5 + vCharisma * 3 + vWillpower | ||
69 | , _sSHomeEconomics = 25 + vIntelligence | ||
70 | , _sSSurvival = 30 + vReflexes + vMobility + vIntelligence + vPerception + vWillpower `quot'` 2 | ||
71 | , _sSMotorcycle = vReflexes * 2 + vMobility + vWillpower | ||
72 | , _sSWheeled = 15 + vReflexes + vWillpower | ||
73 | , _sSHovercraft = 10 + vReflexes + vWillpower | ||
74 | , _sSAircraft = vReflexes + vWillpower | ||
75 | , _sSSpacecraft = vReflexes + vIntelligence `quot'` 2 + vPerception `quot'` 2 | ||
76 | , _sSWatercraft = 20 + vReflexes `quot'` 2 + vPerception `quot'` 2 | ||
77 | , _sSTracked = 15 + vReflexes + vPerception | ||
78 | , _sSExoskeleton = 30 + vReflexes + vMobility * 2 + vPerception | ||
79 | |||
80 | , _sMaxVitality = vEndurance * 2 + vMass * 2 + vWillpower + 10 | ||
81 | , _sSeqVal = vReflexes * 2 + vMobility + vPerception + d 10 | ||
82 | , _sPainTolerance = vMass `quot'` 2 + vWillpower | ||
83 | , _sFatigueTolerance = vWillpower `quot'` 2 + vEndurance | ||
84 | } | ||
85 | |||
86 | childOfMu = human | ||
87 | & sAStrength +~ 2 | ||
88 | & sAReflexes +~ 5 | ||
89 | & sAMobility +~ 5 | ||
90 | & sAPerception +~ 2 | ||
diff --git a/src/Sequence/Contact/Types.hs b/src/Sequence/Contact/Types.hs index b63b369..d3ca31e 100644 --- a/src/Sequence/Contact/Types.hs +++ b/src/Sequence/Contact/Types.hs | |||
@@ -38,7 +38,7 @@ data Stats = Prop | |||
38 | , _sSHumanities | 38 | , _sSHumanities |
39 | , _sSEngineering | 39 | , _sSEngineering |
40 | , _sSCraft | 40 | , _sSCraft |
41 | , _sSInterfacte | 41 | , _sSInterface |
42 | , _sSSpeech | 42 | , _sSSpeech |
43 | , _sSLeadership | 43 | , _sSLeadership |
44 | , _sSHomeEconomics | 44 | , _sSHomeEconomics |
@@ -108,3 +108,13 @@ makeLenses ''Stats | |||
108 | instance Default Stats where | 108 | instance Default Stats where |
109 | def = Prop | 109 | def = Prop |
110 | 110 | ||
111 | vStrength = val sAStrength "Stärke?" True | ||
112 | vEndurance = val sAEndurance "Ausdauer?" True | ||
113 | vMass = val sAMass "Masse?" True | ||
114 | vReflexes = val sAReflexes "Reflexe?" True | ||
115 | vMobility = val sAMobility "Beweglichkeit?" True | ||
116 | vDexterity = val sADexterity "Geschicklichkeit?" True | ||
117 | vIntelligence = val sAIntelligence "Intelligenz?" True | ||
118 | vCharisma = val sACharisma "Charisma?" True | ||
119 | vPerception = val sAPerception "Wahrnehmung?" True | ||
120 | vWillpower = val sAWillpower "Entschlossenheit?" True | ||
diff --git a/src/Sequence/Types.hs b/src/Sequence/Types.hs index 4370618..c47136c 100644 --- a/src/Sequence/Types.hs +++ b/src/Sequence/Types.hs | |||
@@ -1,13 +1,13 @@ | |||
1 | {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances, ViewPatterns, OverloadedStrings, TemplateHaskell, GeneralizedNewtypeDeriving #-} | 1 | {-# LANGUAGE FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, TypeSynonymInstances, ViewPatterns, OverloadedStrings, TemplateHaskell, GeneralizedNewtypeDeriving #-} |
2 | 2 | ||
3 | module Sequence.Types | 3 | module Sequence.Types |
4 | ( GameState(..), gEntities, gEntityNames, gFocus | 4 | ( GameState, gEntities, gEntityNames, gFocus, gNextId' |
5 | , Faction, faction, faction' | 5 | , Faction, faction, faction' |
6 | , SeqVal(..), seqVal | 6 | , SeqVal(..), seqVal |
7 | , Entity(..), eFaction, eSeqVal | 7 | , Entity(..), eFaction, eSeqVal, eStats |
8 | , EntityName(..), entityName | 8 | , EntityName(..), entityName |
9 | , EntityIdentifier(..), entityId | 9 | , EntityIdentifier(..), entityId, entityId' |
10 | , inhabitedFactions, priorityQueue, tip | 10 | , inhabitedFactions, priorityQueue, tip, insertEntity |
11 | ) where | 11 | ) where |
12 | 12 | ||
13 | import Control.Lens | 13 | import Control.Lens |
@@ -24,13 +24,16 @@ import qualified Data.Map.Strict as Map | |||
24 | import Data.Bimap (Bimap) | 24 | import Data.Bimap (Bimap) |
25 | import qualified Data.Bimap as Bimap | 25 | import qualified Data.Bimap as Bimap |
26 | 26 | ||
27 | import Control.Monad.State | ||
28 | |||
27 | import Data.List | 29 | import Data.List |
28 | import Data.Maybe | 30 | import Data.Maybe |
29 | import Data.Tuple | 31 | import Data.Tuple |
30 | import Data.Ord | 32 | import Data.Ord |
31 | 33 | ||
32 | import Sequence.Contact.Types | 34 | import Sequence.Contact.Types |
33 | 35 | ||
36 | import Text.Read (readMaybe) | ||
34 | 37 | ||
35 | newtype Faction = Faction { _lFaction :: Maybe (CI String) } | 38 | newtype Faction = Faction { _lFaction :: Maybe (CI String) } |
36 | deriving (Show, Eq, Ord) | 39 | deriving (Show, Eq, Ord) |
@@ -75,16 +78,24 @@ instance Default Entity where | |||
75 | 78 | ||
76 | newtype EntityName = EntityName { _entityName :: CI String } | 79 | newtype EntityName = EntityName { _entityName :: CI String } |
77 | deriving (Show, Eq, Ord) | 80 | deriving (Show, Eq, Ord) |
78 | makeLenses ''EntityName | 81 | |
82 | entityName :: Iso' String EntityName | ||
83 | entityName = iso (EntityName . CI.mk) (CI.original . _entityName) | ||
79 | 84 | ||
80 | newtype EntityIdentifier = EntityIdentifier { _entityId :: Integer } | 85 | newtype EntityIdentifier = EntityIdentifier { _entityId :: Integer } |
81 | deriving (Show, Eq, Ord) | 86 | deriving (Show, Eq, Ord, Enum) |
82 | makeLenses ''EntityIdentifier | 87 | |
88 | entityId :: Iso' Integer EntityIdentifier | ||
89 | entityId = iso EntityIdentifier _entityId | ||
90 | |||
91 | entityId' :: Prism' String EntityIdentifier | ||
92 | entityId' = prism' (show . _entityId) (fmap EntityIdentifier . readMaybe) | ||
83 | 93 | ||
84 | data GameState = GameState | 94 | data GameState = GameState |
85 | { _gEntities :: Map EntityIdentifier Entity | 95 | { _gEntities :: Map EntityIdentifier Entity |
86 | , _gEntityNames :: Bimap EntityIdentifier EntityName | 96 | , _gEntityNames :: Bimap EntityIdentifier EntityName |
87 | , _gFocus :: Maybe EntityIdentifier | 97 | , _gFocus :: Maybe EntityIdentifier |
98 | , _gNextId :: EntityIdentifier | ||
88 | } | 99 | } |
89 | makeLenses ''GameState | 100 | makeLenses ''GameState |
90 | 101 | ||
@@ -93,6 +104,7 @@ instance Default GameState where | |||
93 | { _gEntities = def | 104 | { _gEntities = def |
94 | , _gEntityNames = Bimap.empty | 105 | , _gEntityNames = Bimap.empty |
95 | , _gFocus = Nothing | 106 | , _gFocus = Nothing |
107 | , _gNextId = toEnum 0 | ||
96 | } | 108 | } |
97 | 109 | ||
98 | inhabitedFactions :: Getter GameState [Faction] | 110 | inhabitedFactions :: Getter GameState [Faction] |
@@ -107,3 +119,13 @@ priorityQueue = to priorityQueue' | |||
107 | 119 | ||
108 | tip :: Getter GameState (Maybe EntityIdentifier) | 120 | tip :: Getter GameState (Maybe EntityIdentifier) |
109 | tip = priorityQueue . to (fmap snd . listToMaybe) | 121 | tip = priorityQueue . to (fmap snd . listToMaybe) |
122 | |||
123 | gNextId' :: Getter GameState EntityIdentifier | ||
124 | gNextId' = gNextId | ||
125 | |||
126 | insertEntity :: Entity -> GameState -> GameState | ||
127 | insertEntity entity = execState $ do | ||
128 | identifier <- use gNextId | ||
129 | gEntities . at identifier ?= entity | ||
130 | gNextId %= succ | ||
131 | |||
diff --git a/src/Sequence/Utils.hs b/src/Sequence/Utils.hs index 274a69d..9fc0ab2 100644 --- a/src/Sequence/Utils.hs +++ b/src/Sequence/Utils.hs | |||
@@ -2,7 +2,9 @@ | |||
2 | 2 | ||
3 | module Sequence.Utils | 3 | module Sequence.Utils |
4 | ( withArg, withFocus | 4 | ( withArg, withFocus |
5 | , toName, fromName | 5 | , toName |
6 | , Argument(..) | ||
7 | , Completion(..) | ||
6 | , module Sequence.Utils.Ask | 8 | , module Sequence.Utils.Ask |
7 | ) where | 9 | ) where |
8 | 10 | ||
@@ -10,6 +12,7 @@ import Sequence.Types | |||
10 | 12 | ||
11 | import Control.Monad.State.Strict | 13 | import Control.Monad.State.Strict |
12 | 14 | ||
15 | import Control.Applicative | ||
13 | import Control.Monad | 16 | import Control.Monad |
14 | import Control.Lens | 17 | import Control.Lens |
15 | 18 | ||
@@ -28,6 +31,7 @@ import Data.Maybe | |||
28 | import Text.Read (readMaybe) | 31 | import Text.Read (readMaybe) |
29 | 32 | ||
30 | import Data.List | 33 | import Data.List |
34 | import Data.Bool | ||
31 | 35 | ||
32 | import System.Console.Shell | 36 | import System.Console.Shell |
33 | import System.Console.Shell.ShellMonad | 37 | import System.Console.Shell.ShellMonad |
@@ -49,20 +53,30 @@ withFocus f = use gFocus >>= \focus -> case focus of | |||
49 | Just id -> f id | 53 | Just id -> f id |
50 | 54 | ||
51 | unaligned = view faction' def | 55 | unaligned = view faction' def |
52 | |||
53 | toName :: MonadState GameState m => EntityIdentifier -> m String | ||
54 | toName id = fromMaybe (show $ id ^. entityId) . fmap (CI.original . view entityName) . Bimap.lookup id <$> use gEntityNames | ||
55 | 56 | ||
56 | fromName :: MonadState GameState m => String -> m (Maybe EntityIdentifier) | 57 | toName :: MonadState GameState m => EntityIdentifier -> m String |
57 | fromName (readMaybe -> (Just (EntityIdentifier -> n))) = (n <$) . guard . Map.member n <$> use gEntities | 58 | toName ident = do |
58 | fromName (EntityName . CI.mk -> name) = Bimap.lookupR name <$> use gEntityNames | 59 | let number = review entityId' ident |
60 | isShadowed <- uses gEntityNames . Bimap.memberR $ view entityName number | ||
61 | let number' = bool id ('#':) isShadowed $ number | ||
62 | fromMaybe number' . fmap (review entityName) . Bimap.lookup ident <$> use gEntityNames | ||
59 | 63 | ||
60 | instance Completion EntityIdentifier GameState where | 64 | instance Completion EntityIdentifier GameState where |
61 | completableLabel _ = "<entity>" | 65 | completableLabel _ = "<entity>" |
62 | complete _ st prefix = return . filter ((isPrefixOf `on` CI.foldCase) prefix) . map ((evalState ?? st) . toName) . Map.keys $ st ^. gEntities | 66 | complete _ st prefix = return . filter ((isPrefixOf `on` CI.foldCase) prefix) . map ((evalState ?? st) . toName) . Map.keys $ st ^. gEntities |
63 | 67 | ||
64 | instance Argument EntityIdentifier GameState where | 68 | instance Argument EntityIdentifier GameState where |
65 | arg = fromName | 69 | arg = \str -> do |
70 | fromForcedIdR <- fromForcedId str | ||
71 | fromNameR <- fromName str | ||
72 | fromIdR <- fromId str | ||
73 | return $ fromForcedIdR <|> fromNameR <|> fromIdR | ||
74 | where | ||
75 | fromName (EntityName . CI.mk -> name) = Bimap.lookupR name <$> use gEntityNames | ||
76 | fromId (preview entityId' -> Just n) = (n <$) . guard . Map.member n <$> use gEntities | ||
77 | fromId _ = return Nothing | ||
78 | fromForcedId ('#':str) = fromId str | ||
79 | fromForcedId _ = return Nothing | ||
66 | 80 | ||
67 | instance Completion Faction GameState where | 81 | instance Completion Faction GameState where |
68 | completableLabel _ = "<faction>" | 82 | completableLabel _ = "<faction>" |