properly centre menu headings
This commit is contained in:
parent
166483dc50
commit
097d51f34b
|
@ -36,7 +36,6 @@ module Mtlstats.Menu (
|
|||
|
||||
import Brick.Main (halt)
|
||||
import Brick.Types (BrickEvent (VtyEvent), Widget)
|
||||
import Brick.Widgets.Center (hCenter)
|
||||
import Control.Monad.State.Class (gets, modify)
|
||||
import Data.Char (toUpper)
|
||||
import qualified Data.Map as M
|
||||
|
@ -86,7 +85,7 @@ menuStateController menuFunc = Controller
|
|||
drawMenu :: Menu a -> Widget ()
|
||||
drawMenu m = let
|
||||
menuLines = lines $ show m
|
||||
in hCenter $ linesToWidget menuLines
|
||||
in linesToWidgetC menuLines
|
||||
|
||||
-- | The event handler for a 'Menu'
|
||||
menuHandler :: Menu a -> Handler a
|
||||
|
|
|
@ -19,8 +19,6 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
|
|||
|
||||
-}
|
||||
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
|
||||
module Mtlstats.Util
|
||||
( nth
|
||||
, modifyNth
|
||||
|
@ -29,9 +27,11 @@ module Mtlstats.Util
|
|||
, slice
|
||||
, capitalizeName
|
||||
, linesToWidget
|
||||
, linesToWidgetC
|
||||
) where
|
||||
|
||||
import Brick.Types (Widget)
|
||||
import Brick.Widgets.Center (hCenter)
|
||||
import Brick.Widgets.Core (str, vBox)
|
||||
import Data.Char (isSpace, toUpper)
|
||||
import qualified Data.Map as M
|
||||
|
@ -124,9 +124,15 @@ capitalizeName ch s = s ++ [ch']
|
|||
| isSpace c = lockFlag' cs
|
||||
| otherwise = False
|
||||
|
||||
-- | Converts a list of lines to a widget
|
||||
linesToWidget :: [String] -> Widget ()
|
||||
linesToWidget = vBox . map
|
||||
( str . \case
|
||||
"" -> " "
|
||||
s -> s
|
||||
)
|
||||
linesToWidget = vBox . map (str . keepBlank)
|
||||
|
||||
-- | Converts a list of lines to a widget with each line horizontally
|
||||
-- centered
|
||||
linesToWidgetC :: [String] -> Widget ()
|
||||
linesToWidgetC = vBox . map (hCenter . str . keepBlank)
|
||||
|
||||
keepBlank :: String -> String
|
||||
keepBlank "" = " "
|
||||
keepBlank s = s
|
||||
|
|
Loading…
Reference in New Issue
Block a user