LambdaHack-0.11.0.0: A game engine library for tactical squad ASCII roguelike dungeon crawlers
Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.Misc

Description

Hacks that haven't found their home yet.

Synopsis

Documentation

data FontDefinition Source #

Constructors

FontProportional Text Int HintingMode

filename, size, hinting mode

FontMonospace Text Int HintingMode 
FontMapScalable Text Int HintingMode Int

extra cell extension

FontMapBitmap Text Int

size ignored for bitmap fonts and no hinting

Instances

Instances details
Eq FontDefinition Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Read FontDefinition Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Show FontDefinition Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Generic FontDefinition Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Associated Types

type Rep FontDefinition :: Type -> Type #

Binary FontDefinition Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

NFData FontDefinition Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

rnf :: FontDefinition -> () #

type Rep FontDefinition Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

type Rep FontDefinition = D1 ('MetaData "FontDefinition" "Game.LambdaHack.Common.Misc" "LambdaHack-0.11.0.0-inplace" 'False) ((C1 ('MetaCons "FontProportional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 HintingMode))) :+: C1 ('MetaCons "FontMonospace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 HintingMode)))) :+: (C1 ('MetaCons "FontMapScalable" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 HintingMode) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))) :+: C1 ('MetaCons "FontMapBitmap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))))

data HintingMode Source #

Constructors

HintingHeavy

current libfreetype6 default, thin, large letter spacing

HintingLight

mimics OTF, blurry, thick, tight tracking, accurate shape

Instances

Instances details
Eq HintingMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Read HintingMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Show HintingMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Generic HintingMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Associated Types

type Rep HintingMode :: Type -> Type #

Binary HintingMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

NFData HintingMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

rnf :: HintingMode -> () #

type Rep HintingMode Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

type Rep HintingMode = D1 ('MetaData "HintingMode" "Game.LambdaHack.Common.Misc" "LambdaHack-0.11.0.0-inplace" 'False) (C1 ('MetaCons "HintingHeavy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HintingLight" 'PrefixI 'False) (U1 :: Type -> Type))

data FontSet Source #

Instances

Instances details
Eq FontSet Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

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

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

Read FontSet Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Show FontSet Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Generic FontSet Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Associated Types

type Rep FontSet :: Type -> Type #

Methods

from :: FontSet -> Rep FontSet x #

to :: Rep FontSet x -> FontSet #

Binary FontSet Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

put :: FontSet -> Put #

get :: Get FontSet #

putList :: [FontSet] -> Put #

NFData FontSet Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

Methods

rnf :: FontSet -> () #

type Rep FontSet Source # 
Instance details

Defined in Game.LambdaHack.Common.Misc

type Rep FontSet = D1 ('MetaData "FontSet" "Game.LambdaHack.Common.Misc" "LambdaHack-0.11.0.0-inplace" 'False) (C1 ('MetaCons "FontSet" 'PrefixI 'True) ((S1 ('MetaSel ('Just "fontMapScalable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "fontMapBitmap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "fontPropRegular") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "fontPropBold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "fontMono") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))))

makePhrase :: [Part] -> Text Source #

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

makeSentence :: [Part] -> Text Source #

Re-exported English phrase creation functions, applied to our custom 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).

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/.

xM :: Int -> Int64 Source #

Multiplies by a million.

xD :: Double -> Double Source #

Multiplies by a million, double precision.