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

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.Kind

Description

General content types and operations.

Synopsis

Documentation

data ContentId c Source #

Content identifiers for the content type c.

Instances
Enum (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Eq (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Methods

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

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

Ord (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Show (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Generic (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Associated Types

type Rep (ContentId c) :: * -> * #

Methods

from :: ContentId c -> Rep (ContentId c) x #

to :: Rep (ContentId c) x -> ContentId c #

Binary (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Methods

put :: ContentId c -> Put #

get :: Get (ContentId c) #

putList :: [ContentId c] -> Put #

NFData (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Methods

rnf :: ContentId c -> () #

Hashable (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Methods

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

hash :: ContentId c -> Int #

UnboxRepClass (ContentId k) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Associated Types

type UnboxRep (ContentId k) :: * Source #

type Rep (ContentId c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

type Rep (ContentId c) = D1 (MetaData "ContentId" "Game.LambdaHack.Common.ContentData" "LambdaHack-0.8.1.2-9Fmfvbfsr9xEInnejydwaW" True) (C1 (MetaCons "ContentId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16)))
type UnboxRep (ContentId k) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

data ContentData c Source #

Verified and preprocessed content data of a particular kind.

Instances
Generic (ContentData c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Associated Types

type Rep (ContentData c) :: * -> * #

Methods

from :: ContentData c -> Rep (ContentData c) x #

to :: Rep (ContentData c) x -> ContentData c #

NFData c => NFData (ContentData c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

Methods

rnf :: ContentData c -> () #

type Rep (ContentData c) Source # 
Instance details

Defined in Game.LambdaHack.Common.ContentData

type Rep (ContentData c) = D1 (MetaData "ContentData" "Game.LambdaHack.Common.ContentData" "LambdaHack-0.8.1.2-9Fmfvbfsr9xEInnejydwaW" False) (C1 (MetaCons "ContentData" PrefixI True) (S1 (MetaSel (Just "contentVector") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector c)) :*: S1 (MetaSel (Just "groupFreq") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Map (GroupName c) [(Int, (ContentId c, c))]))))

data COps Source #

Operations for all content types, gathered together.

Instances
Eq COps Source # 
Instance details

Defined in Game.LambdaHack.Common.Kind

Methods

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

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

Show COps Source # 
Instance details

Defined in Game.LambdaHack.Common.Kind

Methods

showsPrec :: Int -> COps -> ShowS #

show :: COps -> String #

showList :: [COps] -> ShowS #

Generic COps Source # 
Instance details

Defined in Game.LambdaHack.Common.Kind

Associated Types

type Rep COps :: * -> * #

Methods

from :: COps -> Rep COps x #

to :: Rep COps x -> COps #

type Rep COps Source # 
Instance details

Defined in Game.LambdaHack.Common.Kind

getStdRuleset :: COps -> RuleKind Source #

The standard ruleset used for level operations.

okind :: ContentData a -> ContentId a -> a Source #

Content element at given id.

ouniqGroup :: Show a => ContentData a -> GroupName a -> ContentId a Source #

The id of the unique member of a singleton content group.

opick :: Show a => ContentData a -> GroupName a -> (a -> Bool) -> Rnd (Maybe (ContentId a)) Source #

Pick a random id belonging to a group and satisfying a predicate.

ofoldrWithKey :: ContentData a -> (ContentId a -> a -> b -> b) -> b -> b Source #

Fold over all content elements of a.

ofoldlWithKey' :: ContentData a -> (b -> ContentId a -> a -> b) -> b -> b Source #

Fold strictly over all content a.

ofoldlGroup' :: ContentData a -> GroupName a -> (b -> Int -> ContentId a -> a -> b) -> b -> b Source #

Fold over the given group only.

omapVector :: ContentData a -> (a -> b) -> Vector b Source #

oimapVector :: ContentData a -> (ContentId a -> a -> b) -> Vector b Source #

olength :: ContentData a -> Int Source #

Size of content a.