{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Text.PrettyPrint.GHCi.Value (
prettyPrintValue, value2Doc,
ValuePrintConf(..),
defaultValueConf,
) where
import Text.PrettyPrint.GHCi.Value.Lexer
import Text.PrettyPrint.GHCi.Value.Parser
import System.Terminal.Utils
import Data.String ( fromString )
import Control.Exception ( catch, ErrorCall )
import System.IO ( stdout )
import qualified Data.List.NonEmpty as N
import Data.Text.Prettyprint.Doc
import Data.Text.Prettyprint.Doc.Render.Terminal
prettyPrintValue :: Bool -> String -> IO ()
prettyPrintValue smarter str = do
termSize <- getTerminalSize
let layoutOpts = LayoutOptions (AvailablePerLine (maybe 80 snd termSize) 1.0)
layoutAlgo = if smarter then layoutSmart else layoutPretty
rendered = layoutAlgo layoutOpts (value2Doc str)
renderIO stdout rendered `catch` \(_ :: ErrorCall) -> putStr str
value2Doc :: String -> Doc AnsiStyle
value2Doc shown = case parseValue shown of
Just v -> renderValue defaultValueConf v <> hardline
Nothing -> renderTokens defaultValueConf tokens
where
tokens = lexTokens shown
defaultValueConf :: ValuePrintConf
defaultValueConf = ValuePrintConf
{ vpc_number = color Cyan
, vpc_character = color Blue
, vpc_string = color Green
, vpc_control = bold <> color Magenta
, vpc_comma = color Yellow
, vpc_operator = color White
, vpc_field = italicized <> colorDull Red
, vpc_indent = 2
}
data ValuePrintConf = ValuePrintConf
{ vpc_number :: AnsiStyle
, vpc_character :: AnsiStyle
, vpc_string :: AnsiStyle
, vpc_control :: AnsiStyle
, vpc_comma :: AnsiStyle
, vpc_operator :: AnsiStyle
, vpc_field :: AnsiStyle
, vpc_indent :: Int
}
renderValue :: ValuePrintConf -> Value -> Doc AnsiStyle
renderValue vpc = renderVal
where
renderVal v = case v of
Num i -> num (fromString i)
Char c -> char (fromString c)
Str s -> string (fromString s)
List vs -> renderSeq (ctrl "[") (map (align . renderVal) vs) (ctrl "]")
Tuple vs -> renderSeq (ctrl "(") (map (align . renderVal) vs) (ctrl ")")
Prefix c [] -> fromString c
Prefix c vs ->
let args = map (align . renderVal) vs
in fromString c <> group (nest n (line <> align (vsep args)))
Infix arg0 ops ->
let tails = fmap (\(op,arg) -> optr (fromString op) <+> align (renderVal arg)) ops
in renderVal arg0 <> group (nest n (line <> align (vsep (N.toList tails))))
Record c vs ->
let fields = zipWith (\l (f,x) -> hsep [ l, field (fromString f)
, ctrl "=", align (renderVal x) ])
(ctrl "{" : repeat (coma ",")) (N.toList vs)
in fromString c <> group (nest n (line <> align (vcat fields) <+> ctrl "}"))
Paren x -> ctrl "(" <> align (renderVal x) <> ctrl ")"
renderSeq :: Doc AnsiStyle -> [Doc AnsiStyle] -> Doc AnsiStyle -> Doc AnsiStyle
renderSeq opn [] cls = opn <> cls
renderSeq opn vs cls = align . group . encloseSep opn' cls' (coma ", ") $ vs
where
opn' = flatAlt (opn <> space) opn
cls' = flatAlt (space <> cls) cls
n = vpc_indent vpc
num = annotate (vpc_number vpc)
char = annotate (vpc_character vpc)
string = annotate (vpc_string vpc)
ctrl = annotate (vpc_control vpc)
coma = annotate (vpc_comma vpc)
optr = annotate (vpc_operator vpc)
field = annotate (vpc_field vpc)
renderTokens :: ValuePrintConf -> [Token] -> Doc AnsiStyle
renderTokens vpc = mconcat . map renderTok
where
renderTok tok = case tok of
WhiteTok w -> renderWhite w
NumberTok i -> num (fromString i)
CharacterTok c -> char (fromString c)
StringTok s -> string (fromString s)
OpenBracket -> ctrl "["
CloseBracket -> ctrl "]"
OpenParen -> ctrl "("
CloseParen -> ctrl ")"
OpenBrace -> ctrl "{"
CloseBrace -> ctrl "}"
Equal -> ctrl "="
OperatorTok op -> optr (fromString op)
IdentifierTok c -> fromString c
Comma -> coma ","
renderWhite :: String -> Doc AnsiStyle
renderWhite "" = mempty
renderWhite str = let (ln, str') = span (/= '\n') str
in fromString ln <> hardline <> renderWhite (drop 1 str')
num = annotate (vpc_number vpc)
char = annotate (vpc_character vpc)
string = annotate (vpc_string vpc)
ctrl = annotate (vpc_control vpc)
coma = annotate (vpc_comma vpc)
optr = annotate (vpc_operator vpc)