vty-5.30: A simple terminal UI library

Safe HaskellSafe
LanguageHaskell2010

Graphics.Vty.Attributes

Contents

Description

Display attributes

Attributes have three components: a foreground color, a background color, and a style mask. The simplest attribute is the default attribute, or defAttr. Attributes can be modified with withForeColor, withBackColor, and withStyle, e.g.,

    defAttr `withForeColor` red

Image constructors often require an Attr to indicate the attributes used in the image, e.g.,

    string (defAttr `withForeColor` red) "this text will be red"

The appearance of Images using defAttr is determined by the The terminal, so this is not something VTY can control. The user is free to The define the color scheme of the terminal as they see fit.

The value currentAttr will keep the attributes of whatever was output previously.

Synopsis

Documentation

data Attr Source #

A display attribute defines the Color and Style of all the characters rendered after the attribute is applied.

At most 256 colors, picked from a 240 and 16 color palette, are possible for the background and foreground. The 240 colors and 16 colors are points in different palettes. See Color for more information.

Instances
Eq Attr Source # 
Instance details

Defined in Graphics.Vty.Attributes

Methods

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

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

Read Attr Source # 
Instance details

Defined in Graphics.Vty.Attributes

Show Attr Source # 
Instance details

Defined in Graphics.Vty.Attributes

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

Generic Attr Source # 
Instance details

Defined in Graphics.Vty.Attributes

Associated Types

type Rep Attr :: Type -> Type #

Methods

from :: Attr -> Rep Attr x #

to :: Rep Attr x -> Attr #

Semigroup Attr Source # 
Instance details

Defined in Graphics.Vty.Attributes

Methods

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

sconcat :: NonEmpty Attr -> Attr #

stimes :: Integral b => b -> Attr -> Attr #

Monoid Attr Source # 
Instance details

Defined in Graphics.Vty.Attributes

Methods

mempty :: Attr #

mappend :: Attr -> Attr -> Attr #

mconcat :: [Attr] -> Attr #

NFData Attr Source # 
Instance details

Defined in Graphics.Vty.Attributes

Methods

rnf :: Attr -> () #

type Rep Attr Source # 
Instance details

Defined in Graphics.Vty.Attributes

data FixedAttr Source #

Specifies the display attributes such that the final style and color values do not depend on the previously applied display attribute. The display attributes can still depend on the terminal's default colors (unfortunately).

Instances
Eq FixedAttr Source # 
Instance details

Defined in Graphics.Vty.Attributes

Show FixedAttr Source # 
Instance details

Defined in Graphics.Vty.Attributes

data MaybeDefault v where Source #

The style and color attributes can either be the terminal defaults. Or be equivalent to the previously applied style. Or be a specific value.

Constructors

Default :: MaybeDefault v 
KeepCurrent :: MaybeDefault v 
SetTo :: forall v. (Eq v, Show v, Read v) => !v -> MaybeDefault v 
Instances
Eq v => Eq (MaybeDefault v) Source # 
Instance details

Defined in Graphics.Vty.Attributes

(Eq v, Show v, Read v) => Read (MaybeDefault v) Source # 
Instance details

Defined in Graphics.Vty.Attributes

Eq v => Show (MaybeDefault v) Source # 
Instance details

Defined in Graphics.Vty.Attributes

Eq v => Semigroup (MaybeDefault v) Source # 
Instance details

Defined in Graphics.Vty.Attributes

Eq v => Monoid (MaybeDefault v) Source # 
Instance details

Defined in Graphics.Vty.Attributes

NFData v => NFData (MaybeDefault v) Source # 
Instance details

Defined in Graphics.Vty.Attributes

Methods

rnf :: MaybeDefault v -> () #

defAttr :: Attr Source #

Sets the style, background color and foreground color to the default values for the terminal. There is no easy way to determine what the default background and foreground colors are.

currentAttr :: Attr Source #

Keeps the style, background color and foreground color that was previously set. Used to override some part of the previous style.

EG: current_style withForeColor brightMagenta

Would be the currently applied style (be it underline, bold, etc) but with the foreground color set to brightMagenta.

Styles

type Style = Word8 Source #

Styles are represented as an 8 bit word. Each bit in the word is 1 if the style attribute assigned to that bit should be applied and 0 if the style attribute should not be applied.

withStyle :: Attr -> Style -> Attr Source #

Add the given style attribute

standout :: Style Source #

The 7 possible style attributes:

  • standout
  • underline
  • reverseVideo
  • blink
  • dim
  • bold/bright
  • italic

(The invisible, protect, and altcharset display attributes some terminals support are not supported via VTY.)

italic :: Style Source #

The 7 possible style attributes:

  • standout
  • underline
  • reverseVideo
  • blink
  • dim
  • bold/bright
  • italic

(The invisible, protect, and altcharset display attributes some terminals support are not supported via VTY.)

underline :: Style Source #

The 7 possible style attributes:

  • standout
  • underline
  • reverseVideo
  • blink
  • dim
  • bold/bright
  • italic

(The invisible, protect, and altcharset display attributes some terminals support are not supported via VTY.)

reverseVideo :: Style Source #

The 7 possible style attributes:

  • standout
  • underline
  • reverseVideo
  • blink
  • dim
  • bold/bright
  • italic

(The invisible, protect, and altcharset display attributes some terminals support are not supported via VTY.)

blink :: Style Source #

The 7 possible style attributes:

  • standout
  • underline
  • reverseVideo
  • blink
  • dim
  • bold/bright
  • italic

(The invisible, protect, and altcharset display attributes some terminals support are not supported via VTY.)

dim :: Style Source #

The 7 possible style attributes:

  • standout
  • underline
  • reverseVideo
  • blink
  • dim
  • bold/bright
  • italic

(The invisible, protect, and altcharset display attributes some terminals support are not supported via VTY.)

bold :: Style Source #

The 7 possible style attributes:

  • standout
  • underline
  • reverseVideo
  • blink
  • dim
  • bold/bright
  • italic

(The invisible, protect, and altcharset display attributes some terminals support are not supported via VTY.)

hasStyle :: Style -> Style -> Bool Source #

true if the given Style value has the specified Style set.

Setting attribute colors

withForeColor :: Attr -> Color -> Attr Source #

Set the foreground color of an Attr.

withBackColor :: Attr -> Color -> Attr Source #

Set the background color of an Attr.

Setting hyperlinks

withURL :: Attr -> Text -> Attr Source #

Add a hyperlinked URL using the proposed escape sequences for hyperlinked URLs. These escape sequences are comparatively new and aren't widely supported in terminal emulators yet, but most terminal emulators that don't know about these sequences will ignore these sequences, and therefore this should fall back sensibly. In some cases they won't and this will result in garbage, so this is why hyperlinking is disabled by default, in which case this combinator has no observable effect. To enable it, enable Hyperlink mode on your Vty output interface.