LambdaHack-0.11.0.1: A game engine library for tactical squad ASCII roguelike dungeon crawlers
Safe HaskellSafe-Inferred
LanguageHaskell2010

Game.LambdaHack.Definition.Defs

Description

Basic types for content definitions.

Synopsis

Documentation

data GroupName c Source #

Instances

Instances details
Show (GroupName c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Binary (GroupName c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Methods

put :: GroupName c -> Put #

get :: Get (GroupName c) #

putList :: [GroupName c] -> Put #

NFData (GroupName c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Methods

rnf :: GroupName c -> () #

Eq (GroupName c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Methods

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

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

Ord (GroupName c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Hashable (GroupName c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Methods

hashWithSalt :: Int -> GroupName c -> Int #

hash :: GroupName c -> Int #

displayGroupName :: GroupName c -> Text Source #

This does not need to be 1-1, so should not be used in place of the Eq instance, etc.

data ContentId c Source #

Content identifiers for the content type c.

Instances

Instances details
UnboxRepClass (ContentId k) Source # 
Instance details

Defined in Game.LambdaHack.Common.PointArray

Associated Types

type UnboxRep (ContentId k) Source #

Enum (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Show (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Binary (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Methods

put :: ContentId c -> Put #

get :: Get (ContentId c) #

putList :: [ContentId c] -> Put #

Eq (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Methods

(==) :: ContentId c -> ContentId c -> Bool #

(/=) :: ContentId c -> ContentId c -> Bool #

Ord (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Hashable (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Definition.DefsInternal

Methods

hashWithSalt :: Int -> ContentId c -> Int #

hash :: ContentId c -> Int #

type UnboxRep (ContentId k) Source # 
Instance details

Defined in Game.LambdaHack.Common.PointArray

type X = Int Source #

X spacial dimension for points and vectors.

type Y = Int Source #

Y xpacial dimension for points and vectors.

type Freqs c = [(GroupName c, 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.

renameFreqs :: (Text -> Text) -> Freqs c -> Freqs c Source #

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

Rarity on given depths. The first element of the pair is normally in (0, 10] interval and, e.g., if there are 20 levels, 0.5 represents the first level and 10 the last. Exceptionally, it may be larger than 10, meaning appearance in the dungeon is not possible under normal circumstances and the value remains constant above the interval bound.

data CStore Source #

Actor's item stores.

Constructors

CGround 
COrgan 
CEqp 
CStash 

Instances

Instances details
Bounded CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Enum CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Generic CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Associated Types

type Rep CStore :: Type -> Type #

Methods

from :: CStore -> Rep CStore x #

to :: Rep CStore x -> CStore #

Read CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Show CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Binary CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Methods

put :: CStore -> Put #

get :: Get CStore #

putList :: [CStore] -> Put #

NFData CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Methods

rnf :: CStore -> () #

Eq CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Methods

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

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

Ord CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

type Rep CStore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

type Rep CStore = D1 ('MetaData "CStore" "Game.LambdaHack.Definition.Defs" "LambdaHack-0.11.0.1-inplace" 'False) ((C1 ('MetaCons "CGround" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "COrgan" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CEqp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CStash" 'PrefixI 'False) (U1 :: Type -> Type)))

data SLore Source #

Item slot and lore categories.

Instances

Instances details
Bounded SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Enum SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Generic SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Associated Types

type Rep SLore :: Type -> Type #

Methods

from :: SLore -> Rep SLore x #

to :: Rep SLore x -> SLore #

Read SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Show SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Methods

showsPrec :: Int -> SLore -> ShowS #

show :: SLore -> String #

showList :: [SLore] -> ShowS #

Binary SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Methods

put :: SLore -> Put #

get :: Get SLore #

putList :: [SLore] -> Put #

NFData SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Methods

rnf :: SLore -> () #

Eq SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Methods

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

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

Ord SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

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 #

type Rep SLore Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

type Rep SLore = D1 ('MetaData "SLore" "Game.LambdaHack.Definition.Defs" "LambdaHack-0.11.0.1-inplace" 'False) ((C1 ('MetaCons "SItem" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SOrgan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "STrunk" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SCondition" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SBlast" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SEmbed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SBody" 'PrefixI 'False) (U1 :: Type -> Type))))

data ItemDialogMode Source #

Constructors

MStore CStore

a leader's store

MOwned

all party's items

MSkills

not items, but determined by leader's items

MLore SLore

not party's items, but all known generalized items

MPlaces

places; not items at all, but definitely a lore

MFactions

factions in this game, with some data from previous

MModes

scenarios; not items at all, but definitely a lore

Instances

Instances details
Generic ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Associated Types

type Rep ItemDialogMode :: Type -> Type #

Read ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Show ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Binary ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

NFData ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Methods

rnf :: ItemDialogMode -> () #

Eq ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Ord ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

type Rep ItemDialogMode Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

type Rep ItemDialogMode = D1 ('MetaData "ItemDialogMode" "Game.LambdaHack.Definition.Defs" "LambdaHack-0.11.0.1-inplace" 'False) ((C1 ('MetaCons "MStore" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CStore)) :+: (C1 ('MetaCons "MOwned" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MSkills" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MLore" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SLore)) :+: C1 ('MetaCons "MPlaces" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MFactions" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MModes" 'PrefixI 'False) (U1 :: Type -> Type))))

data Direction Source #

Constructors

Forward 
Backward 

Instances

Instances details
Generic Direction Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Associated Types

type Rep Direction :: Type -> Type #

Read Direction Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Show Direction Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Binary Direction Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

NFData Direction Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Methods

rnf :: Direction -> () #

Eq Direction Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

Ord Direction Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

type Rep Direction Source # 
Instance details

Defined in Game.LambdaHack.Definition.Defs

type Rep Direction = D1 ('MetaData "Direction" "Game.LambdaHack.Definition.Defs" "LambdaHack-0.11.0.1-inplace" 'False) (C1 ('MetaCons "Forward" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Backward" 'PrefixI 'False) (U1 :: Type -> Type))