{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
module Cli.Extras.TerminalString
( TerminalString(..)
, render
, putStrWithSGR
, getTerminalWidth
, enquiryCode
) where
import Control.Monad (when)
import Control.Monad.Catch (bracket_)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Reader (MonadIO)
import Data.Semigroup ((<>))
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import System.Console.ANSI
import qualified System.Console.Terminal.Size as TerminalSize
import System.IO (Handle)
data TerminalString
= TerminalString_Normal Text
| TerminalString_Colorized Color Text
deriving (Eq, Show, Ord)
printableLength :: [TerminalString] -> Int
printableLength = T.length . toText False
render
:: Bool
-> Maybe Int
-> [TerminalString]
-> Text
render withColor w ts = trim w $ toText withColor ts
where
trim = \case
Nothing -> id
Just n -> \s -> if printableLength ts > n
then T.take (n-3) s <> "..." <> T.pack resetCode
else s
toText :: Bool -> [TerminalString] -> Text
toText withColor = mconcat . map (toText' withColor)
toText' :: Bool -> TerminalString -> Text
toText' withColor = \case
TerminalString_Normal s -> s
TerminalString_Colorized c s -> if withColor then colorizeText c s else s
colorizeText :: Color -> Text -> Text
colorizeText color s = mconcat
[ T.pack $ setSGRCode [SetColor Foreground Vivid color]
, s
, T.pack resetCode
]
putStrWithSGR :: MonadIO m => [SGR] -> Handle -> Bool -> Text -> m ()
putStrWithSGR sgr h withNewLine s = liftIO $ bracket_ (hSetSGR h sgr) reset $ T.hPutStr h s
where
reset = hSetSGR h [Reset] >> newline
newline = when withNewLine $ T.hPutStrLn h ""
enquiryCode :: String
enquiryCode = "\ENQ"
resetCode :: String
resetCode = setSGRCode [Reset]
getTerminalWidth :: IO (Maybe Int)
getTerminalWidth = fmap TerminalSize.width <$> TerminalSize.size