module Player.Consume where import Control.Monad.State.Strict import Data.Char import qualified Data.CaseInsensitive as CI import qualified Data.Map as M import Types import Status import Unicode import World import Spell import Rand import Player import Time isEdible :: Char -> Bool isEdible c = isPunctuation c || isSymbol c || isLetter c playerConsume :: M NextStep -> Char -> M NextStep playerConsume cont = handle where handle '!' = do immediateConsume showMessage "Yum! You grow longer.." modifyPlayer $ \p -> p { playerLen = succ (playerLen p) } cont handle '.' = do immediateConsume roll <- randFrom [1..10 :: Int] if roll > 6 then do p' <- teachRandomSpell =<< gets player modifyPlayer $ \_ -> p' else showMessage "You try to remember a spell, but fail. (i:Inventory)" cont handle ',' = powerup cont handle '\'' = powerup cont handle c | isPunctuation c || isSymbol c = do showMessage $ "You turn up your nose at eating the " ++ unicodeCharString c noswallow handle c | isEdible c = do m <- gets poisons case M.lookup (CI.mk c) m of Just poison -> do immediateConsume poison c cont Nothing -> do swallowIngredient c cont handle _ = noswallow noswallow = do modifyPlayer $ \p -> p { playerSwallowing = Nothing } cont immediateConsume :: M () immediateConsume = do modifyPlayer $ \p -> p { playerSwallowing = Nothing } p <- gets player writeWorld (playerHead p) ' ' swallowIngredient :: Char -> M NextStep -> M NextStep swallowIngredient c cont = do p <- gets player unless (spellCaster p) $ showMessage $ "Swallowing " ++ unicodeCharDesc c modifyPlayer $ \_ -> p { playerSwallowing = Just c } cont powerup :: M NextStep -> M NextStep powerup cont = do immediateConsume duration <- randFrom [3..10 :: Int] showMessage "Yum! You feel energetic!" modifyPlayer $ \p -> p { playerEnergized = True } delayAction duration cont $ do p <- gets player when (playerEnergized p && not (playerBerzerk p)) $ do showMessage "The burst of energy fades away.." modifyPlayer $ \pl -> pl { playerEnergized = False }