{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK hide #-}
module System.Console.Byline.Internal.Render
( RenderMode (..)
, render
, renderText
) where
import Control.Applicative
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Word
import System.Console.ANSI as ANSI
import System.IO (Handle, hPutStr)
import System.Console.Byline.Internal.Color as C
import System.Console.Byline.Internal.Types
import System.Console.Byline.Stylized
import Prelude
data RenderMode = Plain
| Simple
| Term256
data RenderInstruction = RenderText Text
| RenderSGR [SGR]
render :: RenderMode -> Handle -> Stylized -> IO ()
render mode h stylized = mapM_ go (renderInstructions mode stylized)
where
go :: RenderInstruction -> IO ()
go (RenderText t) = hPutStr h (Text.unpack t)
go (RenderSGR s) = hSetSGR h s
renderText :: RenderMode -> Stylized -> Text
renderText mode stylized = Text.concat $ map go (renderInstructions mode stylized)
where
go :: RenderInstruction -> Text
go (RenderText t) = t
go (RenderSGR _) = Text.empty
renderInstructions :: RenderMode -> Stylized -> [RenderInstruction]
renderInstructions mode = concat . mapStylized renderMod
where
renderMod :: (Text, Modifier) -> [RenderInstruction]
renderMod (t, m) =
case mode of
Plain -> [ RenderText t ]
_ -> [ RenderSGR (modToSGR m)
, RenderText (modToText mode m)
, RenderText t
, RenderSGR [Reset]
]
modToSGR :: Modifier -> [SGR]
modToSGR m =
catMaybes [ SetColor Foreground Dull <$> modColor modColorFG
, SetColor Background Dull <$> modColor modColorBG
, SetConsoleIntensity <$> modIntensity
, SetUnderlining <$> modUnderlining
, SetSwapForegroundBackground <$> modSwapForegroundBackground
]
where
modColor :: (Modifier -> OnlyOne C.Color) -> Maybe ANSI.Color
modColor f = C.colorAsANSI <$> unOne (f m)
modIntensity :: Maybe ConsoleIntensity
modIntensity = case modBold m of
Off -> Nothing
On -> Just BoldIntensity
modUnderlining :: Maybe Underlining
modUnderlining = case modUnderline m of
Off -> Nothing
On -> Just SingleUnderline
modSwapForegroundBackground :: Maybe Bool
modSwapForegroundBackground = case modSwapFgBg m of
Off -> Nothing
On -> Just True
modToText :: RenderMode -> Modifier -> Text
modToText Plain _ = Text.empty
modToText Simple _ = Text.empty
modToText Term256 m =
Text.concat $ catMaybes [ escape Foreground <$> modColor modColorFG
, escape Background <$> modColor modColorBG
]
where
modColor :: (Modifier -> OnlyOne C.Color) -> Maybe (Word8, Word8, Word8)
modColor f = case unOne (f m) of
Just (ColorRGB c) -> Just c
_ -> Nothing
escape :: ConsoleLayer -> (Word8, Word8, Word8) -> Text
escape Foreground c = Text.concat ["\ESC[38;5;", colorIndex c, "m"]
escape Background c = Text.concat ["\ESC[48;5;", colorIndex c, "m"]
colorIndex :: (Word8, Word8, Word8) -> Text
colorIndex c = Text.pack $ show (nearestColor c term256Locations)