module CharMap where import qualified Data.Map as M import qualified Data.Set as S import Data.Char import Data.Tuple import Types import Spell.Enum import Poison.Enum data CharUse = CharControl Control | IngredientFor SpellEnum Int | Poison PoisonEnum deriving (Show, Eq, Ord) data Control = Movement Direction | Inventory | Help | Quit | Wait deriving (Show, Eq, Ord) -- Every character that has special meaning in the game is kept here -- in one place. charSet :: S.Set (Char, CharUse) charSet = S.fromList $ concat -- movement [ use 'h' $ CharControl (Movement DLeft) , use 'j' $ CharControl (Movement DDown) , use 'k' $ CharControl (Movement DUp) , use 'l' $ CharControl (Movement DRight) , use 'd' $ CharControl (Movement DDive) -- specials , use 'i' $ CharControl Inventory , use '?' $ CharControl Help , use 'Q' $ CharControl Quit , use '.' $ CharControl Wait -- spell ingredients , ingredient 'v' SpellVomit , ingredient 'p' SpellWhiteout , ingredient 'b' SpellBerzerk , ingredients "re" SpellReverse , ingredients "new" SpellNew , ingredients "gen" SpellGenocide , ingredients "ogo" SpellDream , ingredients "ws" SpellWish -- poisons , poison 'm' PoisonMold , poison 'c' PoisonStunner , poison 'f' PoisonFungus ] where use c u = [(c, u)] ingredient c s = ingredient' 0 c s ingredient' n c s = bothcases c (IngredientFor s n) ingredients cs s = concatMap (\(c, n) -> ingredient' n c s) (zip cs [0..]) poison c = bothcases c . Poison bothcases c v = [(toLower c, v), (toUpper c, v)] charMap :: M.Map Char CharUse charMap = M.fromList $ S.toList charSet charUseMap :: M.Map CharUse Char charUseMap = M.fromList $ map swap $ S.toList charSet