brick-1.5: A declarative terminal user interface library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Brick.AttrMap

Description

This module provides types and functions for managing an attribute map which maps attribute names (AttrName) to attributes (Attr).

Attribute maps work by mapping hierarchical attribute names to attributes and inheriting parent names' attributes when child names specify partial attributes. Hierarchical names are created with mappend:

let n = attrName "parent" <> attrName "child"

Attribute names are mapped to attributes, but some attributes may be partial (specify only a foreground or background color). When attribute name lookups occur, the attribute corresponding to a more specific name ('parent <> child' as above) is successively merged with the parent attribute (parent as above) all the way to the "root" of the attribute map, the map's default attribute. In this way, more specific attributes inherit what they don't specify from more general attributes in the same hierarchy. This allows more modularity and less repetition in specifying how elements of your user interface take on different attributes.

Synopsis

Documentation

data AttrMap Source #

An attribute map which maps AttrName values to Attr values.

Instances

Instances details
Generic AttrMap Source # 
Instance details

Defined in Brick.AttrMap

Associated Types

type Rep AttrMap :: Type -> Type #

Methods

from :: AttrMap -> Rep AttrMap x #

to :: Rep AttrMap x -> AttrMap #

Show AttrMap Source # 
Instance details

Defined in Brick.AttrMap

NFData AttrMap Source # 
Instance details

Defined in Brick.AttrMap

Methods

rnf :: AttrMap -> () #

type Rep AttrMap Source # 
Instance details

Defined in Brick.AttrMap

data AttrName Source #

An attribute name. Attribute names are hierarchical; use mappend (<>) to assemble them. Hierarchy in an attribute name is used to represent increasing levels of specificity in referring to the attribute you want to use for a visual element, with names to the left being general and names to the right being more specific. For example:

attrName "window" <> attrName "border"
attrName "window" <> attrName "title"
attrName "header" <> attrName "clock" <> attrName "seconds"

Instances

Instances details
Monoid AttrName Source # 
Instance details

Defined in Brick.AttrMap

Semigroup AttrName Source # 
Instance details

Defined in Brick.AttrMap

Generic AttrName Source # 
Instance details

Defined in Brick.AttrMap

Associated Types

type Rep AttrName :: Type -> Type #

Methods

from :: AttrName -> Rep AttrName x #

to :: Rep AttrName x -> AttrName #

Read AttrName Source # 
Instance details

Defined in Brick.AttrMap

Show AttrName Source # 
Instance details

Defined in Brick.AttrMap

NFData AttrName Source # 
Instance details

Defined in Brick.AttrMap

Methods

rnf :: AttrName -> () #

Eq AttrName Source # 
Instance details

Defined in Brick.AttrMap

Ord AttrName Source # 
Instance details

Defined in Brick.AttrMap

type Rep AttrName Source # 
Instance details

Defined in Brick.AttrMap

type Rep AttrName = D1 ('MetaData "AttrName" "Brick.AttrMap" "brick-1.5-4Skg8aDAMwVLZBUMCQ8Oa9" 'False) (C1 ('MetaCons "AttrName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))

Construction

attrMap Source #

Arguments

:: Attr

The map's default attribute to be returned when a name lookup fails, and the attribute that will be merged with successful lookups.

-> [(AttrName, Attr)]

The map's initial contents.

-> AttrMap 

Create an attribute map.

forceAttrMap :: Attr -> AttrMap Source #

Create an attribute map in which all lookups map to the same attribute. This is functionally equivalent to attrMap attr [].

attrName :: String -> AttrName Source #

Create an attribute name from a string.

Inspection

attrNameComponents :: AttrName -> [String] Source #

Get the components of an attribute name.

Finding attributes from names

attrMapLookup :: AttrName -> AttrMap -> Attr Source #

Look up the specified attribute name in the map. Map lookups proceed as follows. If the attribute map is forcing all lookups to a specific attribute, that attribute is returned along with its style settings. If the attribute name is empty, the map's default attribute is returned. If the attribute name is non-empty, every subsequence of names from the specified name are used to perform a lookup and the results are combined as in mergeWithDefault, with more specific results taking precedence over less specific ones. As attributes are merged, styles are also merged. If a more specific attribute name introduces a style (underline, say) and a less specific attribute name introduces an additional style (bold, say) then the final result will include both styles.

For example:

attrMapLookup (attrName "foo" <> attrName "bar") (attrMap a []) == a
attrMapLookup (attrName "foo" <> attrName "bar") (attrMap (bg blue) [(attrName "foo" <> attrName "bar", fg red)]) == red `on` blue
attrMapLookup (attrName "foo" <> attrName "bar") (attrMap (bg blue) [(attrName "foo" <> attrName "bar", red on cyan)]) == red `on` cyan
attrMapLookup (attrName "foo" <> attrName "bar") (attrMap (bg blue) [(attrName "foo" <> attrName "bar", fg red), ("foo", bg cyan)]) == red `on` cyan
attrMapLookup (attrName "foo" <> attrName "bar") (attrMap (bg blue) [(attrName "foo", fg red)]) == red `on` blue

Manipulating attribute maps

setDefaultAttr :: Attr -> AttrMap -> AttrMap Source #

Set the default attribute value in an attribute map.

getDefaultAttr :: AttrMap -> Attr Source #

Get the default attribute value in an attribute map.

applyAttrMappings :: [(AttrName, Attr)] -> AttrMap -> AttrMap Source #

Insert a set of attribute mappings to an attribute map.

mergeWithDefault :: Attr -> AttrMap -> Attr Source #

Given an attribute and a map, merge the attribute with the map's default attribute. If the map is forcing all lookups to a specific attribute, the forced attribute is returned without merging it with the one specified here. Otherwise the attribute given here is merged with the attribute map's default attribute in that any aspect of the specified attribute that is not provided falls back to the map default. For example,

mergeWithDefault (fg blue) $ attrMap (bg red) []

returns

blue `on` red

mapAttrName :: AttrName -> AttrName -> AttrMap -> AttrMap Source #

Update an attribute map such that a lookup of ontoName returns the attribute value specified by fromName. This is useful for composite widgets with specific attribute names mapping those names to the sub-widget's expected name when calling that sub-widget's rendering function. See the ProgressBarDemo for an example usage, and overrideAttr for an alternate syntax.

mapAttrNames :: [(AttrName, AttrName)] -> AttrMap -> AttrMap Source #

Map several attributes to return the value associated with an alternate name. Applies mapAttrName across a list of mappings.