module Brick.Widgets.Border
(
border
, borderWithLabel
, hBorder
, hBorderWithLabel
, vBorder
, borderElem
, borderAttr
, vBorderAttr
, hBorderAttr
, hBorderLabelAttr
, tlCornerAttr
, trCornerAttr
, blCornerAttr
, brCornerAttr
)
where
import Data.Monoid ((<>))
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Lens.Micro ((^.), to)
import Graphics.Vty (imageHeight, imageWidth)
import Brick.AttrMap
import Brick.Types
import Brick.Widgets.Core
import Brick.Widgets.Center (hCenterWith)
import Brick.Widgets.Border.Style (BorderStyle(..))
borderAttr :: AttrName
borderAttr = "border"
vBorderAttr :: AttrName
vBorderAttr = borderAttr <> "vertical"
hBorderAttr :: AttrName
hBorderAttr = borderAttr <> "horizontal"
hBorderLabelAttr :: AttrName
hBorderLabelAttr = hBorderAttr <> "label"
tlCornerAttr :: AttrName
tlCornerAttr = borderAttr <> "corner" <> "tl"
trCornerAttr :: AttrName
trCornerAttr = borderAttr <> "corner" <> "tr"
blCornerAttr :: AttrName
blCornerAttr = borderAttr <> "corner" <> "bl"
brCornerAttr :: AttrName
brCornerAttr = borderAttr <> "corner" <> "br"
borderElem :: (BorderStyle -> Char) -> Widget n
borderElem f =
Widget Fixed Fixed $ do
bs <- ctxBorderStyle <$> getContext
render $ withAttr borderAttr $ str [f bs]
border :: Widget n -> Widget n
border = border_ Nothing
borderWithLabel :: Widget n
-> Widget n
-> Widget n
borderWithLabel label = border_ (Just label)
border_ :: Maybe (Widget n) -> Widget n -> Widget n
border_ label wrapped =
Widget (hSize wrapped) (vSize wrapped) $ do
bs <- ctxBorderStyle <$> getContext
c <- getContext
middleResult <- render $ hLimit (c^.availWidthL 2)
$ vLimit (c^.availHeightL 2)
$ wrapped
let top = (withAttr tlCornerAttr $ str [bsCornerTL bs])
<+> hBorder_ label <+>
(withAttr trCornerAttr $ str [bsCornerTR bs])
bottom = (withAttr blCornerAttr $ str [bsCornerBL bs])
<+> hBorder <+>
(withAttr brCornerAttr $ str [bsCornerBR bs])
middle = vBorder <+> (Widget Fixed Fixed $ return middleResult) <+> vBorder
total = top <=> middle <=> bottom
render $ hLimit (middleResult^.imageL.to imageWidth + 2)
$ vLimit (middleResult^.imageL.to imageHeight + 2)
$ total
hBorder :: Widget n
hBorder = hBorder_ Nothing
hBorderWithLabel :: Widget n
-> Widget n
hBorderWithLabel label = hBorder_ (Just label)
hBorder_ :: Maybe (Widget n) -> Widget n
hBorder_ label =
Widget Greedy Fixed $ do
bs <- ctxBorderStyle <$> getContext
let msg = maybe (str [bsHorizontal bs]) (withAttr hBorderLabelAttr) label
render $ vLimit 1 $ withAttr hBorderAttr $ hCenterWith (Just $ bsHorizontal bs) msg
vBorder :: Widget n
vBorder =
Widget Fixed Greedy $ do
bs <- ctxBorderStyle <$> getContext
render $ hLimit 1 $ withAttr vBorderAttr $ fill (bsVertical bs)