{- - Copyright (C) 2022 Nikola Hadžić - - This file is part of weatherhs. - - weatherhs 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. - - weatherhs 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 weatherhs. If not, see . -} module Draw where import Data.List.Extra (dropEnd) import Text.Printf (printf) minTermWidth :: Word minTermWidth = 5 -- Header nesting level. data HeaderStrength = H1 | H2 | H3 -- Draws table header. drawHeader :: Word -> HeaderStrength -> String -> String drawHeader termWidth headStrength text | termWidth < minTermWidth = error (printf "Minimum terminal width for drawing not satisfied: %u < %u" termWidth minTermWidth) | otherwise = do let textLength = fromIntegral (length text) :: Word let textSpace = termWidth - (minTermWidth - 1) let excess = if textLength > textSpace then textLength - textSpace else 0 let position = (termWidth `div` 2 + 1) - ((textLength - excess) `div` 2) let sepTopLeft = case headStrength of H1 -> '┏' _ -> '┠' let sepTopRight = case headStrength of H1 -> '┓' _ -> '┨' let sepHor = case headStrength of H1 -> '━' H2 -> '─' H3 -> '╌' let sepVer = '┃' let sepBotLeft = case headStrength of H1 -> '┣' _ -> '┠' let sepBotRight = case headStrength of H1 -> '┫' _ -> '┨' printf "%s\n%c \o33[%uG%s%s\o33[0m\o33[%uG %c\n%s" (sepTopLeft : (replicate (fromIntegral (termWidth - 2) :: Int) sepHor) ++ [sepTopRight]) sepVer position (case headStrength of H1 -> "\o33[1m\o33[3m" H2 -> "\o33[1m" H3 -> "\o33[3m") ((if excess == 0 then id else (++ "…") . (dropEnd ((fromIntegral excess :: Int) + 1))) text) (termWidth - 1) sepVer (sepBotLeft : (replicate (fromIntegral (termWidth - 2) :: Int) sepHor) ++ [sepBotRight]) -- Draws table field. drawField :: Word -> String -> String -> String drawField termWidth name value | termWidth < minTermWidth = error (printf "Minimum terminal width for drawing not satisfied: %u < %u" termWidth minTermWidth) | otherwise = do let nameLength = fromIntegral (length name) :: Word let valueLength = fromIntegral (length value) :: Word let textLength = nameLength + valueLength + 2 let textSpace = termWidth - (minTermWidth - 1) let excess = if textLength > textSpace then textLength - textSpace else 0 let inter = if excess == 0 then textSpace - textLength else 0 let sep = '┃' let field = printf "%s: %s%s" name (replicate (fromIntegral inter :: Int) ' ') value printf "%c %s %c" sep ((if excess == 0 then id else (++ "…") . (dropEnd ((fromIntegral excess :: Int) + 1))) field) sep -- Draws table footer. drawFooter :: Word -> String drawFooter termWidth | termWidth < minTermWidth = error (printf "Minimum terminal width for drawing not satisfied: %u < %u" termWidth minTermWidth) | otherwise = '┗' : (replicate (fromIntegral (termWidth - 2) :: Int) '━') ++ "┛"