module Brick.Widgets.Center
(
hCenter
, hCenterWith
, hCenterLayer
, vCenter
, vCenterWith
, vCenterLayer
, center
, centerWith
, centerLayer
, centerAbout
)
where
import Lens.Micro ((^.), (&), (.~), to)
import Data.Maybe (fromMaybe)
import Graphics.Vty (imageWidth, imageHeight, horizCat, charFill, vertCat,
translateX, translateY)
import Brick.Types
import Brick.Widgets.Core
hCenter :: Widget n -> Widget n
hCenter = hCenterWith Nothing
hCenterLayer :: Widget n -> Widget n
hCenterLayer p =
Widget Greedy (vSize p) $ do
result <- render p
c <- getContext
let rWidth = result^.imageL.to imageWidth
leftPaddingAmount = max 0 $ (c^.availWidthL - rWidth) `div` 2
paddedImage = translateX leftPaddingAmount $ result^.imageL
off = Location (leftPaddingAmount, 0)
if leftPaddingAmount == 0 then
return result else
return $ addResultOffset off
$ result & imageL .~ paddedImage
hCenterWith :: Maybe Char -> Widget n -> Widget n
hCenterWith mChar p =
let ch = fromMaybe ' ' mChar
in Widget Greedy (vSize p) $ do
result <- render p
c <- getContext
let rWidth = result^.imageL.to imageWidth
rHeight = result^.imageL.to imageHeight
remainder = max 0 $ c^.availWidthL - (leftPaddingAmount * 2)
leftPaddingAmount = max 0 $ (c^.availWidthL - rWidth) `div` 2
rightPaddingAmount = max 0 $ leftPaddingAmount + remainder
leftPadding = charFill (c^.attrL) ch leftPaddingAmount rHeight
rightPadding = charFill (c^.attrL) ch rightPaddingAmount rHeight
paddedImage = horizCat [ leftPadding
, result^.imageL
, rightPadding
]
off = Location (leftPaddingAmount, 0)
if leftPaddingAmount == 0 && rightPaddingAmount == 0 then
return result else
return $ addResultOffset off
$ result & imageL .~ paddedImage
vCenter :: Widget n -> Widget n
vCenter = vCenterWith Nothing
vCenterLayer :: Widget n -> Widget n
vCenterLayer p =
Widget (hSize p) Greedy $ do
result <- render p
c <- getContext
let rHeight = result^.imageL.to imageHeight
topPaddingAmount = max 0 $ (c^.availHeightL - rHeight) `div` 2
paddedImage = translateY topPaddingAmount $ result^.imageL
off = Location (0, topPaddingAmount)
if topPaddingAmount == 0 then
return result else
return $ addResultOffset off
$ result & imageL .~ paddedImage
vCenterWith :: Maybe Char -> Widget n -> Widget n
vCenterWith mChar p =
let ch = fromMaybe ' ' mChar
in Widget (hSize p) Greedy $ do
result <- render p
c <- getContext
let rWidth = result^.imageL.to imageWidth
rHeight = result^.imageL.to imageHeight
remainder = max 0 $ c^.availHeightL - (topPaddingAmount * 2)
topPaddingAmount = max 0 $ (c^.availHeightL - rHeight) `div` 2
bottomPaddingAmount = max 0 $ topPaddingAmount + remainder
topPadding = charFill (c^.attrL) ch rWidth topPaddingAmount
bottomPadding = charFill (c^.attrL) ch rWidth bottomPaddingAmount
paddedImage = vertCat [ topPadding
, result^.imageL
, bottomPadding
]
off = Location (0, topPaddingAmount)
if topPaddingAmount == 0 && bottomPaddingAmount == 0 then
return result else
return $ addResultOffset off
$ result & imageL .~ paddedImage
center :: Widget n -> Widget n
center = centerWith Nothing
centerWith :: Maybe Char -> Widget n -> Widget n
centerWith c = vCenterWith c . hCenterWith c
centerLayer :: Widget n -> Widget n
centerLayer = vCenterLayer . hCenterLayer
centerAbout :: Location -> Widget n -> Widget n
centerAbout l p =
Widget Greedy Greedy $ do
c <- getContext
let centerW = c^.availWidthL `div` 2
centerH = c^.availHeightL `div` 2
off = Location ( centerW - l^.locationColumnL
, centerH - l^.locationRowL
)
result <- render $ translateBy off p
let rightPaddingAmt = max 0 $ c^.availWidthL - imageWidth (result^.imageL)
bottomPaddingAmt = max 0 $ c^.availHeightL - imageHeight (result^.imageL)
rightPadding = charFill (c^.attrL) ' ' rightPaddingAmt (imageHeight $ result^.imageL)
bottomPadding = charFill (c^.attrL) ' ' (imageWidth $ result^.imageL) bottomPaddingAmt
paddedImg = horizCat [vertCat [result^.imageL, bottomPadding], rightPadding]
return $ result & imageL .~ paddedImg