aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
Diffstat (limited to 'test')
-rw-r--r--test/Haddock/Parser/UtilSpec.hs23
-rw-r--r--test/Haddock/ParserSpec.hs48
2 files changed, 70 insertions, 1 deletions
diff --git a/test/Haddock/Parser/UtilSpec.hs b/test/Haddock/Parser/UtilSpec.hs
new file mode 100644
index 00000000..acb88220
--- /dev/null
+++ b/test/Haddock/Parser/UtilSpec.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Haddock.Parser.UtilSpec (main, spec) where
+
+import Test.Hspec
+import Data.Either
+
+import Data.Attoparsec.ByteString.Char8
+import Haddock.Parser.Util
+
+main :: IO ()
+main = hspec spec
+
+spec :: Spec
+spec = do
+ describe "takeUntil" $ do
+ it "takes everything until a specified byte sequence" $ do
+ parseOnly (takeUntil "end") "someend" `shouldBe` Right "some"
+
+ it "requires the end sequence" $ do
+ parseOnly (takeUntil "end") "someen" `shouldSatisfy` isLeft
+
+ it "takes escaped bytes unconditionally" $ do
+ parseOnly (takeUntil "end") "some\\endend" `shouldBe` Right "some\\end"
diff --git a/test/Haddock/ParserSpec.hs b/test/Haddock/ParserSpec.hs
index 42f19c96..8c8e25ca 100644
--- a/test/Haddock/ParserSpec.hs
+++ b/test/Haddock/ParserSpec.hs
@@ -174,7 +174,53 @@ spec = before initStaticOpts $ do
"/foo\\/bar/" `shouldParseTo` DocEmphasis "foo/bar"
it "recognizes other markup constructs within emphasised text" $ do
- "/foo @bar@ baz/" `shouldParseTo` DocEmphasis ("foo " <> DocMonospaced "bar" <> " baz")
+ "/foo @bar@ baz/" `shouldParseTo`
+ DocEmphasis ("foo " <> DocMonospaced "bar" <> " baz")
+
+ it "allows other markup inside of emphasis" $ do
+ "/__inner bold__/" `shouldParseTo` DocEmphasis (DocBold "inner bold")
+
+ it "doesn't mangle inner markup unicode" $ do
+ "/__灼眼のシャナ &#65;__/" `shouldParseTo` DocEmphasis (DocBold "灼眼のシャナ A")
+
+ it "properly converts HTML escape sequences" $ do
+ "/&#65;&#65;&#65;&#65;/" `shouldParseTo` DocEmphasis "AAAA"
+
+ it "allows to escape the emphasis delimiter inside of emphasis" $ do
+ "/empha\\/sis/" `shouldParseTo` DocEmphasis "empha/sis"
+
+ context "when parsing bold strings" $ do
+ it "allows for a bold string on its own" $ do
+ "__bold string__" `shouldParseTo`
+ DocBold "bold string"
+
+ it "bolds inline correctly" $ do
+ "hello __everyone__ there" `shouldParseTo`
+ "hello "
+ <> DocBold "everyone" <> " there"
+
+ it "bolds unicode" $ do
+ "__灼眼のシャナ__" `shouldParseTo`
+ DocBold "灼眼のシャナ"
+
+ it "does not do __multi-line\\n bold__" $ do
+ " __multi-line\n bold__" `shouldParseTo` "__multi-line\n bold__"
+
+ it "allows other markup inside of bold" $ do
+ "__/inner emphasis/__" `shouldParseTo`
+ (DocBold $ DocEmphasis "inner emphasis")
+
+ it "doesn't mangle inner markup unicode" $ do
+ "__/灼眼のシャナ &#65;/__" `shouldParseTo`
+ (DocBold $ DocEmphasis "灼眼のシャナ A")
+
+ it "properly converts HTML escape sequences" $ do
+ "__&#65;&#65;&#65;&#65;__" `shouldParseTo`
+ DocBold "AAAA"
+
+ it "allows to escape the bold delimiter inside of bold" $ do
+ "__bo\\__ld__" `shouldParseTo`
+ DocBold "bo__ld"
context "when parsing monospaced text" $ do
it "parses simple monospaced text" $ do