Skip to content

Commit

Permalink
fix: Fix showNode to display ANSI colours.
Browse files Browse the repository at this point in the history
Without this, tokstyle will not show colours in error messages.
  • Loading branch information
iphydf committed Nov 6, 2024
1 parent 94ea74a commit ed563ef
Show file tree
Hide file tree
Showing 2 changed files with 21 additions and 6 deletions.
2 changes: 1 addition & 1 deletion src/Language/Cimple/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -576,7 +576,7 @@ ppTranslationUnit :: [Node (Lexeme Text)] -> Doc AnsiStyle
ppTranslationUnit decls = (ppToplevel . map ppNode $ decls) <> line

showNode :: Node (Lexeme Text) -> Text
showNode = Text.pack . show . ppNode
showNode = render . ppNode

renderSmart :: Float -> Int -> Doc AnsiStyle -> SimpleDocStream AnsiStyle
renderSmart ribbonFraction widthPerLine
Expand Down
25 changes: 20 additions & 5 deletions test/Language/Cimple/PrettySpec.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,15 @@
{-# LANGUAGE OverloadedStrings #-}
module Language.Cimple.PrettySpec where

import Test.Hspec (Spec, describe, it, shouldBe)

import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as TL
import Language.Cimple (Lexeme, Node)
import Language.Cimple.IO (parseText)
import Language.Cimple.Pretty (plain, ppTranslationUnit)
import Language.Cimple.Pretty (plain, ppTranslationUnit,
showNode)
import Prettyprinter (SimpleDocStream, layoutCompact)
import Prettyprinter.Render.Terminal (AnsiStyle, renderLazy)

Expand All @@ -18,17 +22,19 @@ pretty =
show
. plain
. ppTranslationUnit
. getRight
. parseText
. Text.pack
. mustParse

compact :: String -> String
compact =
flip displayS ""
. layoutCompact
. plain
. ppTranslationUnit
. getRight
. mustParse

mustParse :: String -> [Node (Lexeme Text)]
mustParse =
getRight
. parseText
. Text.pack

Expand All @@ -40,6 +46,15 @@ displayS sdoc =

spec :: Spec
spec = do
describe "showNode" $ do
it "prints code with syntax highlighting" $ do
let pp = showNode $ head $ mustParse "int a(void) { return 3; }"
pp <> "\n" `shouldBe` Text.unlines
[ "\ESC[0;32mint\ESC[0m a(\ESC[0;32mvoid\ESC[0m) {"
, " \ESC[0;31mreturn\ESC[0m \ESC[0;31m3\ESC[0m;"
, "}"
]

describe "renderPretty" $ do
it "pretty-prints a simple C function" $ do
let pp = pretty "int a(void) { return 3; }"
Expand Down

0 comments on commit ed563ef

Please sign in to comment.