AttrName: remove IsString instance

This change is motivated by the API wart that results from the
overloading of both "<>" and string literals that resulted in code like
this:

  a :: AttrName
  a = "blah" <> "things"

While this worked to create an AttrName with two segments, it is far too
easy to read this as two strings concatenated. The overloading hides
what is really going on with the segments of the attribute name. The way
to write the above example after this change is:

  a :: AttrName
  a = attrName "blah" <> attrName "things"
This commit is contained in:
Jonathan Daugherty 2022-08-04 18:44:57 -07:00
parent bf58926132
commit 6f1b62ae53
19 changed files with 67 additions and 78 deletions

View File

@ -23,28 +23,28 @@ import Brick.Widgets.Core
, modifyDefAttr , modifyDefAttr
) )
import Brick.Util (on, fg) import Brick.Util (on, fg)
import Brick.AttrMap (attrMap, AttrMap) import Brick.AttrMap (attrMap, AttrMap, attrName)
ui :: Widget n ui :: Widget n
ui = ui =
vBox [ str "This text uses the global default attribute." vBox [ str "This text uses the global default attribute."
, withAttr "foundFull" $ , withAttr (attrName "foundFull") $
str "Specifying an attribute name means we look it up in the attribute tree." str "Specifying an attribute name means we look it up in the attribute tree."
, (withAttr "foundFgOnly" $ , (withAttr (attrName "foundFgOnly") $
str ("When we find a value, we merge it with its parent in the attribute") str ("When we find a value, we merge it with its parent in the attribute")
<=> str "name tree all the way to the root (the global default).") <=> str "name tree all the way to the root (the global default).")
, withAttr "missing" $ , withAttr (attrName "missing") $
str "A missing attribute name just resumes the search at its parent." str "A missing attribute name just resumes the search at its parent."
, withAttr ("general" <> "specific") $ , withAttr (attrName "general" <> attrName "specific") $
str "In this way we build complete attribute values by using an inheritance scheme." str "In this way we build complete attribute values by using an inheritance scheme."
, withAttr "foundFull" $ , withAttr (attrName "foundFull") $
str "You can override everything ..." str "You can override everything ..."
, withAttr "foundFgOnly" $ , withAttr (attrName "foundFgOnly") $
str "... or only what you want to change and inherit the rest." str "... or only what you want to change and inherit the rest."
, str "Attribute names are assembled with the Monoid append operation to indicate" , str "Attribute names are assembled with the Monoid append operation to indicate"
, str "hierarchy levels, e.g. \"window\" <> \"title\"." , str "hierarchy levels, e.g. \"window\" <> \"title\"."
, str " " , str " "
, withAttr "linked" $ , withAttr (attrName "linked") $
str "This text is hyperlinked in terminals that support hyperlinking." str "This text is hyperlinked in terminals that support hyperlinking."
, str " " , str " "
, hyperlink "http://www.google.com/" $ , hyperlink "http://www.google.com/" $
@ -59,11 +59,12 @@ globalDefault = white `on` blue
theMap :: AttrMap theMap :: AttrMap
theMap = attrMap globalDefault theMap = attrMap globalDefault
[ ("foundFull", white `on` green) [ (attrName "foundFull", white `on` green)
, ("foundFgOnly", fg red) , (attrName "foundFgOnly", fg red)
, ("general", yellow `on` black) , (attrName "general", yellow `on` black)
, ("general" <> "specific", fg cyan) , (attrName "general" <> attrName "specific",
, ("linked", fg yellow `withURL` "http://www.google.com/") fg cyan)
, (attrName "linked", fg yellow `withURL` "http://www.google.com/")
] ]
app :: App () e () app :: App () e ()

View File

@ -68,7 +68,7 @@ mkBorderDemo (styleName, sty) =
txt $ " " <> styleName <> " style " txt $ " " <> styleName <> " style "
titleAttr :: A.AttrName titleAttr :: A.AttrName
titleAttr = "title" titleAttr = A.attrName "title"
borderMappings :: [(A.AttrName, V.Attr)] borderMappings :: [(A.AttrName, V.Attr)]
borderMappings = borderMappings =

View File

@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where module Main where
import Control.Monad (void) import Control.Monad (void)
@ -31,6 +30,7 @@ import Brick.Widgets.Center
) )
import Brick.AttrMap import Brick.AttrMap
( AttrName ( AttrName
, attrName
, attrMap , attrMap
) )
@ -66,7 +66,7 @@ appEvent (VtyEvent (V.EvKey V.KEsc [])) = M.halt
appEvent _ = return () appEvent _ = return ()
emphAttr :: AttrName emphAttr :: AttrName
emphAttr = "emphasis" emphAttr = attrName "emphasis"
app :: M.App Int e Name app :: M.App Int e Name
app = app =

View File

@ -12,7 +12,7 @@ import Control.Monad.State (get)
import qualified Data.Text as Text import qualified Data.Text as Text
import qualified Brick.Main as M import qualified Brick.Main as M
import qualified Brick.Widgets.List as L import qualified Brick.Widgets.List as L
import Brick.AttrMap (AttrName) import Brick.AttrMap (AttrName, attrName)
import Brick.Types import Brick.Types
( Widget ( Widget
, BrickEvent(..) , BrickEvent(..)
@ -77,7 +77,7 @@ appEvent (VtyEvent ev) = do
appEvent _ = return () appEvent _ = return ()
errorAttr :: AttrName errorAttr :: AttrName
errorAttr = "error" errorAttr = attrName "error"
theMap :: A.AttrMap theMap :: A.AttrMap
theMap = A.attrMap V.defAttr theMap = A.attrMap V.defAttr

View File

@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Main where module Main where
@ -31,6 +30,7 @@ import Brick.Util (fg)
import Brick.AttrMap import Brick.AttrMap
( attrMap ( attrMap
, AttrName , AttrName
, attrName
) )
data St = data St =
@ -96,7 +96,7 @@ appEvent (T.VtyEvent (V.EvKey V.KEsc [])) = M.halt
appEvent _ = return () appEvent _ = return ()
arrowAttr :: AttrName arrowAttr :: AttrName
arrowAttr = "attr" arrowAttr = attrName "attr"
app :: M.App St e Name app :: M.App St e Name
app = app =

View File

@ -1,4 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Main where module Main where
@ -84,7 +83,7 @@ initialState :: L.List () Char
initialState = L.list () (Vec.fromList ['a','b','c']) 1 initialState = L.list () (Vec.fromList ['a','b','c']) 1
customAttr :: A.AttrName customAttr :: A.AttrName
customAttr = L.listSelectedAttr <> "custom" customAttr = L.listSelectedAttr <> A.attrName "custom"
theMap :: A.AttrMap theMap :: A.AttrMap
theMap = A.attrMap V.defAttr theMap = A.attrMap V.defAttr

View File

@ -1,4 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Main where module Main where
@ -75,7 +74,7 @@ initialState :: L.List () Char
initialState = L.list () (Vec.fromList ['a','b','c']) 1 initialState = L.list () (Vec.fromList ['a','b','c']) 1
customAttr :: A.AttrName customAttr :: A.AttrName
customAttr = L.listSelectedAttr <> "custom" customAttr = L.listSelectedAttr <> A.attrName "custom"
theMap :: A.AttrMap theMap :: A.AttrMap
theMap = A.attrMap V.defAttr theMap = A.attrMap V.defAttr

View File

@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Main where module Main where
@ -51,9 +50,9 @@ buttonLayer st =
C.hCenterLayer (vLimit 3 $ hLimit 50 $ E.renderEditor (str . unlines) True (st^.edit)) C.hCenterLayer (vLimit 3 $ hLimit 50 $ E.renderEditor (str . unlines) True (st^.edit))
where where
buttons = mkButton <$> buttonData buttons = mkButton <$> buttonData
buttonData = [ (Button1, "Button 1", "button1") buttonData = [ (Button1, "Button 1", attrName "button1")
, (Button2, "Button 2", "button2") , (Button2, "Button 2", attrName "button2")
, (Button3, "Button 3", "button3") , (Button3, "Button 3", attrName "button3")
] ]
mkButton (name, label, attr) = mkButton (name, label, attr) =
let wasClicked = (fst <$> st^.lastReportedClick) == Just name let wasClicked = (fst <$> st^.lastReportedClick) == Just name
@ -82,7 +81,7 @@ infoLayer st = T.Widget T.Fixed T.Fixed $ do
Just (name, T.Location l) -> Just (name, T.Location l) ->
"Mouse down at " <> show name <> " @ " <> show l "Mouse down at " <> show name <> " @ " <> show l
T.render $ translateBy (T.Location (0, h-1)) $ clickable Info $ T.render $ translateBy (T.Location (0, h-1)) $ clickable Info $
withDefAttr "info" $ withDefAttr (attrName "info") $
C.hCenter $ str msg C.hCenter $ str msg
appEvent :: T.BrickEvent Name e -> T.EventM Name St () appEvent :: T.BrickEvent Name e -> T.EventM Name St ()
@ -104,10 +103,10 @@ appEvent ev =
aMap :: AttrMap aMap :: AttrMap
aMap = attrMap V.defAttr aMap = attrMap V.defAttr
[ ("info", V.white `on` V.magenta) [ (attrName "info", V.white `on` V.magenta)
, ("button1", V.white `on` V.cyan) , (attrName "button1", V.white `on` V.cyan)
, ("button2", V.white `on` V.green) , (attrName "button2", V.white `on` V.green)
, ("button3", V.white `on` V.blue) , (attrName "button3", V.white `on` V.blue)
, (E.editFocusedAttr, V.black `on` V.yellow) , (E.editFocusedAttr, V.black `on` V.yellow)
] ]

View File

@ -1,4 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
module Main where module Main where
import Control.Monad (void) import Control.Monad (void)
@ -32,7 +31,7 @@ import Brick.Widgets.Core
, withDefAttr , withDefAttr
) )
import Brick.Util (on, fg) import Brick.Util (on, fg)
import Brick.AttrMap (AttrName) import Brick.AttrMap (AttrName, attrName)
ui :: Widget n ui :: Widget n
ui = ui =
@ -44,7 +43,7 @@ ui =
] ]
keybindingAttr :: AttrName keybindingAttr :: AttrName
keybindingAttr = "keybinding" keybindingAttr = attrName "keybinding"
theme1 :: Theme theme1 :: Theme
theme1 = theme1 =

View File

@ -1,4 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Main where module Main where
@ -16,7 +15,7 @@ import qualified Brick.Types as T
import qualified Brick.Main as M import qualified Brick.Main as M
import qualified Brick.Widgets.Center as C import qualified Brick.Widgets.Center as C
import qualified Brick.Widgets.Border as B import qualified Brick.Widgets.Border as B
import Brick.AttrMap (AttrMap, AttrName, attrMap) import Brick.AttrMap (AttrMap, AttrName, attrMap, attrName)
import Brick.Util (on) import Brick.Util (on)
import Brick.Types import Brick.Types
( Widget ( Widget
@ -56,7 +55,7 @@ vp3Size :: (Int, Int)
vp3Size = (25, 25) vp3Size = (25, 25)
selectedAttr :: AttrName selectedAttr :: AttrName
selectedAttr = "selected" selectedAttr = attrName "selected"
drawUi :: St -> [Widget Name] drawUi :: St -> [Widget Name]
drawUi st = [ui] drawUi st = [ui]

View File

@ -2,9 +2,6 @@
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
-- | This module provides types and functions for managing an attribute -- | This module provides types and functions for managing an attribute
-- map which maps attribute names ('AttrName') to attributes ('Attr'). -- map which maps attribute names ('AttrName') to attributes ('Attr').
-- This module is designed to be used with the 'OverloadedStrings'
-- language extension to permit easy construction of 'AttrName' values
-- and you should also use 'mappend' ('<>') to combine names.
-- --
-- Attribute maps work by mapping hierarchical attribute names to -- Attribute maps work by mapping hierarchical attribute names to
-- attributes and inheriting parent names' attributes when child names -- attributes and inheriting parent names' attributes when child names
@ -52,7 +49,6 @@ import Data.Bits ((.|.))
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Data.List (inits) import Data.List (inits)
import Data.String (IsString(..))
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Graphics.Vty (Attr(..), MaybeDefault(..), Style) import Graphics.Vty (Attr(..), MaybeDefault(..), Style)
@ -65,9 +61,9 @@ import Graphics.Vty (Attr(..), MaybeDefault(..), Style)
-- example: -- example:
-- --
-- @ -- @
-- "window" <> "border" -- attrName "window" <> attrName "border"
-- "window" <> "title" -- attrName "window" <> attrName "title"
-- "header" <> "clock" <> "seconds" -- attrName "header" <> attrName "clock" <> attrName "seconds"
-- @ -- @
data AttrName = AttrName [String] data AttrName = AttrName [String]
deriving (Show, Read, Eq, Ord, Generic, NFData) deriving (Show, Read, Eq, Ord, Generic, NFData)
@ -79,9 +75,6 @@ instance Monoid AttrName where
mempty = AttrName [] mempty = AttrName []
mappend = (Sem.<>) mappend = (Sem.<>)
instance IsString AttrName where
fromString = AttrName . (:[])
-- | An attribute map which maps 'AttrName' values to 'Attr' values. -- | An attribute map which maps 'AttrName' values to 'Attr' values.
data AttrMap = AttrMap Attr (M.Map AttrName Attr) data AttrMap = AttrMap Attr (M.Map AttrName Attr)
| ForceAttr Attr | ForceAttr Attr

View File

@ -642,15 +642,15 @@ toPassword s = txt $ T.replicate (T.length $ T.concat s) "*"
-- | The namespace for the other form attributes. -- | The namespace for the other form attributes.
formAttr :: AttrName formAttr :: AttrName
formAttr = "brickForm" formAttr = attrName "brickForm"
-- | The attribute for form input fields with invalid values. -- | The attribute for form input fields with invalid values.
invalidFormInputAttr :: AttrName invalidFormInputAttr :: AttrName
invalidFormInputAttr = formAttr <> "invalidInput" invalidFormInputAttr = formAttr <> attrName "invalidInput"
-- | The attribute for form input fields that have the focus. -- | The attribute for form input fields that have the focus.
focusedFormInputAttr :: AttrName focusedFormInputAttr :: AttrName
focusedFormInputAttr = formAttr <> "focusedInput" focusedFormInputAttr = formAttr <> attrName "focusedInput"
-- | Returns whether all form fields in the form currently have valid -- | Returns whether all form fields in the form currently have valid
-- values according to the fields' validation functions. This is useful -- values according to the fields' validation functions. This is useful

View File

@ -39,7 +39,7 @@ import qualified Brick.BorderMap as BM
-- | The top-level border attribute name. -- | The top-level border attribute name.
borderAttr :: AttrName borderAttr :: AttrName
borderAttr = "border" borderAttr = attrName "border"
-- | Draw the specified border element using the active border style -- | Draw the specified border element using the active border style
-- using 'borderAttr'. -- using 'borderAttr'.

View File

@ -1544,17 +1544,17 @@ viewport vpname typ p =
-- | The base attribute for scroll bars. -- | The base attribute for scroll bars.
scrollbarAttr :: AttrName scrollbarAttr :: AttrName
scrollbarAttr = "scrollbar" scrollbarAttr = attrName "scrollbar"
-- | The attribute for scroll bar troughs. This attribute is a -- | The attribute for scroll bar troughs. This attribute is a
-- specialization of @scrollbarAttr@. -- specialization of @scrollbarAttr@.
scrollbarTroughAttr :: AttrName scrollbarTroughAttr :: AttrName
scrollbarTroughAttr = scrollbarAttr <> "trough" scrollbarTroughAttr = scrollbarAttr <> attrName "trough"
-- | The attribute for scroll bar handles. This attribute is a -- | The attribute for scroll bar handles. This attribute is a
-- specialization of @scrollbarAttr@. -- specialization of @scrollbarAttr@.
scrollbarHandleAttr :: AttrName scrollbarHandleAttr :: AttrName
scrollbarHandleAttr = scrollbarAttr <> "handle" scrollbarHandleAttr = scrollbarAttr <> attrName "handle"
maybeClick :: (Ord n) maybeClick :: (Ord n)
=> n => n

View File

@ -99,15 +99,15 @@ dialog title buttonData w =
-- | The default attribute of the dialog -- | The default attribute of the dialog
dialogAttr :: AttrName dialogAttr :: AttrName
dialogAttr = "dialog" dialogAttr = attrName "dialog"
-- | The default attribute for all dialog buttons -- | The default attribute for all dialog buttons
buttonAttr :: AttrName buttonAttr :: AttrName
buttonAttr = "button" buttonAttr = attrName "button"
-- | The attribute for the selected dialog button (extends 'dialogAttr') -- | The attribute for the selected dialog button (extends 'dialogAttr')
buttonSelectedAttr :: AttrName buttonSelectedAttr :: AttrName
buttonSelectedAttr = buttonAttr <> "selected" buttonSelectedAttr = buttonAttr <> attrName "selected"
-- | Render a dialog with the specified body widget. This renders the -- | Render a dialog with the specified body widget. This renders the
-- dialog as a layer, which makes this suitable as a top-level layer in -- dialog as a layer, which makes this suitable as a top-level layer in

View File

@ -193,12 +193,12 @@ applyEdit f e = e & editContentsL %~ f
-- | The attribute assigned to the editor when it does not have focus. -- | The attribute assigned to the editor when it does not have focus.
editAttr :: AttrName editAttr :: AttrName
editAttr = "edit" editAttr = attrName "edit"
-- | The attribute assigned to the editor when it has focus. Extends -- | The attribute assigned to the editor when it has focus. Extends
-- 'editAttr'. -- 'editAttr'.
editFocusedAttr :: AttrName editFocusedAttr :: AttrName
editFocusedAttr = editAttr <> "focused" editFocusedAttr = editAttr <> attrName "focused"
-- | Get the contents of the editor. -- | Get the contents of the editor.
getEditContents :: Monoid t => Editor t n -> [t] getEditContents :: Monoid t => Editor t n -> [t]

View File

@ -165,7 +165,7 @@ import qualified System.FilePath as FP
import Text.Printf (printf) import Text.Printf (printf)
import Brick.Types import Brick.Types
import Brick.AttrMap (AttrName) import Brick.AttrMap (AttrName, attrName)
import Brick.Widgets.Core import Brick.Widgets.Core
import Brick.Widgets.List import Brick.Widgets.List
@ -837,49 +837,49 @@ attrForFileType UnixSocket = fileBrowserUnixSocketAttr
-- | The base attribute for all file browser attributes. -- | The base attribute for all file browser attributes.
fileBrowserAttr :: AttrName fileBrowserAttr :: AttrName
fileBrowserAttr = "fileBrowser" fileBrowserAttr = attrName "fileBrowser"
-- | The attribute used for the current directory displayed at the top -- | The attribute used for the current directory displayed at the top
-- of the browser. -- of the browser.
fileBrowserCurrentDirectoryAttr :: AttrName fileBrowserCurrentDirectoryAttr :: AttrName
fileBrowserCurrentDirectoryAttr = fileBrowserAttr <> "currentDirectory" fileBrowserCurrentDirectoryAttr = fileBrowserAttr <> attrName "currentDirectory"
-- | The attribute used for the entry information displayed at the -- | The attribute used for the entry information displayed at the
-- bottom of the browser. -- bottom of the browser.
fileBrowserSelectionInfoAttr :: AttrName fileBrowserSelectionInfoAttr :: AttrName
fileBrowserSelectionInfoAttr = fileBrowserAttr <> "selectionInfo" fileBrowserSelectionInfoAttr = fileBrowserAttr <> attrName "selectionInfo"
-- | The attribute used to render directory entries. -- | The attribute used to render directory entries.
fileBrowserDirectoryAttr :: AttrName fileBrowserDirectoryAttr :: AttrName
fileBrowserDirectoryAttr = fileBrowserAttr <> "directory" fileBrowserDirectoryAttr = fileBrowserAttr <> attrName "directory"
-- | The attribute used to render block device entries. -- | The attribute used to render block device entries.
fileBrowserBlockDeviceAttr :: AttrName fileBrowserBlockDeviceAttr :: AttrName
fileBrowserBlockDeviceAttr = fileBrowserAttr <> "block" fileBrowserBlockDeviceAttr = fileBrowserAttr <> attrName "block"
-- | The attribute used to render regular file entries. -- | The attribute used to render regular file entries.
fileBrowserRegularFileAttr :: AttrName fileBrowserRegularFileAttr :: AttrName
fileBrowserRegularFileAttr = fileBrowserAttr <> "regular" fileBrowserRegularFileAttr = fileBrowserAttr <> attrName "regular"
-- | The attribute used to render character device entries. -- | The attribute used to render character device entries.
fileBrowserCharacterDeviceAttr :: AttrName fileBrowserCharacterDeviceAttr :: AttrName
fileBrowserCharacterDeviceAttr = fileBrowserAttr <> "char" fileBrowserCharacterDeviceAttr = fileBrowserAttr <> attrName "char"
-- | The attribute used to render named pipe entries. -- | The attribute used to render named pipe entries.
fileBrowserNamedPipeAttr :: AttrName fileBrowserNamedPipeAttr :: AttrName
fileBrowserNamedPipeAttr = fileBrowserAttr <> "pipe" fileBrowserNamedPipeAttr = fileBrowserAttr <> attrName "pipe"
-- | The attribute used to render symbolic link entries. -- | The attribute used to render symbolic link entries.
fileBrowserSymbolicLinkAttr :: AttrName fileBrowserSymbolicLinkAttr :: AttrName
fileBrowserSymbolicLinkAttr = fileBrowserAttr <> "symlink" fileBrowserSymbolicLinkAttr = fileBrowserAttr <> attrName "symlink"
-- | The attribute used to render Unix socket entries. -- | The attribute used to render Unix socket entries.
fileBrowserUnixSocketAttr :: AttrName fileBrowserUnixSocketAttr :: AttrName
fileBrowserUnixSocketAttr = fileBrowserAttr <> "unixSocket" fileBrowserUnixSocketAttr = fileBrowserAttr <> attrName "unixSocket"
-- | The attribute used for selected entries in the file browser. -- | The attribute used for selected entries in the file browser.
fileBrowserSelectedAttr :: AttrName fileBrowserSelectedAttr :: AttrName
fileBrowserSelectedAttr = fileBrowserAttr <> "selected" fileBrowserSelectedAttr = fileBrowserAttr <> attrName "selected"
-- | A file type filter for use with 'setFileBrowserEntryFilter'. This -- | A file type filter for use with 'setFileBrowserEntryFilter'. This
-- filter permits entries whose file types are in the specified list. -- filter permits entries whose file types are in the specified list.

View File

@ -250,17 +250,17 @@ listMoveToEnd l = listMoveTo (max 0 $ length (listElements l) - 1) l
-- | The top-level attribute used for the entire list. -- | The top-level attribute used for the entire list.
listAttr :: AttrName listAttr :: AttrName
listAttr = "list" listAttr = attrName "list"
-- | The attribute used only for the currently-selected list item when -- | The attribute used only for the currently-selected list item when
-- the list does not have focus. Extends 'listAttr'. -- the list does not have focus. Extends 'listAttr'.
listSelectedAttr :: AttrName listSelectedAttr :: AttrName
listSelectedAttr = listAttr <> "selected" listSelectedAttr = listAttr <> attrName "selected"
-- | The attribute used only for the currently-selected list item when -- | The attribute used only for the currently-selected list item when
-- the list has focus. Extends 'listSelectedAttr'. -- the list has focus. Extends 'listSelectedAttr'.
listSelectedFocusedAttr :: AttrName listSelectedFocusedAttr :: AttrName
listSelectedFocusedAttr = listSelectedAttr <> "focused" listSelectedFocusedAttr = listSelectedAttr <> attrName "focused"
-- | Construct a list in terms of container 't' with element type 'e'. -- | Construct a list in terms of container 't' with element type 'e'.
list :: (Foldable t) list :: (Foldable t)

View File

@ -22,11 +22,11 @@ import Brick.Widgets.Core
-- | The attribute of the completed portion of the progress bar. -- | The attribute of the completed portion of the progress bar.
progressCompleteAttr :: AttrName progressCompleteAttr :: AttrName
progressCompleteAttr = "progressComplete" progressCompleteAttr = attrName "progressComplete"
-- | The attribute of the incomplete portion of the progress bar. -- | The attribute of the incomplete portion of the progress bar.
progressIncompleteAttr :: AttrName progressIncompleteAttr :: AttrName
progressIncompleteAttr = "progressIncomplete" progressIncompleteAttr = attrName "progressIncomplete"
-- | Draw a progress bar with the specified (optional) label and -- | Draw a progress bar with the specified (optional) label and
-- progress value. This fills available horizontal space and is one row -- progress value. This fills available horizontal space and is one row