Safe Haskell | None |
---|
A huge pile of utility functions for building our dungeon.
- modifyRoomState :: MonadRoom m => (RoomState -> RoomState) -> m ()
- getRoomDesc :: (MonadRoom m, ChAtoms m) => m String
- getRoomTitle :: (MonadRoom m, IsText t) => m t
- setRoomTitle :: (MonadRoom m, IsText t) => t -> m ()
- markRoom :: MonadDungeon m => m ()
- enterRoom :: NodeId -> ChattyDungeonM Bool
- reenterCurrentRoom :: ChattyDungeonM ()
- enterAndAnnounce :: NodeId -> ChattyDungeonM ()
- changeRoom :: Direction -> ChattyDungeonM ()
- constructRoom :: MonadDungeon m => RoomT m a -> m NodeId
- establishWay :: MonadDungeon m => NodeId -> NodeId -> Direction -> PathState -> m ()
- addRoomObject :: (ChCounter m, MonadRoom m) => ObjectT m a -> m ObjectId
- removeRoomObject :: MonadRoom m => ObjectId -> m ObjectState
- insertRoomObject :: MonadRoom m => ObjectState -> m ()
- constructObject :: Monad m => ObjectT m a -> Maybe ObjectId -> KindId -> m ObjectState
- modifyObjectState :: MonadObject m => (ObjectState -> ObjectState) -> m ()
- setObjectDesc :: (MonadObject m, IsText t) => t -> m ()
- setObjectTitle :: (MonadObject m, IsText t) => t -> m ()
- addObjectName :: MonadObject m => String -> m ()
- addObjectAttr :: MonadObject m => String -> m ()
- setObjectIsMob :: MonadObject m => Bool -> m ()
- setObjectIsAcquirable :: MonadObject m => Bool -> m ()
- addFeature :: MonadObject m => Feature -> m ()
- addDescSeg :: (MonadObject m, ChAtoms m) => String -> m ()
- addEquipSlot :: MonadObject m => EquipKey -> m ()
- registerForm :: ChAtoms m => ObjectT m () -> m (Atom ObjectState)
- instanciateForm :: (ChAtoms m, MonadRoom m) => Atom ObjectState -> m ObjectId
- registerKind :: ChCounter m => m KindId
- setObjectKind :: MonadObject m => KindId -> m ()
- getObjectTitle :: (MonadObject m, IsText t) => m t
- getObjectDesc :: (MonadObject m, IsText t) => m t
- getObjectNames :: MonadObject m => m [String]
- matchObjectName :: MonadObject m => String -> m Bool
- getObjectIsMob :: (MonadObject m, Functor m) => m Bool
- getObjectIsAcquirable :: (MonadObject m, Functor m) => m Bool
- roomOfObject :: MonadDungeon m => ObjectId -> m [NodeId]
- setMobRoute :: MonadObject m => [NodeId] -> m ()
- continueMobRoute :: ObjectId -> Handler
- schedule :: (MonadDungeon m, ChClock m) => Integer -> Handler -> m ()
- subscribePlayer :: (MonadDungeon m, ChCounter m) => PlayerT m a -> m ()
- setPlayerRoom :: MonadPlayer m => NodeId -> m ()
- acquireObject :: ObjectId -> ChattyDungeonM ()
- dropObject :: ObjectId -> ChattyDungeonM ()
- equipObject :: (MonadPlayer m, MonadError SplErr m) => ObjectState -> m (Maybe ObjectState)
- equipObjectAt :: (MonadPlayer m, MonadError SplErr m) => EquipKey -> ObjectState -> m (Maybe ObjectState)
- getEquipment :: MonadPlayer m => EquipKey -> m (Maybe ObjectState)
- getCooldown :: MonadPlayer m => CooldownId -> m Bool
- setCooldown :: MonadPlayer m => CooldownId -> Bool -> m ()
- consumeAlcohol :: (ChPrinter m, ChRandom m, MonadPlayer m, MonadDungeon m, ChClock m) => Int -> m ()
- registerCurrency :: (ChCounter m, MonadDungeon m) => String -> String -> m CurrencyId
- getCurrency :: MonadPlayer m => CurrencyId -> m Int
- modifyCurrency :: MonadPlayer m => CurrencyId -> (Int -> Int) -> m ()
- damage :: DamageTarget -> Int -> ChattyDungeonM ()
- focusOpponent :: ObjectId -> ChattyDungeonM ()
- dealDamage :: Int -> ChattyDungeonM ()
- withRoom :: MonadDungeon m => NodeId -> RoomT m a -> m a
- withPlayer :: MonadDungeon m => PlayerId -> PlayerT (RoomT m) a -> m a
- withObject :: MonadDungeon m => ObjectId -> ObjectT (RoomT m) a -> m a
- guardRoom :: MonadDungeon m => NodeId -> m () -> m ()
- guardObject :: MonadDungeon m => ObjectId -> m () -> m ()
- guardObjectInRoom :: MonadDungeon m => ObjectId -> NodeId -> m () -> m ()
- guardObjectNotInRoom :: MonadDungeon m => ObjectId -> NodeId -> m () -> m ()
- guardKindInRoom :: MonadDungeon m => KindId -> NodeId -> m () -> m ()
- guardKindNotInRoom :: MonadDungeon m => KindId -> NodeId -> m () -> m ()
- drunken :: (ChRandom m, MonadPlayer m) => String -> m String
Room modification
modifyRoomState :: MonadRoom m => (RoomState -> RoomState) -> m ()Source
Modify the room state.
getRoomDesc :: (MonadRoom m, ChAtoms m) => m StringSource
Get the current room's description
getRoomTitle :: (MonadRoom m, IsText t) => m tSource
Get the current room's title
setRoomTitle :: (MonadRoom m, IsText t) => t -> m ()Source
Set the current room's description setRoomDesc :: (MonadRoom m,IsText t) => t -> m () setRoomDesc t = modifyRoomState $ s -> s{roomDescOf=toText t}
Set the current room's title
markRoom :: MonadDungeon m => m ()Source
Mark the current room as visited
Moving around
enterRoom :: NodeId -> ChattyDungeonM BoolSource
Enter the given room and trigger most events, but don't announce it. Result tells whether this room is visited the first time.
reenterCurrentRoom :: ChattyDungeonM ()Source
Reenter the current room and trigger all events (but don't announce it).
enterAndAnnounce :: NodeId -> ChattyDungeonM ()Source
Enter the given room, trigger all events and announce it. On the first visit, look around.
changeRoom :: Direction -> ChattyDungeonM ()Source
Enter a neighbouring room by its direction.
Room construction
constructRoom :: MonadDungeon m => RoomT m a -> m NodeIdSource
Construct a new room using the room monad.
establishWay :: MonadDungeon m => NodeId -> NodeId -> Direction -> PathState -> m ()Source
Establish a path from one room to another one (one-way only).
addRoomObject :: (ChCounter m, MonadRoom m) => ObjectT m a -> m ObjectIdSource
Add a new object to the current room. It is contructed using the object monad.
removeRoomObject :: MonadRoom m => ObjectId -> m ObjectStateSource
Remove an object from the current room and return its state.
insertRoomObject :: MonadRoom m => ObjectState -> m ()Source
Insert an already constructed object to the current room.
Object construction
constructObject :: Monad m => ObjectT m a -> Maybe ObjectId -> KindId -> m ObjectStateSource
Construct a room object (but don't add it)
modifyObjectState :: MonadObject m => (ObjectState -> ObjectState) -> m ()Source
Modify the object state
setObjectDesc :: (MonadObject m, IsText t) => t -> m ()Source
Set the object's description
setObjectTitle :: (MonadObject m, IsText t) => t -> m ()Source
Set the object's title
addObjectName :: MonadObject m => String -> m ()Source
Add a name for the current object
addObjectAttr :: MonadObject m => String -> m ()Source
Add an attribute for the current object
setObjectIsMob :: MonadObject m => Bool -> m ()Source
Set whether the current object is a mob.
setObjectIsAcquirable :: MonadObject m => Bool -> m ()Source
Set whether the current object is acquirable.
addFeature :: MonadObject m => Feature -> m ()Source
Add an object feature to the current object
addDescSeg :: (MonadObject m, ChAtoms m) => String -> m ()Source
Add a room description segment to the current object
addEquipSlot :: MonadObject m => EquipKey -> m ()Source
Add equippable slot
Object forms
registerForm :: ChAtoms m => ObjectT m () -> m (Atom ObjectState)Source
Register an object form and return its atom
instanciateForm :: (ChAtoms m, MonadRoom m) => Atom ObjectState -> m ObjectIdSource
Instanciate a registered form
registerKind :: ChCounter m => m KindIdSource
Register an object kind.
setObjectKind :: MonadObject m => KindId -> m ()Source
Set object kind.
Object investigation
getObjectTitle :: (MonadObject m, IsText t) => m tSource
Get the object's title
getObjectDesc :: (MonadObject m, IsText t) => m tSource
Get the object's description
getObjectNames :: MonadObject m => m [String]Source
Get the object's names
matchObjectName :: MonadObject m => String -> m BoolSource
Check if the given name matches our current object
getObjectIsMob :: (MonadObject m, Functor m) => m BoolSource
Check if the current object is a mob.
getObjectIsAcquirable :: (MonadObject m, Functor m) => m BoolSource
Check if the current object is acquirable.
roomOfObject :: MonadDungeon m => ObjectId -> m [NodeId]Source
Determine which rooms contain the given object (won't be more than one, but we're careful)
Object actions
setMobRoute :: MonadObject m => [NodeId] -> m ()Source
Set the current mob's route
continueMobRoute :: ObjectId -> HandlerSource
The given object may continue its route
Scheduling
schedule :: (MonadDungeon m, ChClock m) => Integer -> Handler -> m ()Source
Schedule an event for a given time offset (in milliseconds).
Players
subscribePlayer :: (MonadDungeon m, ChCounter m) => PlayerT m a -> m ()Source
Create a new player using the player monad
setPlayerRoom :: MonadPlayer m => NodeId -> m ()Source
Move the current player to the given room, but don't trigger anything.
acquireObject :: ObjectId -> ChattyDungeonM ()Source
Acquire the given object and put it in the player's inventory
dropObject :: ObjectId -> ChattyDungeonM ()Source
Drop the given object and remove it from the player's inventory
equipObject :: (MonadPlayer m, MonadError SplErr m) => ObjectState -> m (Maybe ObjectState)Source
Equip the given object somewhere
equipObjectAt :: (MonadPlayer m, MonadError SplErr m) => EquipKey -> ObjectState -> m (Maybe ObjectState)Source
Equip the given object at a given key
getEquipment :: MonadPlayer m => EquipKey -> m (Maybe ObjectState)Source
Get equipped object
getCooldown :: MonadPlayer m => CooldownId -> m BoolSource
Get cooldown state
setCooldown :: MonadPlayer m => CooldownId -> Bool -> m ()Source
Set/unset cooldown
consumeAlcohol :: (ChPrinter m, ChRandom m, MonadPlayer m, MonadDungeon m, ChClock m) => Int -> m ()Source
Consume alcohol.
Currencies
registerCurrency :: (ChCounter m, MonadDungeon m) => String -> String -> m CurrencyIdSource
Register a currency
getCurrency :: MonadPlayer m => CurrencyId -> m IntSource
Get currency state
modifyCurrency :: MonadPlayer m => CurrencyId -> (Int -> Int) -> m ()Source
Modify currency state
Fight
damage :: DamageTarget -> Int -> ChattyDungeonM ()Source
Damage a target (no matter whether player or mob) without setting focus
focusOpponent :: ObjectId -> ChattyDungeonM ()Source
Focus an opponent
dealDamage :: Int -> ChattyDungeonM ()Source
Deal damage to an opponent. Real damage is influenced by random.
Masquerades
withRoom :: MonadDungeon m => NodeId -> RoomT m a -> m aSource
Run a function in the context of the given room.
withPlayer :: MonadDungeon m => PlayerId -> PlayerT (RoomT m) a -> m aSource
Run a function in the context of a given player
withObject :: MonadDungeon m => ObjectId -> ObjectT (RoomT m) a -> m aSource
Run a function in the context of a given object
Guardians
guardRoom :: MonadDungeon m => NodeId -> m () -> m ()Source
Only run the given function if the player is inside the also given room.
guardObject :: MonadDungeon m => ObjectId -> m () -> m ()Source
Only run the given function if the given object exists
guardObjectInRoom :: MonadDungeon m => ObjectId -> NodeId -> m () -> m ()Source
Only run the given function if the given object is in the also given room
guardObjectNotInRoom :: MonadDungeon m => ObjectId -> NodeId -> m () -> m ()Source
Only run the given function if the given object is not in the also given room
guardKindInRoom :: MonadDungeon m => KindId -> NodeId -> m () -> m ()Source
Only run the given function if an object of the given kind is in the also given room
guardKindNotInRoom :: MonadDungeon m => KindId -> NodeId -> m () -> m ()Source
Only run the given function if no object of the given kind is in the also given room