antisplice-0.7.2.0: An engine for text-based dungeons.

Safe HaskellNone

Game.Antisplice.Monad.Dungeon

Contents

Description

Provides the basic data types and monads for Antisplice.

Synopsis

Context quantifiers

type DungeonM a = forall m. MonadDungeon m => m aSource

Matches any MonadDungeon context

type ChattyDungeonM a = forall m. (Functor m, ExtendedPrinter m, MonadScanner m, MonadExpand m, ExpanderEnv m, MonadDungeon m, MonadError SplErr m, MonadAtoms m, MonadClock m, MonadVocab m) => m aSource

Matches any MonadDungeon context that also implements most of the Chatty classes and some of our utility classes.

type Trigger = ChattyDungeonM ()Source

The common type of all event handlers.

newtype TriggerBox Source

A boxed Trigger to avoid ImpredicativeTypes

Constructors

TriggerBox 

Fields

runTrigger :: Trigger
 

Utilities

class IsText t whereSource

Typeclass for all types that are convertible to or from Text

Methods

toText :: t -> TextSource

fromText :: Text -> tSource

Instances

data Direction Source

10 directions to go

Rooms

newtype RoomT m a Source

The room monad. Used to create or modify room data.

Constructors

Room 

Fields

runRoomT :: RoomState -> m (a, RoomState)
 

class Monad m => MonadRoom m whereSource

Typeclass for all room monads.

Methods

getRoomState :: m RoomStateSource

Get the room state

putRoomState :: RoomState -> m ()Source

Put the room state

Objects

data StatKey Source

Key for item or player statistics

Instances

data EquipKey Source

Key for equipment slot

Instances

data Implication Source

Implications an object infers for its containing room

Constructors

DescSeg (Atom String)

An additional particle for the room description (e.g. saying that XYZ is there).

StereoSeg (Atom PlayerStereo)

An additional stereotype for the nearcarryingwearing player

data Feature Source

Object features.

Constructors

Damagable

May take damage.

Acquirable

May be acquired.

Equipable EquipKey

May be equipped at the given slot.

Mobile

May move around.

Instances

data ObjectId Source

Phantom ID type for objects.

Constructors

ObjectId Int 
FalseObject 

class Monad m => MonadObject m whereSource

Typeclass for all object monads

Methods

getObjectState :: m ObjectStateSource

Get the object state

putObjectState :: ObjectState -> m ()Source

Put the object state

Factions

data Attitude Source

Constructors

Hostile 
Friendly 
Exalted 

Instances

Players

data PlayerStereo Source

A player stereotype

Constructors

PlayerStereo 

Fields

stereoCalcStatBonus :: (StatKey -> Int) -> StatKey -> Int
 

class Monad m => MonadPlayer m whereSource

Typeclass for all player monads.

Methods

getPlayerState :: m PlayerStateSource

Get the player state.

putPlayerState :: PlayerState -> m ()Source

Put the player state.

Dungeons

currentRoomOf :: DungeonState -> Maybe NodeIdSource

For compatibility. Earlier versions of DungeonT had a field for that.

class (MonadRoom m, MonadPlayer m) => MonadDungeon m whereSource

Typeclass for all dungeon monads.

Methods

getDungeonState :: m DungeonStateSource

Get the dungeon state.

putDungeonState :: DungeonState -> m ()Source

Put the dungeon state.