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

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.Misc

Contents

Description

Hacks that haven't found their home yet.

Synopsis

Game object identifiers

newtype AbsDepth Source #

Absolute depth in the dungeon. When used for the maximum depth of the whole dungeon, this can be different than dungeon size, e.g., when the dungeon is branched, and it can even be different than the length of the longest branch, if levels at some depths are missing.

Constructors

AbsDepth Int 

Item containers

data Container Source #

Item container type.

Constructors

CFloor LevelId Point 
CEmbed LevelId Point 
CActor ActorId CStore 
CTrunk FactionId LevelId Point

for bootstrapping actor bodies

Instances

Eq Container Source # 
Ord Container Source # 
Show Container Source # 
Generic Container Source # 

Associated Types

type Rep Container :: * -> * #

Binary Container Source # 
type Rep Container Source # 

data CStore Source #

Constructors

CGround 
COrgan 
CEqp 
CInv 
CSha 

Instances

Bounded CStore Source # 
Enum CStore Source # 
Eq CStore Source # 

Methods

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

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

Ord CStore Source # 
Read CStore Source # 
Show CStore Source # 
Generic CStore Source # 

Associated Types

type Rep CStore :: * -> * #

Methods

from :: CStore -> Rep CStore x #

to :: Rep CStore x -> CStore #

Binary CStore Source # 

Methods

put :: CStore -> Put #

get :: Get CStore #

putList :: [CStore] -> Put #

NFData CStore Source # 

Methods

rnf :: CStore -> () #

Hashable CStore Source # 

Methods

hashWithSalt :: Int -> CStore -> Int #

hash :: CStore -> Int #

type Rep CStore Source # 
type Rep CStore = D1 * (MetaData "CStore" "Game.LambdaHack.Common.Misc" "LambdaHack-0.6.2.0-6LvAjp6yuzE4Q9dWwe00a" False) ((:+:) * ((:+:) * (C1 * (MetaCons "CGround" PrefixI False) (U1 *)) (C1 * (MetaCons "COrgan" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CEqp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CInv" PrefixI False) (U1 *)) (C1 * (MetaCons "CSha" PrefixI False) (U1 *)))))

data ItemDialogMode Source #

Instances

Eq ItemDialogMode Source # 
Ord ItemDialogMode Source # 
Read ItemDialogMode Source # 
Show ItemDialogMode Source # 
Generic ItemDialogMode Source # 

Associated Types

type Rep ItemDialogMode :: * -> * #

Binary ItemDialogMode Source # 
NFData ItemDialogMode Source # 

Methods

rnf :: ItemDialogMode -> () #

type Rep ItemDialogMode Source # 
type Rep ItemDialogMode = D1 * (MetaData "ItemDialogMode" "Game.LambdaHack.Common.Misc" "LambdaHack-0.6.2.0-6LvAjp6yuzE4Q9dWwe00a" False) ((:+:) * ((:+:) * (C1 * (MetaCons "MStore" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 * CStore))) (C1 * (MetaCons "MOwned" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MStats" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MLoreItem" PrefixI False) (U1 *)) (C1 * (MetaCons "MLoreOrgan" PrefixI False) (U1 *)))))

Assorted

makePhrase :: [Part] -> Text Source #

Re-exported English phrase creation functions, applied to default irregular word sets.

makeSentence :: [Part] -> Text Source #

Re-exported English phrase creation functions, applied to default irregular word sets.

normalLevelBound :: (Int, Int) Source #

Level bounds.

data GroupName a Source #

Instances

Eq (GroupName a) Source # 

Methods

(==) :: GroupName a -> GroupName a -> Bool #

(/=) :: GroupName a -> GroupName a -> Bool #

Ord (GroupName a) Source # 
Read (GroupName a) Source # 
Show (GroupName a) Source # 
IsString (GroupName a) Source # 

Methods

fromString :: String -> GroupName a #

Generic (GroupName a) Source # 

Associated Types

type Rep (GroupName a) :: * -> * #

Methods

from :: GroupName a -> Rep (GroupName a) x #

to :: Rep (GroupName a) x -> GroupName a #

Binary (GroupName a) Source # 

Methods

put :: GroupName a -> Put #

get :: Get (GroupName a) #

putList :: [GroupName a] -> Put #

NFData (GroupName a) Source # 

Methods

rnf :: GroupName a -> () #

Hashable (GroupName a) Source # 

Methods

hashWithSalt :: Int -> GroupName a -> Int #

hash :: GroupName a -> Int #

type Rep (GroupName a) Source # 
type Rep (GroupName a) = D1 * (MetaData "GroupName" "Game.LambdaHack.Common.Misc" "LambdaHack-0.6.2.0-6LvAjp6yuzE4Q9dWwe00a" True) (C1 * (MetaCons "GroupName" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

type Freqs a = [(GroupName a, Int)] Source #

For each group that the kind belongs to, denoted by a GroupName in the first component of a pair, the second component of a pair shows how common the kind is within the group.

breturn :: MonadPlus m => Bool -> a -> m a Source #

breturn b a = [a | b]

type Rarity = [(Double, Int)] Source #

Rarity on given depths.

data Tactic Source #

Tactic of non-leader actors. Apart of determining AI operation, each tactic implies a skill modifier, that is added to the non-leader skills defined in fskillsOther field of Player.

Constructors

TExplore

if enemy nearby, attack, if no items, etc., explore unknown

TFollow

always follow leader's target or his position if no target

TFollowNoItems

follow but don't do any item management nor use

TMeleeAndRanged

only melee and do ranged combat

TMeleeAdjacent

only melee (or wait)

TBlock

always only wait, even if enemy in melee range

TRoam

if enemy nearby, attack, if no items, etc., roam randomly

TPatrol

find an open and uncrowded area, patrol it according to sight radius and fallback temporarily to TRoam when enemy is seen by the faction and is within the actor's sight radius

Instances

Bounded Tactic Source # 
Enum Tactic Source # 
Eq Tactic Source # 

Methods

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

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

Ord Tactic Source # 
Show Tactic Source # 
Generic Tactic Source # 

Associated Types

type Rep Tactic :: * -> * #

Methods

from :: Tactic -> Rep Tactic x #

to :: Rep Tactic x -> Tactic #

Binary Tactic Source # 

Methods

put :: Tactic -> Put #

get :: Get Tactic #

putList :: [Tactic] -> Put #

Hashable Tactic Source # 

Methods

hashWithSalt :: Int -> Tactic -> Int #

hash :: Tactic -> Int #

type Rep Tactic Source # 
type Rep Tactic = D1 * (MetaData "Tactic" "Game.LambdaHack.Common.Misc" "LambdaHack-0.6.2.0-6LvAjp6yuzE4Q9dWwe00a" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "TExplore" PrefixI False) (U1 *)) (C1 * (MetaCons "TFollow" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TFollowNoItems" PrefixI False) (U1 *)) (C1 * (MetaCons "TMeleeAndRanged" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "TMeleeAdjacent" PrefixI False) (U1 *)) (C1 * (MetaCons "TBlock" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TRoam" PrefixI False) (U1 *)) (C1 * (MetaCons "TPatrol" PrefixI False) (U1 *)))))

appDataDir :: IO FilePath Source #

Personal data directory for the game. Depends on the OS and the game, e.g., for LambdaHack under Linux it's ~/.LambdaHack/.

Orphan instances

Binary NominalDiffTime Source # 
NFData Part Source # 

Methods

rnf :: Part -> () #

NFData Person Source # 

Methods

rnf :: Person -> () #

NFData Polarity Source # 

Methods

rnf :: Polarity -> () #

(Enum k, Binary k) => Binary (EnumSet k) Source # 

Methods

put :: EnumSet k -> Put #

get :: Get (EnumSet k) #

putList :: [EnumSet k] -> Put #

Enum k => Keyed (EnumMap k) Source # 

Methods

mapWithKey :: (Key (EnumMap k) -> a -> b) -> EnumMap k a -> EnumMap k b #

Zip (EnumMap k) Source # 

Methods

zipWith :: (a -> b -> c) -> EnumMap k a -> EnumMap k b -> EnumMap k c #

zip :: EnumMap k a -> EnumMap k b -> EnumMap k (a, b) #

zap :: EnumMap k (a -> b) -> EnumMap k a -> EnumMap k b #

Enum k => ZipWithKey (EnumMap k) Source # 

Methods

zipWithKey :: (Key (EnumMap k) -> a -> b -> c) -> EnumMap k a -> EnumMap k b -> EnumMap k c #

zapWithKey :: EnumMap k (Key (EnumMap k) -> a -> b) -> EnumMap k a -> EnumMap k b #

Enum k => Indexable (EnumMap k) Source # 

Methods

index :: EnumMap k a -> Key (EnumMap k) -> a #

Enum k => Lookup (EnumMap k) Source # 

Methods

lookup :: Key (EnumMap k) -> EnumMap k a -> Maybe a #

Enum k => Adjustable (EnumMap k) Source # 

Methods

adjust :: (a -> a) -> Key (EnumMap k) -> EnumMap k a -> EnumMap k a #

replace :: Key (EnumMap k) -> a -> EnumMap k a -> EnumMap k a #

Enum k => FoldableWithKey (EnumMap k) Source # 

Methods

toKeyedList :: EnumMap k a -> [(Key (EnumMap k), a)] #

foldMapWithKey :: Monoid m => (Key (EnumMap k) -> a -> m) -> EnumMap k a -> m #

foldrWithKey :: (Key (EnumMap k) -> a -> b -> b) -> b -> EnumMap k a -> b #

foldlWithKey :: (b -> Key (EnumMap k) -> a -> b) -> b -> EnumMap k a -> b #

Enum k => TraversableWithKey (EnumMap k) Source # 

Methods

traverseWithKey :: Applicative f => (Key (EnumMap k) -> a -> f b) -> EnumMap k a -> f (EnumMap k b) #

mapWithKeyM :: Monad m => (Key (EnumMap k) -> a -> m b) -> EnumMap k a -> m (EnumMap k b) #

(Enum k, Binary k, Binary e) => Binary (EnumMap k e) Source # 

Methods

put :: EnumMap k e -> Put #

get :: Get (EnumMap k e) #

putList :: [EnumMap k e] -> Put #

(Hashable k, Eq k, Binary k, Binary v) => Binary (HashMap k v) Source # 

Methods

put :: HashMap k v -> Put #

get :: Get (HashMap k v) #

putList :: [HashMap k v] -> Put #

(Enum k, Hashable k, Hashable e) => Hashable (EnumMap k e) Source # 

Methods

hashWithSalt :: Int -> EnumMap k e -> Int #

hash :: EnumMap k e -> Int #