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

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Definition.Color

Contents

Description

Colours and text attributes.

Synopsis

Colours

data Color Source #

Colours supported by the major frontends.

Instances
Enum Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Eq Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Methods

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

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

Ord Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Methods

compare :: Color -> Color -> Ordering #

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

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

(>) :: Color -> Color -> Bool #

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

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Read Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Show Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Generic Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Associated Types

type Rep Color :: Type -> Type #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

Binary Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Methods

put :: Color -> Put #

get :: Get Color #

putList :: [Color] -> Put #

NFData Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Methods

rnf :: Color -> () #

Hashable Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Methods

hashWithSalt :: Int -> Color -> Int #

hash :: Color -> Int #

type Rep Color Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

type Rep Color = D1 (MetaData "Color" "Game.LambdaHack.Definition.Color" "LambdaHack-0.9.4.1-inplace" False) ((((C1 (MetaCons "Black" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Red" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Green" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Brown" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Blue" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Magenta" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Cyan" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "White" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "AltWhite" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BrBlack" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "BrRed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BrGreen" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "BrYellow" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BrBlue" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "BrMagenta" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "BrCyan" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BrWhite" PrefixI False) (U1 :: Type -> Type))))))

defFG :: Color Source #

The default colours, to optimize attribute setting.

isBright :: Color -> Bool Source #

A helper for the terminal frontends that display bright via bold.

darkCol :: [Color] Source #

Colour sets.

brightCol :: [Color] Source #

Colour sets.

stdCol :: [Color] Source #

Colour sets.

legalFgCol :: [Color] Source #

Colour sets.

colorToRGB :: Color -> Text Source #

Translationg to heavily modified Linux console color RGB values.

Warning: SDL frontend sadly duplicates this code.

Complete text attributes

data Highlight Source #

Additional map cell highlight, e.g., a colorful square around the cell or a colorful background.

Note: the highlight underscored by the terminal cursor is the maximal element of this type present of this screen.

Instances
Bounded Highlight Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Enum Highlight Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Eq Highlight Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Ord Highlight Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Show Highlight Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Generic Highlight Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Associated Types

type Rep Highlight :: Type -> Type #

type Rep Highlight Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

type Rep Highlight = D1 (MetaData "Highlight" "Game.LambdaHack.Definition.Color" "LambdaHack-0.9.4.1-inplace" False) (((C1 (MetaCons "HighlightNone" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HighlightGreen" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "HighlightBlue" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HighlightGrey" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HighlightWhite" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "HighlightMagenta" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HighlightRed" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "HighlightYellow" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HighlightYellowAim" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HighlightRedAim" PrefixI False) (U1 :: Type -> Type)))))

data Attr Source #

Text attributes: foreground color and highlight.

Constructors

Attr 

Fields

Instances
Eq Attr Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Methods

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

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

Ord Attr Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Methods

compare :: Attr -> Attr -> Ordering #

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

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

(>) :: Attr -> Attr -> Bool #

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

max :: Attr -> Attr -> Attr #

min :: Attr -> Attr -> Attr #

Show Attr Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

defAttr :: Attr Source #

The default attribute, to optimize attribute setting.

Characters with attributes

data AttrChar Source #

Character to display, with its attribute.

Constructors

AttrChar 

Fields

newtype AttrCharW32 Source #

Optimized representation of AttrChar.

Constructors

AttrCharW32 

Fields

Instances
Enum AttrCharW32 Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Eq AttrCharW32 Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Ord AttrCharW32 Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Show AttrCharW32 Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

Binary AttrCharW32 Source # 
Instance details

Defined in Game.LambdaHack.Definition.Color

UnboxRepClass AttrCharW32 Source # 
Instance details

Defined in Game.LambdaHack.Common.PointArray

Associated Types

type UnboxRep AttrCharW32 :: Type Source #

type UnboxRep AttrCharW32 Source # 
Instance details

Defined in Game.LambdaHack.Common.PointArray