#include "version-compatibility-macros.h"
module Data.Text.Prettyprint.Doc.Render.Terminal.Internal where
import Control.Applicative
import Control.Monad.ST
import Data.IORef
import Data.Maybe
import Data.Semigroup
import Data.STRef
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TLB
import qualified System.Console.ANSI as ANSI
import System.IO (Handle, hPutChar, stdout)
import Data.Text.Prettyprint.Doc
import Data.Text.Prettyprint.Doc.Render.Util.Panic
data Color = Black | Red | Green | Yellow | Blue | Magenta | Cyan | White
deriving (Eq, Ord, Show)
data Intensity = Vivid | Dull
deriving (Eq, Ord, Show)
data Layer = Foreground | Background
deriving (Eq, Ord, Show)
data Bold = Bold deriving (Eq, Ord, Show)
data Underlined = Underlined deriving (Eq, Ord, Show)
data Italicized = Italicized deriving (Eq, Ord, Show)
color :: Color -> AnsiStyle
color c = mempty { ansiForeground = Just (Vivid, c) }
bgColor :: Color -> AnsiStyle
bgColor c = mempty { ansiBackground = Just (Vivid, c) }
colorDull :: Color -> AnsiStyle
colorDull c = mempty { ansiForeground = Just (Dull, c) }
bgColorDull :: Color -> AnsiStyle
bgColorDull c = mempty { ansiBackground = Just (Dull, c) }
bold :: AnsiStyle
bold = mempty { ansiBold = Just Bold }
italicized :: AnsiStyle
italicized = mempty { ansiItalics = Just Italicized }
underlined :: AnsiStyle
underlined = mempty { ansiUnderlining = Just Underlined }
renderLazy :: SimpleDocStream AnsiStyle -> TL.Text
renderLazy sdoc = runST (do
styleStackRef <- newSTRef [mempty]
outputRef <- newSTRef mempty
let push x = modifySTRef' styleStackRef (x :)
unsafePeek = readSTRef styleStackRef >>= \case
[] -> panicPeekedEmpty
x:_ -> pure x
unsafePop = readSTRef styleStackRef >>= \case
[] -> panicPeekedEmpty
x:xs -> writeSTRef styleStackRef xs >> pure x
writeOutput x = modifySTRef outputRef (<> x)
let go = \case
SFail -> panicUncaughtFail
SEmpty -> pure ()
SChar c rest -> do
writeOutput (TLB.singleton c)
go rest
SText _ t rest -> do
writeOutput (TLB.fromText t)
go rest
SLine i rest -> do
writeOutput (TLB.singleton '\n' <> TLB.fromText (T.replicate i " "))
go rest
SAnnPush style rest -> do
currentStyle <- unsafePeek
let newStyle = style <> currentStyle
push newStyle
writeOutput (TLB.fromText (styleToRawText newStyle))
go rest
SAnnPop rest -> do
_currentStyle <- unsafePop
newStyle <- unsafePeek
writeOutput (TLB.fromText (styleToRawText newStyle))
go rest
go sdoc
readSTRef styleStackRef >>= \case
[] -> panicStyleStackFullyConsumed
[_] -> fmap TLB.toLazyText (readSTRef outputRef)
xs -> panicStyleStackNotFullyConsumed (length xs) )
renderIO :: Handle -> SimpleDocStream AnsiStyle -> IO ()
renderIO h sdoc = do
styleStackRef <- newIORef [mempty]
let push x = modifyIORef' styleStackRef (x :)
unsafePeek = readIORef styleStackRef >>= \case
[] -> panicPeekedEmpty
x:_ -> pure x
unsafePop = readIORef styleStackRef >>= \case
[] -> panicPeekedEmpty
x:xs -> writeIORef styleStackRef xs >> pure x
let go = \case
SFail -> panicUncaughtFail
SEmpty -> pure ()
SChar c rest -> do
hPutChar h c
go rest
SText _ t rest -> do
T.hPutStr h t
go rest
SLine i rest -> do
hPutChar h '\n'
T.hPutStr h (T.replicate i " ")
go rest
SAnnPush style rest -> do
currentStyle <- unsafePeek
let newStyle = style <> currentStyle
push newStyle
T.hPutStr h (styleToRawText newStyle)
go rest
SAnnPop rest -> do
_currentStyle <- unsafePop
newStyle <- unsafePeek
T.hPutStr h (styleToRawText newStyle)
go rest
go sdoc
readIORef styleStackRef >>= \case
[] -> panicStyleStackFullyConsumed
[_] -> pure ()
xs -> panicStyleStackNotFullyConsumed (length xs)
panicStyleStackFullyConsumed :: void
panicStyleStackFullyConsumed
= error ("There is no empty style left at the end of rendering" ++
" (but there should be). Please report this as a bug.")
panicStyleStackNotFullyConsumed :: Int -> void
panicStyleStackNotFullyConsumed len
= error ("There are " <> show len <> " styles left at the" ++
"end of rendering (there should be only 1). Please report" ++
" this as a bug.")
data AnsiStyle = SetAnsiStyle
{ ansiForeground :: Maybe (Intensity, Color)
, ansiBackground :: Maybe (Intensity, Color)
, ansiBold :: Maybe Bold
, ansiItalics :: Maybe Italicized
, ansiUnderlining :: Maybe Underlined
} deriving (Eq, Ord, Show)
instance Semigroup AnsiStyle where
cs1 <> cs2 = SetAnsiStyle
{ ansiForeground = ansiForeground cs1 <|> ansiForeground cs2
, ansiBackground = ansiBackground cs1 <|> ansiBackground cs2
, ansiBold = ansiBold cs1 <|> ansiBold cs2
, ansiItalics = ansiItalics cs1 <|> ansiItalics cs2
, ansiUnderlining = ansiUnderlining cs1 <|> ansiUnderlining cs2 }
instance Monoid AnsiStyle where
mempty = SetAnsiStyle Nothing Nothing Nothing Nothing Nothing
mappend = (<>)
styleToRawText :: AnsiStyle -> Text
styleToRawText = T.pack . ANSI.setSGRCode . stylesToSgrs
where
stylesToSgrs :: AnsiStyle -> [ANSI.SGR]
stylesToSgrs (SetAnsiStyle fg bg b i u) = catMaybes
[ Just ANSI.Reset
, fmap (\(intensity, c) -> ANSI.SetColor ANSI.Foreground (convertIntensity intensity) (convertColor c)) fg
, fmap (\(intensity, c) -> ANSI.SetColor ANSI.Background (convertIntensity intensity) (convertColor c)) bg
, fmap (\_ -> ANSI.SetConsoleIntensity ANSI.BoldIntensity) b
, fmap (\_ -> ANSI.SetItalicized True) i
, fmap (\_ -> ANSI.SetUnderlining ANSI.SingleUnderline) u
]
convertIntensity :: Intensity -> ANSI.ColorIntensity
convertIntensity = \case
Vivid -> ANSI.Vivid
Dull -> ANSI.Dull
convertColor :: Color -> ANSI.Color
convertColor = \case
Black -> ANSI.Black
Red -> ANSI.Red
Green -> ANSI.Green
Yellow -> ANSI.Yellow
Blue -> ANSI.Blue
Magenta -> ANSI.Magenta
Cyan -> ANSI.Cyan
White -> ANSI.White
renderStrict :: SimpleDocStream AnsiStyle -> Text
renderStrict = TL.toStrict . renderLazy
putDoc :: Doc AnsiStyle -> IO ()
putDoc = hPutDoc stdout
hPutDoc :: Handle -> Doc AnsiStyle -> IO ()
hPutDoc h doc = renderIO h (layoutPretty defaultLayoutOptions doc)