antisplice-0.17.0.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. SomeDungeon m => m aSource

Matches any SomeDungeon context

type ChattyDungeonM a = forall m. SomeChattyDungeon m => m aSource

Matches any SomeChattyDungeon context

type Handler = ChattyDungeonM ()Source

The common type of all event handlers.

newtype HandlerBox Source

A boxed Handler to avoid ImpredicativeTypes

Constructors

Handler 

Fields

runHandler :: Handler
 

type Prerequisite = ChattyDungeonM BoolSource

The common type of all prerequisites.

type Predicate = ChattyDungeonM (Maybe ReError)Source

The common type for all predicates.

Utilities

class IsText t whereSource

Typeclass for all types that are convertible to or from Text

Methods

toText :: t -> TextSource

fromText :: Text -> tSource

Instances

Rooms

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

data PathState Source

State type for a path from one room to another

Objects

data StatKey Source

Key for item or player statistics

data Relation Source

Relation between the player and the object.

Constructors

Near 
Carried 
Worn 

data Feature Source

Object features.

Constructors

Damagable

May take damage.

Acquirable

May be acquired.

Usable

May be used.

Drinkable

May be drunk.

Eatable

May be eaten.

Equipable EquipKey

May be equipped at the given slot.

Redeemable Currency Int

May be redeemed for the given currency.

AutoRedeem Currency Int

Redeem automatically for a given currency.

Weighty Int

Has a known weight.

Played PlayerId

Is connected to a real player.

Mobile

May move around.

Stereo Relation (Atom PlayerStereo)

Implies an additional stereotype for the nearcarryingwearing player

Described (Atom String)

Implies an additional particle for the room description

data KindId Source

Phantom ID type for object kinds.

Constructors

KindId Int 
FalseKind 

data ObjectState Source

State type for ObjectT

newtype ObjectT m a Source

The object monad. Used to create or modify objects.

Constructors

Object 

Fields

runObjectT :: ObjectState -> m (a, ObjectState)
 

Instances

MonadTrans ObjectT 
ChChannelPrinter Bool m0 => ChChannelPrinter Bool (ObjectT m0) 
ChChannelPrinter Int m0 => ChChannelPrinter Int (ObjectT m0) 
ChChannelPrinter Handle m0 => ChChannelPrinter Handle (ObjectT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (ObjectT m0) 
MonadError SplErr m0 => MonadError SplErr (ObjectT m0) 
Monad m => Monad (ObjectT m) 
Functor m => Functor (ObjectT m) 
ChHistoryEnv m0 => ChHistoryEnv (ObjectT m0) 
ChExpanderEnv m0 => ChExpanderEnv (ObjectT m0) 
ChExpand m0 => ChExpand (ObjectT m0) 
ChExtendedPrinter m0 => ChExtendedPrinter (ObjectT m0) 
ChSpawn m0 => ChSpawn (ObjectT m0) 
ChPrinter m0 => ChPrinter (ObjectT m0) 
ChBufferedScanner m0 => ChBufferedScanner (ObjectT m0) 
ChScanner m0 => ChScanner (ObjectT m0) 
ChFinalizer m0 => ChFinalizer (ObjectT m0) 
ChClock m0 => ChClock (ObjectT m0) 
ChRandom m0 => ChRandom (ObjectT m0) 
ChAtoms m0 => ChAtoms (ObjectT m0) 
ChCounter m0 => ChCounter (ObjectT m0) 
MonadIO m0 => MonadIO (ObjectT m0) 
MonadVocab m0 => MonadVocab (ObjectT m0) 
Monad m => MonadObject (ObjectT m) 
Monad m => OnUse (ObjectT m) 
Monad m => OnEat (ObjectT m) 
Monad m => OnDrink (ObjectT m) 
Monad m => OnDie (ObjectT m) 
Monad m => OnTakeDamage (ObjectT m) 
Monad m => OnRoomLeave (ObjectT m) 
Monad m => OnRoomEnter (ObjectT m) 
Monad m => OnRead (ObjectT m) 
Monad m => OnFirstInspection (ObjectT m) 
Monad m => OnInspection (ObjectT m) 
Monad m => OnFirstAcquire (ObjectT m) 
Monad m => OnAcquire (ObjectT m) 
Monad m => OnFirstSight (ObjectT m) 
Monad m => OnSight (ObjectT m) 
Monad m => OnAnnounce (ObjectT m) 
Monad m => OnLookInto (ObjectT m) 
Monad m => OnLook (ObjectT m) 
Monad m => OnEnter (ObjectT m) 

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

Currencies

data Currency Source

Currency descriptor (description and expander name)

data CurrencyId Source

Phantom ID type for currencies

Constructors

Health 
CurrencyId Int 

Fight

data DamageTarget Source

Target for attacks. May be a player or an object.

Players

newtype PlayerId Source

Phantom ID type for players

Constructors

PlayerId Int 

Instances

Eq PlayerId 
Ord PlayerId 
Tuplify PlayerId PlayerId 
Indexable PlayerState PlayerId PlayerState 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (AnsiPrinterT m0) 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (HtmlPrinterT m0) 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (ExpanderT m0) 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (NullExpanderT m0) 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (RecorderT m0) 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (AtomStoreT m0) 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (CounterT m0) 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (SplErrT m0) 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (VocabT m0) 
ChChannelPrinter PlayerId m => ChBroadcaster PlayerId (DungeonT m) 
(MonadDungeon m0, ChChannelPrinter PlayerId m0) => ChBroadcaster PlayerId (StereoBuilderT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (AnsiPrinterT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (HtmlPrinterT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (ExpanderT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (NullExpanderT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (RecorderT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (AtomStoreT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (CounterT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (SplErrT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (VocabT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (DungeonT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (PlayerT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (ObjectT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (RoomT m0) 
ChChannelPrinter PlayerId m0 => ChChannelPrinter PlayerId (StereoBuilderT m0) 
ChHistoryEnv m0 => ChHistoryEnv (PlayerFilterT m0) 
ChExpanderEnv m0 => ChExpanderEnv (PlayerFilterT m0) 
ChExpand m0 => ChExpand (PlayerFilterT m0) 
ChSpawn m0 => ChSpawn (PlayerFilterT m0) 
ChScanner m0 => ChScanner (PlayerFilterT m0) 
ChFinalizer m0 => ChFinalizer (PlayerFilterT m0) 
ChClock m0 => ChClock (PlayerFilterT m0) 
ChRandom m0 => ChRandom (PlayerFilterT m0) 
ChAtoms m0 => ChAtoms (PlayerFilterT m0) 
ChCounter m0 => ChCounter (PlayerFilterT m0) 
MonadVocab m0 => MonadVocab (PlayerFilterT m0) 

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.

modifyPlayerState :: (PlayerState -> PlayerState) -> m ()Source

Modify the player state.

Stereotypes

data CooldownId Source

Phantom ID type for cooldowns

data GetterResponse Source

Response of an object getter

Instances

type Invokable = [String] -> HandlerBoxSource

Some handler that may be invoked by the user

type InvokableP = [String] -> PredicateBoxSource

Some prerequisite that may be invoked by the user

data RecipeMethod Source

Method of using recipes

Constructors

RecipeMethod Int 

Dungeons

currentRoomOf :: DungeonState -> Maybe NodeIdSource

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

playerOf :: DungeonState -> Maybe PlayerStateSource

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.

lowerDungeon :: DungeonT m a -> m aSource

Lower a given DungeonT function