{-# LANGUAGE OverloadedStrings #-} -- | All tests are translated from https://github.com/chalk/ansi-regex/blob/166a0d5eddedacf0db7ccd7ee137b862ab1dae70/test.js module Data.String.StripSpec (main, spec) where import Data.Char (isPrint, isSpace) import Data.Foldable (for_) import qualified Data.Text as T import Test.Hspec import Test.Hspec.QuickCheck import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary, shrink) import Test.QuickCheck.Gen (listOf, suchThat) import Data.String.StripSpec.Table import Data.String.AnsiEscapeCodes.Strip.Text -- `main` is here so that this module can be run from GHCi on its own. It is -- not needed for automatic spec discovery. main :: IO () main = hspec spec spec :: Spec spec = describe "stripAnsiEscapeCodes" $ do it "match ansi code in a string" $ do stripAnsiEscapeCodes "foo\x001B[4mcake\x001B[0m" `shouldBe` "foocake" stripAnsiEscapeCodes "\x001B[4mcake\x001B[0m" `shouldBe` "cake" stripAnsiEscapeCodes "foo\x001B[4mcake\x001B[0m" `shouldBe` "foocake" stripAnsiEscapeCodes "\x001B[0m\x001B[4m\x001B[42m\x001B[31mfoo\x001B[39m\x001B[49m\x001B[24mfoo\x001B[0m" `shouldBe` "foofoo" stripAnsiEscapeCodes "foo\x001B[mfoo" `shouldBe` "foofoo" it "match ansi code from ls command" $ stripAnsiEscapeCodes "\x001B[00;38;5;244m\x001B[m\x001B[00;38;5;33mfoo\x001B[0m" `shouldBe` "foo" it "match reset;setfg;setbg;italics;strike;underline sequence in a string" $ do stripAnsiEscapeCodes "\x001B[0;33;49;3;9;4mbar\x001B[0m" `shouldBe` "bar" stripAnsiEscapeCodes "foo\x001B[0;33;49;3;9;4mbar" `shouldBe` "foobar" it "match clear tabs sequence in a string" $ stripAnsiEscapeCodes "foo\x001B[0gbar" `shouldBe` "foobar" it "match clear line from cursor right in a string" $ stripAnsiEscapeCodes "foo\x001B[Kbar" `shouldBe` "foobar" it "match clear screen in a string" $ stripAnsiEscapeCodes "foo\x001B[2Jbar" `shouldBe` "foobar" it "match terminal link" $ do stripAnsiEscapeCodes ("\x001B]8;k=v;https://example-a.com/?a_b=1&c=2#tit%20le\x0007" <> "click\x001B]8;;\x0007") `shouldBe` "click" stripAnsiEscapeCodes "\x001B]8;;mailto:no-reply@mail.com\x0007mail\x001B]8;;\x0007" `shouldBe` "mail" it "match \"change icon name and window title\" in string" $ stripAnsiEscapeCodes "\x001B]0;sg@tota:~/git/\x0007\x001B[01;32m[sg@tota\x001B[01;37m misc-tests\x001B[01;32m]$" `shouldBe` "[sg@tota misc-tests]$" for_ ansiCodeTable $ \(category, entries) -> describe category $ for_ entries $ \entry -> do let code = entryCode entry ecode = "\x001B" <> code comment = entryComment entry prop (" - " ++ T.unpack code ++ " -- " ++ comment) $ \(PrintableOrSpace phed, PrintableOrSpace pbody, PrintableOrSpace pfoot, onlyHead) -> do let input = if onlyHead then hed <> ecode <> body <> foot else hed <> ecode <> body <> ecode <> foot expected = hed <> body <> foot hed = T.pack phed body = T.pack pbody foot = T.pack pfoot stripAnsiEscapeCodes input `shouldBe` expected newtype PrintableOrSpace = PrintableOrSpace String deriving (Eq, Show) instance Arbitrary PrintableOrSpace where arbitrary = PrintableOrSpace <$> listOf ac where ac = arbitrary `suchThat` (\c -> isPrint c || isSpace c) shrink (PrintableOrSpace s) = PrintableOrSpace <$> shrink s