switch from ncurses to brick #1

Merged
jlamothe merged 21 commits from brick into dev 2023-06-02 15:28:41 -04:00
2 changed files with 14 additions and 9 deletions
Showing only changes of commit 097d51f34b - Show all commits

View File

@ -36,7 +36,6 @@ module Mtlstats.Menu (
import Brick.Main (halt) import Brick.Main (halt)
import Brick.Types (BrickEvent (VtyEvent), Widget) import Brick.Types (BrickEvent (VtyEvent), Widget)
import Brick.Widgets.Center (hCenter)
import Control.Monad.State.Class (gets, modify) import Control.Monad.State.Class (gets, modify)
import Data.Char (toUpper) import Data.Char (toUpper)
import qualified Data.Map as M import qualified Data.Map as M
@ -86,7 +85,7 @@ menuStateController menuFunc = Controller
drawMenu :: Menu a -> Widget () drawMenu :: Menu a -> Widget ()
drawMenu m = let drawMenu m = let
menuLines = lines $ show m menuLines = lines $ show m
in hCenter $ linesToWidget menuLines in linesToWidgetC menuLines
-- | The event handler for a 'Menu' -- | The event handler for a 'Menu'
menuHandler :: Menu a -> Handler a menuHandler :: Menu a -> Handler a

View File

@ -19,8 +19,6 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE LambdaCase #-}
module Mtlstats.Util module Mtlstats.Util
( nth ( nth
, modifyNth , modifyNth
@ -29,9 +27,11 @@ module Mtlstats.Util
, slice , slice
, capitalizeName , capitalizeName
, linesToWidget , linesToWidget
, linesToWidgetC
) where ) where
import Brick.Types (Widget) import Brick.Types (Widget)
import Brick.Widgets.Center (hCenter)
import Brick.Widgets.Core (str, vBox) import Brick.Widgets.Core (str, vBox)
import Data.Char (isSpace, toUpper) import Data.Char (isSpace, toUpper)
import qualified Data.Map as M import qualified Data.Map as M
@ -124,9 +124,15 @@ capitalizeName ch s = s ++ [ch']
| isSpace c = lockFlag' cs | isSpace c = lockFlag' cs
| otherwise = False | otherwise = False
-- | Converts a list of lines to a widget
linesToWidget :: [String] -> Widget () linesToWidget :: [String] -> Widget ()
linesToWidget = vBox . map linesToWidget = vBox . map (str . keepBlank)
( str . \case
"" -> " " -- | Converts a list of lines to a widget with each line horizontally
s -> s -- centered
) linesToWidgetC :: [String] -> Widget ()
linesToWidgetC = vBox . map (hCenter . str . keepBlank)
keepBlank :: String -> String
keepBlank "" = " "
keepBlank s = s