LambdaHack-0.6.2.0: A game engine library for roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.Item

Contents

Description

Weapons, treasure and all the other items in the game. No operation in this module involves the state or any of our custom monads.

Synopsis

The Item type

data ItemId Source #

A unique identifier of an item in the dungeon.

data Item Source #

Game items in actor possesion or strewn around the dungeon. The fields jsymbol, jname and jflavour make it possible to refer to and draw an unidentified item. Full information about item is available through the jkindIx index as soon as the item is identified.

Constructors

Item 

Fields

Instances

Eq Item Source # 

Methods

(==) :: Item -> Item -> Bool #

(/=) :: Item -> Item -> Bool #

Show Item Source # 

Methods

showsPrec :: Int -> Item -> ShowS #

show :: Item -> String #

showList :: [Item] -> ShowS #

Generic Item Source # 

Associated Types

type Rep Item :: * -> * #

Methods

from :: Item -> Rep Item x #

to :: Rep Item x -> Item #

Binary Item Source # 

Methods

put :: Item -> Put #

get :: Get Item #

putList :: [Item] -> Put #

Hashable Item Source # 

Methods

hashWithSalt :: Int -> Item -> Int #

hash :: Item -> Int #

type Rep Item Source # 

itemPrice :: (Item, Int) -> Int Source #

Price an item, taking count into consideration.

Item discovery types

data ItemKindIx Source #

An index of the kind id of an item. Clients have partial knowledge how these idexes map to kind ids. They gain knowledge by identifying items.

Instances

Enum ItemKindIx Source # 
Eq ItemKindIx Source # 
Ord ItemKindIx Source # 
Show ItemKindIx Source # 
Ix ItemKindIx Source # 
Binary ItemKindIx Source # 
Hashable ItemKindIx Source # 

data ItemSeed Source #

A seed for rolling aspects of an item Clients have partial knowledge of how item ids map to the seeds. They gain knowledge by identifying items.

data KindMean Source #

Constructors

KindMean 

Instances

Eq KindMean Source # 
Show KindMean Source # 
Generic KindMean Source # 

Associated Types

type Rep KindMean :: * -> * #

Methods

from :: KindMean -> Rep KindMean x #

to :: Rep KindMean x -> KindMean #

Binary KindMean Source # 

Methods

put :: KindMean -> Put #

get :: Get KindMean #

putList :: [KindMean] -> Put #

type Rep KindMean Source # 
type Rep KindMean = D1 * (MetaData "KindMean" "Game.LambdaHack.Common.Item" "LambdaHack-0.6.2.0-6LvAjp6yuzE4Q9dWwe00a" False) (C1 * (MetaCons "KindMean" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "kmKind") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * (Id ItemKind))) (S1 * (MetaSel (Just Symbol "kmMean") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * AspectRecord))))

type DiscoveryKind = EnumMap ItemKindIx KindMean Source #

The map of item kind indexes to item kind ids. The full map, as known by the server, is 1-1.

data Benefit Source #

Fields are intentionally kept non-strict, because they are recomputed often, but not used every time. The fields are, in order: 1. whether the item should be kept in equipment (not in pack nor stash) 2. the total benefit from picking the item up (to use or to put in equipment) 3. the benefit of applying the item to self 4. the (usually negative) benefit of hitting a foe in meleeing with the item 5. the (usually negative) benefit of flinging an item at an opponent

Constructors

Benefit 

Fields

Instances

Show Benefit Source # 
Generic Benefit Source # 

Associated Types

type Rep Benefit :: * -> * #

Methods

from :: Benefit -> Rep Benefit x #

to :: Rep Benefit x -> Benefit #

Binary Benefit Source # 

Methods

put :: Benefit -> Put #

get :: Get Benefit #

putList :: [Benefit] -> Put #

type Rep Benefit Source # 
type Rep Benefit = D1 * (MetaData "Benefit" "Game.LambdaHack.Common.Item" "LambdaHack-0.6.2.0-6LvAjp6yuzE4Q9dWwe00a" False) (C1 * (MetaCons "Benefit" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "benInEqp") NoSourceUnpackedness SourceLazy DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "benPickup") NoSourceUnpackedness SourceLazy DecidedLazy) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "benApply") NoSourceUnpackedness SourceLazy DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "benMelee") NoSourceUnpackedness SourceLazy DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "benFling") NoSourceUnpackedness SourceLazy DecidedLazy) (Rec0 * Int))))))

data AspectRecord Source #

Instances

Eq AspectRecord Source # 
Ord AspectRecord Source # 
Show AspectRecord Source # 
Generic AspectRecord Source # 

Associated Types

type Rep AspectRecord :: * -> * #

Binary AspectRecord Source # 
Hashable AspectRecord Source # 
type Rep AspectRecord Source # 
type Rep AspectRecord = D1 * (MetaData "AspectRecord" "Game.LambdaHack.Common.Item" "LambdaHack-0.6.2.0-6LvAjp6yuzE4Q9dWwe00a" False) (C1 * (MetaCons "AspectRecord" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "aTimeout") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "aHurtMelee") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "aArmorMelee") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "aArmorRanged") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "aMaxHP") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "aMaxCalm") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "aSpeed") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "aSight") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "aSmell") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "aShine") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "aNocto") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "aAggression") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "aSkills") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * Skills)))))))

type DiscoveryAspect = EnumMap ItemId AspectRecord Source #

The map of item ids to item aspects. The full map is known by the server.

Inventory management types

type ItemDict = EnumMap ItemId Item Source #

All items in the dungeon (including in actor inventories), indexed by item identifier.