{-# LANGUAGE TupleSections, FlexibleContexts, ConstraintKinds #-} {- This module is part of Antisplice. Copyleft (c) 2014 Marvin Cohrs All wrongs reversed. Sharing is an act of love, not crime. Please share Antisplice with everyone you like. Antisplice is free software: you can redistribute it and/or modify it under the terms of the GNU Affero General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. Antisplice is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more details. You should have received a copy of the GNU Affero General Public License along with Antisplice. If not, see . -} -- | Provides prototypes for common entities (rooms, objects, mobs). module Game.Antisplice.Prototypes where import Text.Chatty.Printer import Text.Chatty.Expansion import Text.Chatty.Extended.Printer import Control.Monad import Control.Monad.Error.Class import Data.Chatty.Atoms import Data.Chatty.Fail import Data.Chatty.AVL import Data.Chatty.Graph import Game.Antisplice.Monad import Game.Antisplice.Monad.Dungeon import Game.Antisplice.Monad.Vocab import Game.Antisplice.Rooms import Game.Antisplice.Events import Game.Antisplice.Errors import Text.Printf import Data.Char import Data.Text (pack,unpack) import Data.List -- | Construct a simple room from a title and a description. ctorRoom :: ChAtoms m => String -> String -> RoomT m () ctorRoom t d = do setRoomTitle t addRoomDesc d onAnnounce $ enomaskLn (Dull Magenta) =<< expand =<< drunken =<< getRoomTitle onLook $ do rs <- getRoomState mnomaskLn =<< expand =<< drunken =<< liftM (("%{D2;"++).(++"}")) getRoomDesc sequence_ $ avlInorder $ flip fmap (roomObjectsOf rs) $ \os -> objectTriggerOnAnnounceOf os -- | Construct a sign from a text and some attributes. ctorSign :: (ChAtoms m,MonadVocab m,MonadError SplErr m) => String -> [String] -> ObjectT m () ctorSign t as = do onRead $ enomaskLn (Vivid White) =<< expand =<< drunken t lookCountA <- newAtom putAtom lookCountA 0 onLook $ do c <- getAtom lookCountA mprintLn =<< drunken (case c :: Int of 0 -> "This is just a regular sign. There is nothing special about this one in particular." 1 -> "This REALLY is just a regular sign." 2 -> "Stop looking at me!" 3 -> "I'll call the police if you don't stop!" _ -> "You hear the sounds of an arriving police car. This is your end :P") when (c==4) $ throwError QuitError putAtom lookCountA (c+1) setObjectTitle "a sign" setObjectDesc "This is a sign with a text written on it." addObjectName "sign" addObjectName "caption" mapM_ (uncurry insertVocab) [("sign",Noun),("caption",Noun)] forM_ as addObjectAttr forM_ as $ uncurry insertVocab . (,Adj) -- | Construct a mob from a title, some names, a description and some attributes. ctorMob :: MonadVocab m => String -> [String] -> String -> [String] -> ObjectT m () ctorMob t ns d as = do let cap (c:cx) = toUpper c : cx cap [] = [] onLook $ mnomaskLn =<< expand =<< drunken d onRoomEnter $ mnomaskLn =<< expand =<< drunken (printf "%s has entered the room." $ cap t) onRoomLeave $ mnomaskLn =<< expand =<< drunken (printf "%s has left the room." $ cap t) onAnnounce $ mnomaskLn =<< expand =<< drunken (printf " %%{D6;%s is here.}" $ cap t) onDie $ do mnomaskLn =<< expand =<< drunken (printf "%s dies." t) void $ addRoomObject $ do setObjectTitle $ pack $ printf "corpse of %s" t setObjectDesc $ pack $ printf "Looks like %s is dead." t addDescSeg $ printf "The corpse of %s lies here." t insertVocab "corpse" Noun insertVocab "dead" Adj forM_ ("corpse":ns) addObjectName forM_ ("dead":as) addObjectAttr forM_ [Damagable, Mobile] addFeature setObjectTitle t setObjectDesc d forM_ ns addObjectName forM_ ns $ uncurry insertVocab . (,Noun) forM_ as addObjectAttr forM_ as $ uncurry insertVocab . (,Adj) -- | Construct a mob route from some room IDs and a time delay in milliseconds. ctorRoute :: (Monad m,Functor m) => [NodeId] -> Integer -> ObjectT m () ctorRoute rs d = do i <- fmap objectIdOf getObjectState setMobRoute rs let cmr :: Handler cmr = continueMobRoute i >> schedule d cmr onFirstSight $ schedule d cmr -- | Construct a room nesting object from a title, a description, some names, some attributes and the target room ID. ctorRoomNesting :: MonadVocab m => String -> String -> [String] -> [String] -> NodeId -> ObjectT m () ctorRoomNesting t d ns as r = do setObjectTitle t setObjectDesc d forM_ ns addObjectName forM_ ns $ uncurry insertVocab . (,Noun) forM_ as addObjectAttr forM_ as $ uncurry insertVocab . (,Adj) onEnter $ enterAndAnnounce r -- | Construct an acquirable object from a title, a description, some names and some attributes. ctorAcq :: MonadVocab m => String -> String -> [String] -> [String] -> ObjectT m () ctorAcq t d ns as = do setObjectTitle t setObjectDesc d forM_ ns addObjectName forM_ as addObjectAttr forM_ ns $ uncurry insertVocab . (,Noun) forM_ as $ uncurry insertVocab . (,Adj) onLook $ mprintLn d setObjectIsAcquirable True -- | Add a room descriptor object to the current room addRoomDesc :: ChAtoms m => String -> RoomT m ObjectId addRoomDesc = addRoomObject . addDescSeg