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 :: forall n. Widget n -> Widget n
hCenter = forall n. Maybe Char -> Widget n -> Widget n
hCenterWith forall a. Maybe a
Nothing
hCenterLayer :: Widget n -> Widget n
hCenterLayer :: forall n. Widget n -> Widget n
hCenterLayer Widget n
p =
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Greedy (forall n. Widget n -> Size
vSize Widget n
p) forall a b. (a -> b) -> a -> b
$ do
Result n
result <- forall n. Widget n -> RenderM n (Result n)
render Widget n
p
Context n
c <- forall n. RenderM n (Context n)
getContext
let rWidth :: Int
rWidth = Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Image -> Int
imageWidth
leftPaddingAmount :: Int
leftPaddingAmount = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ (Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availWidthL forall a. Num a => a -> a -> a
- Int
rWidth) forall a. Integral a => a -> a -> a
`div` Int
2
paddedImage :: Image
paddedImage = Int -> Image -> Image
translateX Int
leftPaddingAmount forall a b. (a -> b) -> a -> b
$ Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageL
off :: Location
off = (Int, Int) -> Location
Location (Int
leftPaddingAmount, Int
0)
if Int
leftPaddingAmount forall a. Eq a => a -> a -> Bool
== Int
0 then
forall (m :: * -> *) a. Monad m => a -> m a
return Result n
result else
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall n. Location -> Result n -> Result n
addResultOffset Location
off
forall a b. (a -> b) -> a -> b
$ Result n
result forall a b. a -> (a -> b) -> b
& forall n. Lens' (Result n) Image
imageL forall s t a b. ASetter s t a b -> b -> s -> t
.~ Image
paddedImage
hCenterWith :: Maybe Char -> Widget n -> Widget n
hCenterWith :: forall n. Maybe Char -> Widget n -> Widget n
hCenterWith Maybe Char
mChar Widget n
p =
let ch :: Char
ch = forall a. a -> Maybe a -> a
fromMaybe Char
' ' Maybe Char
mChar
in forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Greedy (forall n. Widget n -> Size
vSize Widget n
p) forall a b. (a -> b) -> a -> b
$ do
Result n
result <- forall n. Widget n -> RenderM n (Result n)
render Widget n
p
Context n
c <- forall n. RenderM n (Context n)
getContext
let rWidth :: Int
rWidth = Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Image -> Int
imageWidth
rHeight :: Int
rHeight = Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Image -> Int
imageHeight
remainder :: Int
remainder = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availWidthL forall a. Num a => a -> a -> a
- (Int
leftPaddingAmount forall a. Num a => a -> a -> a
* Int
2)
leftPaddingAmount :: Int
leftPaddingAmount = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ (Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availWidthL forall a. Num a => a -> a -> a
- Int
rWidth) forall a. Integral a => a -> a -> a
`div` Int
2
rightPaddingAmount :: Int
rightPaddingAmount = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ Int
leftPaddingAmount forall a. Num a => a -> a -> a
+ Int
remainder
leftPadding :: Image
leftPadding = forall d. Integral d => Attr -> Char -> d -> d -> Image
charFill (Context n
cforall s a. s -> Getting a s a -> a
^.forall r n. Getting r (Context n) Attr
attrL) Char
ch Int
leftPaddingAmount Int
rHeight
rightPadding :: Image
rightPadding = forall d. Integral d => Attr -> Char -> d -> d -> Image
charFill (Context n
cforall s a. s -> Getting a s a -> a
^.forall r n. Getting r (Context n) Attr
attrL) Char
ch Int
rightPaddingAmount Int
rHeight
paddedImage :: Image
paddedImage = [Image] -> Image
horizCat [ Image
leftPadding
, Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageL
, Image
rightPadding
]
off :: Location
off = (Int, Int) -> Location
Location (Int
leftPaddingAmount, Int
0)
if Int
leftPaddingAmount forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Int
rightPaddingAmount forall a. Eq a => a -> a -> Bool
== Int
0 then
forall (m :: * -> *) a. Monad m => a -> m a
return Result n
result else
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall n. Location -> Result n -> Result n
addResultOffset Location
off
forall a b. (a -> b) -> a -> b
$ Result n
result forall a b. a -> (a -> b) -> b
& forall n. Lens' (Result n) Image
imageL forall s t a b. ASetter s t a b -> b -> s -> t
.~ Image
paddedImage
vCenter :: Widget n -> Widget n
vCenter :: forall n. Widget n -> Widget n
vCenter = forall n. Maybe Char -> Widget n -> Widget n
vCenterWith forall a. Maybe a
Nothing
vCenterLayer :: Widget n -> Widget n
vCenterLayer :: forall n. Widget n -> Widget n
vCenterLayer Widget n
p =
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget (forall n. Widget n -> Size
hSize Widget n
p) Size
Greedy forall a b. (a -> b) -> a -> b
$ do
Result n
result <- forall n. Widget n -> RenderM n (Result n)
render Widget n
p
Context n
c <- forall n. RenderM n (Context n)
getContext
let rHeight :: Int
rHeight = Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Image -> Int
imageHeight
topPaddingAmount :: Int
topPaddingAmount = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ (Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availHeightL forall a. Num a => a -> a -> a
- Int
rHeight) forall a. Integral a => a -> a -> a
`div` Int
2
paddedImage :: Image
paddedImage = Int -> Image -> Image
translateY Int
topPaddingAmount forall a b. (a -> b) -> a -> b
$ Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageL
off :: Location
off = (Int, Int) -> Location
Location (Int
0, Int
topPaddingAmount)
if Int
topPaddingAmount forall a. Eq a => a -> a -> Bool
== Int
0 then
forall (m :: * -> *) a. Monad m => a -> m a
return Result n
result else
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall n. Location -> Result n -> Result n
addResultOffset Location
off
forall a b. (a -> b) -> a -> b
$ Result n
result forall a b. a -> (a -> b) -> b
& forall n. Lens' (Result n) Image
imageL forall s t a b. ASetter s t a b -> b -> s -> t
.~ Image
paddedImage
vCenterWith :: Maybe Char -> Widget n -> Widget n
vCenterWith :: forall n. Maybe Char -> Widget n -> Widget n
vCenterWith Maybe Char
mChar Widget n
p =
let ch :: Char
ch = forall a. a -> Maybe a -> a
fromMaybe Char
' ' Maybe Char
mChar
in forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget (forall n. Widget n -> Size
hSize Widget n
p) Size
Greedy forall a b. (a -> b) -> a -> b
$ do
Result n
result <- forall n. Widget n -> RenderM n (Result n)
render Widget n
p
Context n
c <- forall n. RenderM n (Context n)
getContext
let rWidth :: Int
rWidth = Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Image -> Int
imageWidth
rHeight :: Int
rHeight = Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Image -> Int
imageHeight
remainder :: Int
remainder = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availHeightL forall a. Num a => a -> a -> a
- (Int
topPaddingAmount forall a. Num a => a -> a -> a
* Int
2)
topPaddingAmount :: Int
topPaddingAmount = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ (Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availHeightL forall a. Num a => a -> a -> a
- Int
rHeight) forall a. Integral a => a -> a -> a
`div` Int
2
bottomPaddingAmount :: Int
bottomPaddingAmount = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ Int
topPaddingAmount forall a. Num a => a -> a -> a
+ Int
remainder
topPadding :: Image
topPadding = forall d. Integral d => Attr -> Char -> d -> d -> Image
charFill (Context n
cforall s a. s -> Getting a s a -> a
^.forall r n. Getting r (Context n) Attr
attrL) Char
ch Int
rWidth Int
topPaddingAmount
bottomPadding :: Image
bottomPadding = forall d. Integral d => Attr -> Char -> d -> d -> Image
charFill (Context n
cforall s a. s -> Getting a s a -> a
^.forall r n. Getting r (Context n) Attr
attrL) Char
ch Int
rWidth Int
bottomPaddingAmount
paddedImage :: Image
paddedImage = [Image] -> Image
vertCat [ Image
topPadding
, Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageL
, Image
bottomPadding
]
off :: Location
off = (Int, Int) -> Location
Location (Int
0, Int
topPaddingAmount)
if Int
topPaddingAmount forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Int
bottomPaddingAmount forall a. Eq a => a -> a -> Bool
== Int
0 then
forall (m :: * -> *) a. Monad m => a -> m a
return Result n
result else
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall n. Location -> Result n -> Result n
addResultOffset Location
off
forall a b. (a -> b) -> a -> b
$ Result n
result forall a b. a -> (a -> b) -> b
& forall n. Lens' (Result n) Image
imageL forall s t a b. ASetter s t a b -> b -> s -> t
.~ Image
paddedImage
center :: Widget n -> Widget n
center :: forall n. Widget n -> Widget n
center = forall n. Maybe Char -> Widget n -> Widget n
centerWith forall a. Maybe a
Nothing
centerWith :: Maybe Char -> Widget n -> Widget n
centerWith :: forall n. Maybe Char -> Widget n -> Widget n
centerWith Maybe Char
c = forall n. Maybe Char -> Widget n -> Widget n
vCenterWith Maybe Char
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Maybe Char -> Widget n -> Widget n
hCenterWith Maybe Char
c
centerLayer :: Widget n -> Widget n
centerLayer :: forall n. Widget n -> Widget n
centerLayer = forall n. Widget n -> Widget n
vCenterLayer forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Widget n -> Widget n
hCenterLayer
centerAbout :: Location -> Widget n -> Widget n
centerAbout :: forall n. Location -> Widget n -> Widget n
centerAbout Location
l Widget n
p =
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Greedy Size
Greedy forall a b. (a -> b) -> a -> b
$ do
Context n
c <- forall n. RenderM n (Context n)
getContext
let centerW :: Int
centerW = Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availWidthL forall a. Integral a => a -> a -> a
`div` Int
2
centerH :: Int
centerH = Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availHeightL forall a. Integral a => a -> a -> a
`div` Int
2
off :: Location
off = (Int, Int) -> Location
Location ( Int
centerW forall a. Num a => a -> a -> a
- Location
lforall s a. s -> Getting a s a -> a
^.forall a. TerminalLocation a => Lens' a Int
locationColumnL
, Int
centerH forall a. Num a => a -> a -> a
- Location
lforall s a. s -> Getting a s a -> a
^.forall a. TerminalLocation a => Lens' a Int
locationRowL
)
Result n
result <- forall n. Widget n -> RenderM n (Result n)
render forall a b. (a -> b) -> a -> b
$ forall n. Location -> Widget n -> Widget n
translateBy Location
off Widget n
p
let rightPaddingAmt :: Int
rightPaddingAmt = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availWidthL forall a. Num a => a -> a -> a
- Image -> Int
imageWidth (Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageL)
bottomPaddingAmt :: Int
bottomPaddingAmt = forall a. Ord a => a -> a -> a
max Int
0 forall a b. (a -> b) -> a -> b
$ Context n
cforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Context n) Int
availHeightL forall a. Num a => a -> a -> a
- Image -> Int
imageHeight (Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageL)
rightPadding :: Image
rightPadding = forall d. Integral d => Attr -> Char -> d -> d -> Image
charFill (Context n
cforall s a. s -> Getting a s a -> a
^.forall r n. Getting r (Context n) Attr
attrL) Char
' ' Int
rightPaddingAmt (Image -> Int
imageHeight forall a b. (a -> b) -> a -> b
$ Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageL)
bottomPadding :: Image
bottomPadding = forall d. Integral d => Attr -> Char -> d -> d -> Image
charFill (Context n
cforall s a. s -> Getting a s a -> a
^.forall r n. Getting r (Context n) Attr
attrL) Char
' ' (Image -> Int
imageWidth forall a b. (a -> b) -> a -> b
$ Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageL) Int
bottomPaddingAmt
paddedImg :: Image
paddedImg = [Image] -> Image
horizCat [[Image] -> Image
vertCat [Result n
resultforall s a. s -> Getting a s a -> a
^.forall n. Lens' (Result n) Image
imageL, Image
bottomPadding], Image
rightPadding]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Result n
result forall a b. a -> (a -> b) -> b
& forall n. Lens' (Result n) Image
imageL forall s t a b. ASetter s t a b -> b -> s -> t
.~ Image
paddedImg