LambdaHack-0.8.1.0: A game engine library for tactical squad ASCII roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.Misc

Contents

Description

Hacks that haven't found their home yet.

Synopsis

Game object identifiers

data FactionId Source #

A unique identifier of a faction in a game.

data LevelId Source #

Abstract level identifiers.

data ActorId Source #

A unique identifier of an actor in the dungeon.

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 # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Ord Container Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Show Container Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Generic Container Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Associated Types

type Rep Container :: * -> * #

Binary Container Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

type Rep Container Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

data CStore Source #

Actor's item stores.

Constructors

CGround 
COrgan 
CEqp 
CInv 
CSha 
Instances
Bounded CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Enum CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Eq CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

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

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

Ord CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Read CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Show CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Generic CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Associated Types

type Rep CStore :: * -> * #

Methods

from :: CStore -> Rep CStore x #

to :: Rep CStore x -> CStore #

Binary CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

put :: CStore -> Put #

get :: Get CStore #

putList :: [CStore] -> Put #

NFData CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

rnf :: CStore -> () #

type Rep CStore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

type Rep CStore = D1 (MetaData "CStore" "Game.LambdaHack.Common.Misc" "LambdaHack-0.8.1.0-1OhyQzgxgToLUwg19o2btM" 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 SLore Source #

Item slot and lore categories.

Constructors

SItem 
SOrgan 
STrunk 
STmp 
SBlast 
SEmbed 
Instances
Bounded SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Enum SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Eq SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

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

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

Ord SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

compare :: SLore -> SLore -> Ordering #

(<) :: SLore -> SLore -> Bool #

(<=) :: SLore -> SLore -> Bool #

(>) :: SLore -> SLore -> Bool #

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

max :: SLore -> SLore -> SLore #

min :: SLore -> SLore -> SLore #

Read SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Show SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

showsPrec :: Int -> SLore -> ShowS #

show :: SLore -> String #

showList :: [SLore] -> ShowS #

Generic SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Associated Types

type Rep SLore :: * -> * #

Methods

from :: SLore -> Rep SLore x #

to :: Rep SLore x -> SLore #

Binary SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

put :: SLore -> Put #

get :: Get SLore #

putList :: [SLore] -> Put #

NFData SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

rnf :: SLore -> () #

type Rep SLore Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

type Rep SLore = D1 (MetaData "SLore" "Game.LambdaHack.Common.Misc" "LambdaHack-0.8.1.0-1OhyQzgxgToLUwg19o2btM" False) ((C1 (MetaCons "SItem" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SOrgan" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "STrunk" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "STmp" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SBlast" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SEmbed" PrefixI False) (U1 :: * -> *))))

data ItemDialogMode Source #

Instances
Eq ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Ord ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Read ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Show ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Generic ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Associated Types

type Rep ItemDialogMode :: * -> * #

Binary ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

NFData ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

rnf :: ItemDialogMode -> () #

type Rep ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

type Rep ItemDialogMode = D1 (MetaData "ItemDialogMode" "Game.LambdaHack.Common.Misc" "LambdaHack-0.8.1.0-1OhyQzgxgToLUwg19o2btM" False) ((C1 (MetaCons "MStore" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 CStore)) :+: C1 (MetaCons "MOrgans" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "MOwned" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "MStats" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MLore" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 SLore)))))

Assorted

data GroupName a Source #

Instances
Eq (GroupName a) Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

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

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

Ord (GroupName a) Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Read (GroupName a) Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Show (GroupName a) Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

IsString (GroupName a) Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

fromString :: String -> GroupName a #

Generic (GroupName a) Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

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 # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

put :: GroupName a -> Put #

get :: Get (GroupName a) #

putList :: [GroupName a] -> Put #

NFData (GroupName a) Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

rnf :: GroupName a -> () #

Hashable (GroupName a) Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

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

hash :: GroupName a -> Int #

type Rep (GroupName a) Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

type Rep (GroupName a) = D1 (MetaData "GroupName" "Game.LambdaHack.Common.Misc" "LambdaHack-0.8.1.0-1OhyQzgxgToLUwg19o2btM" True) (C1 (MetaCons "GroupName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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 # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Enum Tactic Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Eq Tactic Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

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

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

Ord Tactic Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Show Tactic Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Generic Tactic Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Associated Types

type Rep Tactic :: * -> * #

Methods

from :: Tactic -> Rep Tactic x #

to :: Rep Tactic x -> Tactic #

Binary Tactic Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

put :: Tactic -> Put #

get :: Get Tactic #

putList :: [Tactic] -> Put #

NFData Tactic Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

rnf :: Tactic -> () #

type Rep Tactic Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

type Rep Tactic = D1 (MetaData "Tactic" "Game.LambdaHack.Common.Misc" "LambdaHack-0.8.1.0-1OhyQzgxgToLUwg19o2btM" 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 :: * -> *))))

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.

squashedWWandW :: [Part] -> (Part, Person) Source #

Apply the WWandW constructor, first representing repetitions as CardinalWs. The parts are not sorted, only grouped, to keep the order. The internal structure of speech parts is compared, not their string rendering, so some coincidental clashes are avoided (and code is simpler).

normalLevelBound :: (Int, Int) Source #

Level bounds.

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 # 
Instance details

NFData Part Source # 
Instance details

Methods

rnf :: Part -> () #

NFData Person Source # 
Instance details

Methods

rnf :: Person -> () #

NFData Polarity Source # 
Instance details

Methods

rnf :: Polarity -> () #

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

Methods

put :: EnumSet k -> Put #

get :: Get (EnumSet k) #

putList :: [EnumSet k] -> Put #

Enum k => Keyed (EnumMap k) Source # 
Instance details

Methods

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

Zip (EnumMap k) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Methods

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

Enum k => Lookup (EnumMap k) Source # 
Instance details

Methods

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

Enum k => Adjustable (EnumMap k) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Methods

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

hash :: EnumMap k e -> Int #