mtlstats/src/Mtlstats/Control/TitleScreen.hs

141 lines
2.9 KiB
Haskell

{- |
mtlstats
Copyright (C) Rhéal Lamothe
<rheal.lamothe@gmail.com>
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or (at
your option) any later version.
This program is distributed in the hope that it will be useful, but
WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
General Public License for more details.
You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE LambdaCase #-}
module Mtlstats.Control.TitleScreen (titleScreenC) where
import Brick.Types (BrickEvent (VtyEvent))
import Brick.Widgets.Center (hCenter)
import Brick.Widgets.Core (str, vBox)
import Control.Monad.State.Class (modify)
import Data.Char (chr)
import Graphics.Vty.Input.Events (Event (EvKey))
import Mtlstats.Actions
import Mtlstats.Types
titleScreenC :: Controller
titleScreenC = Controller
{ drawController = const $ vBox $ map (hCenter . str)
$ [ ""
, "MONTREAL CANADIENS STATISTICS"
]
++ titleText
++ [ ""
, "Copyright (C) 1984, 1985, 2019-2021, 2023 Rhéal Lamothe"
, "<rheal.lamothe@gmail.com>"
, ""
, "Press any key to continue..."
]
, handleController = \case
VtyEvent (EvKey _ _) -> modify backHome
_ -> return ()
}
titleText :: [String]
titleText = box $ map (map blockify) $ foldl joinBlocks (repeat "")
[chM, chT, chL, chS, chT, chA, chT, chS]
box :: [String] -> [String]
box strs
= [[tl] ++ replicate width horiz ++ [tr]]
++ map (\s -> [vert] ++ s ++ [vert]) strs
++ [[bl] ++ replicate width horiz ++ [br]]
where
width = length $ head strs
tl = chr 0x2554
tr = chr 0x2557
bl = chr 0x255a
br = chr 0x255d
horiz = chr 0x2550
vert = chr 0x2551
blockify :: Char -> Char
blockify = \case
'#' -> chr 0x2588
'>' -> chr 0x2590
'<' -> chr 0x258c
ch -> ch
joinBlocks :: [String] -> [String] -> [String]
joinBlocks = zipWith (++)
chM :: [String]
chM =
[ "##< >##"
, ">## ##<"
, ">##< >##<"
, ">### ###<"
, ">#######<"
, ">#<###>#<"
, ">#<>#<>#<"
, "##< >##"
]
chT :: [String]
chT =
[ ">########<"
, ">## ## ##<"
, ">#< ## >#<"
, " ## "
, " ## "
, " ## "
, " ## "
, " >##< "
]
chL :: [String]
chL =
[ "### "
, ">#< "
, ">#< "
, ">#< "
, ">#< "
, ">#< ##"
, ">#< >##"
, "#######"
]
chS :: [String]
chS =
[ " #####< "
, ">#< ## "
, "## "
, " #####< "
, " >#<"
, " ##"
, ">#< >#<"
, " ###### "
]
chA :: [String]
chA =
[ " >##< "
, " ## "
, " >##< "
, " #### "
, " >#<>#< "
, " ###### "
, ">#< >#<"
, "### ###"
]