brick-0.63: A declarative terminal user interface library
Safe HaskellNone
LanguageHaskell2010

Brick.Themes

Description

Support for representing attribute themes and loading and saving theme customizations in INI-style files.

The file format is as follows:

Customization files are INI-style files with two sections, both optional: "default" and "other".

The "default" section specifies three optional fields:

  • "default.fg" - a color specification
  • "default.bg" - a color specification
  • "default.style" - a style specification

A color specification can be any of the strings black, red, green, yellow, blue, magenta, cyan, white, brightBlack, brightRed, brightGreen, brightYellow, brightBlue, brightMagenta, brightCyan, brightWhite, or default.

We also support color specifications in the common hex format #RRGGBB, but note that this specification is lossy: terminals can only display 256 colors, but hex codes can specify 256^3 = 16777216 colors.

A style specification can be either one of the following values (without quotes) or a comma-delimited list of one or more of the following values (e.g. "[bold,underline]") indicating that all of the specified styles be used. Valid styles are standout, underline, reverseVideo, blink, dim, italic, strikethrough, and bold.

The other section specifies for each attribute name in the theme the same fg, bg, and style settings as for the default attribute. Furthermore, if an attribute name has multiple components, the fields in the INI file should use periods as delimiters. For example, if a theme has an attribute name ("foo" <> "bar"), then the file may specify three fields:

  • foo.bar.fg - a color specification
  • foo.bar.bg - a color specification
  • foo.bar.style - a style specification

Any color or style specifications omitted from the file mean that those attribute or style settings will use the theme's default value instead.

Attribute names with multiple components (e.g. attr1 <> attr2) can be referenced in customization files by separating the names with a dot. For example, the attribute name "list" <> "selected" can be referenced by using the string "list.selected".

Synopsis

Documentation

data CustomAttr Source #

An attribute customization can specify which aspects of an attribute to customize.

Constructors

CustomAttr 

Fields

Instances

Instances details
Eq CustomAttr Source # 
Instance details

Defined in Brick.Themes

Read CustomAttr Source # 
Instance details

Defined in Brick.Themes

Show CustomAttr Source # 
Instance details

Defined in Brick.Themes

Generic CustomAttr Source # 
Instance details

Defined in Brick.Themes

Associated Types

type Rep CustomAttr :: Type -> Type #

Semigroup CustomAttr Source # 
Instance details

Defined in Brick.Themes

Monoid CustomAttr Source # 
Instance details

Defined in Brick.Themes

NFData CustomAttr Source # 
Instance details

Defined in Brick.Themes

Methods

rnf :: CustomAttr -> () #

type Rep CustomAttr Source # 
Instance details

Defined in Brick.Themes

type Rep CustomAttr = D1 ('MetaData "CustomAttr" "Brick.Themes" "brick-0.63-AXjxfylufgr2HzZo0AavwP" 'False) (C1 ('MetaCons "CustomAttr" 'PrefixI 'True) (S1 ('MetaSel ('Just "customFg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (MaybeDefault Color))) :*: (S1 ('MetaSel ('Just "customBg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (MaybeDefault Color))) :*: S1 ('MetaSel ('Just "customStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Style)))))

data Theme Source #

A theme provides a set of default attribute mappings, a default attribute, and a set of customizations for the default mapping and default attribute. The idea here is that the application will always need to provide a complete specification of its attribute mapping, but if the user wants to customize any aspect of that default mapping, it can be contained here and then built into an AttrMap (see themeToAttrMap). We keep the defaults separate from customizations to permit users to serialize themes and their customizations to, say, disk files.

Constructors

Theme 

Fields

Instances

Instances details
Eq Theme Source # 
Instance details

Defined in Brick.Themes

Methods

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

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

Read Theme Source # 
Instance details

Defined in Brick.Themes

Show Theme Source # 
Instance details

Defined in Brick.Themes

Methods

showsPrec :: Int -> Theme -> ShowS #

show :: Theme -> String #

showList :: [Theme] -> ShowS #

Generic Theme Source # 
Instance details

Defined in Brick.Themes

Associated Types

type Rep Theme :: Type -> Type #

Methods

from :: Theme -> Rep Theme x #

to :: Rep Theme x -> Theme #

NFData Theme Source # 
Instance details

Defined in Brick.Themes

Methods

rnf :: Theme -> () #

type Rep Theme Source # 
Instance details

Defined in Brick.Themes

type Rep Theme = D1 ('MetaData "Theme" "Brick.Themes" "brick-0.63-AXjxfylufgr2HzZo0AavwP" 'False) (C1 ('MetaCons "Theme" 'PrefixI 'True) ((S1 ('MetaSel ('Just "themeDefaultAttr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Just "themeDefaultMapping") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AttrName Attr))) :*: (S1 ('MetaSel ('Just "themeCustomDefaultAttr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CustomAttr)) :*: S1 ('MetaSel ('Just "themeCustomMapping") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AttrName CustomAttr)))))

newTheme :: Attr -> [(AttrName, Attr)] -> Theme Source #

Create a new theme with the specified default attribute and attribute mapping. The theme will have no customizations.

data ThemeDocumentation Source #

Documentation for a theme's attributes.

Constructors

ThemeDocumentation 

Fields

Instances

Instances details
Eq ThemeDocumentation Source # 
Instance details

Defined in Brick.Themes

Read ThemeDocumentation Source # 
Instance details

Defined in Brick.Themes

Show ThemeDocumentation Source # 
Instance details

Defined in Brick.Themes

Generic ThemeDocumentation Source # 
Instance details

Defined in Brick.Themes

Associated Types

type Rep ThemeDocumentation :: Type -> Type #

NFData ThemeDocumentation Source # 
Instance details

Defined in Brick.Themes

Methods

rnf :: ThemeDocumentation -> () #

type Rep ThemeDocumentation Source # 
Instance details

Defined in Brick.Themes

type Rep ThemeDocumentation = D1 ('MetaData "ThemeDocumentation" "Brick.Themes" "brick-0.63-AXjxfylufgr2HzZo0AavwP" 'False) (C1 ('MetaCons "ThemeDocumentation" 'PrefixI 'True) (S1 ('MetaSel ('Just "themeDescriptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AttrName Text))))

themeToAttrMap :: Theme -> AttrMap Source #

Build an AttrMap from a Theme. This applies all customizations in the returned AttrMap.

applyCustomizations Source #

Arguments

:: Maybe CustomAttr

An optional customization for the theme's default attribute.

-> (AttrName -> Maybe CustomAttr)

A function to obtain a customization for the specified attribute.

-> Theme

The theme to customize.

-> Theme 

Apply customizations using a custom lookup function. Customizations are obtained for each attribute name in the theme. Any customizations already set are lost.

loadCustomizations :: FilePath -> Theme -> IO (Either String Theme) Source #

Load an INI file containing theme customizations. Use the specified theme to determine which customizations to load. Return the specified theme with customizations set. See the module documentation for the theme file format.

saveCustomizations :: FilePath -> Theme -> IO () Source #

Save an INI file containing theme customizations. Use the specified theme to determine which customizations to save. See the module documentation for the theme file format.

saveTheme :: FilePath -> Theme -> IO () Source #

Save an INI file containing all attributes from the specified theme. Customized attributes are saved, but if an attribute is not customized, its default is saved instead. The file can later be re-loaded as a customization file.