aboutsummaryrefslogtreecommitdiffhomepage
path: root/Brick/Widgets/DefnList.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Brick/Widgets/DefnList.hs')
-rw-r--r--Brick/Widgets/DefnList.hs37
1 files changed, 29 insertions, 8 deletions
diff --git a/Brick/Widgets/DefnList.hs b/Brick/Widgets/DefnList.hs
index 5750cdc..090428f 100644
--- a/Brick/Widgets/DefnList.hs
+++ b/Brick/Widgets/DefnList.hs
@@ -1,13 +1,34 @@
-module Brick.Widgets.DefnList (defnList) where
+{-# LANGUAGE OverloadedStrings #-}
+module Brick.Widgets.DefnList (defnList, Align(..)) where
+
+import Data.Monoid
+import qualified Data.Text as T
+import qualified Graphics.Vty as V
+
+import Brick.Markup (markup)
import Brick.Types
import Brick.Widgets.Core
+import Data.Text.Markup ((@@))
+
+data Align = AlignLeft | AlignRight
+ deriving (Eq)
-defnList :: [(String, String)] -> Widget ()
-defnList defns = vBox $ line <$> defns
+defnList :: Align -> Maybe V.Attr -> [(String, String)] -> Widget ()
+defnList align attr defns = vBox $ line <$> defns
where
- line (label, content) = str $
- label ++ sep ++ (gap label content) ++ content
- gap a b = take (maxWidth - length a - length b - length sep) $ repeat ' '
- maxWidth = maximum $ map (\(x,y) -> length sep + length x + length y) defns
- sep = ": "
+ line (label, content) = markup $
+ (T.pack label @@ labelAttr) <> (T.pack sep @@ V.defAttr)
+ <> (if align == AlignRight
+ then (T.pack (gap label content) @@ V.defAttr)
+ else mempty
+ )
+ <> (T.pack content @@ V.defAttr)
+
+ gap a b = take (maxWidth - length a - length b - length sep) $
+ repeat ' '
+ maxWidth = maximum $
+ map (\(x,y) -> length sep + length x + length y) defns
+ sep = if align == AlignRight then ": " else ": "
+
+ labelAttr = maybe V.defAttr id attr