{-# LANGUAGE TupleSections #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} import Test.Tasty import Test.Tasty.QuickCheck import Test.Tasty.HUnit import qualified Data.Text.Lazy as TL import Data.Text.Lazy.Encoding (decodeUtf8With, encodeUtf8) import Data.Text.Encoding.Error (lenientDecode) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy.Char8 as BL import Data.ByteString.Builder ( toLazyByteString ) import Djot ( ParseOptions(..), RenderOptions(..), SourcePosOption(..), parseDoc, renderHtml, renderDjot ) import Djot.Parse ( parse, satisfy, strToUtf8, utf8ToStr, Chunk(..) ) import Djot.AST import System.FilePath ((>), takeExtension, takeFileName) import System.Directory (getDirectoryContents) import Text.DocLayout (render) main :: IO () main = do specTests <- filter ((== ".test") . takeExtension) <$> getDirectoryContents "test" tests <- mapM (\fp -> (fp,) <$> getSpecTests ("test" > fp)) specTests let parser = parseDoc ParseOptions{ sourcePositions = NoSourcePos } . BL.toStrict defaultMain $ testGroup "Tests" $ [ testGroup "djot -> html" (map (\(fp, ts) -> testGroup fp (map (toSpecTest parser) ts)) tests) , testGroup "native -> djot -> native" [testGroup fp (map (toRoundTripTest parser) ts) | (fp, ts) <- tests , takeFileName fp /= "raw.test"] , testGroup "Djot.Parse" parserTests , testGroup "sourcepos" sourcePosTests , testGroup "Fuzz" [testProperty "parses all inputs" (\s -> case parseDoc ParseOptions{ sourcePositions = NoSourcePos } (strToUtf8 s) of Left _ -> False Right _ -> True) ] ] parserTests :: [TestTree] parserTests = [ testCase "satisfy multibyte" (parse (satisfy (=='ǎ') *> satisfy (=='老')) () (toChunks $ strToUtf8 "ǎ老bc") @?= Just '老') , testProperty "UTF8 conversion round-trips" (\s -> utf8ToStr (strToUtf8 s) == s) ] sourcePosTests :: [TestTree] sourcePosTests = let convert = either mempty (fromUtf8 . toLazyByteString . renderHtml RenderOptions{ preserveSoftBreaks = True }) . parseDoc ParseOptions{ sourcePositions = AllSourcePos } in [ testCase "period at end" $ convert "the `goo` option.\n" @?= "
the goo
option.
*
\n" , testCase "no newline at end" $ convert "foo" @?= "foo
\n" , testCase "list" $ convert "1. > hello\nthere\n\n2. ok" @?= "\n\nhello\nthere
\n
ok
\nhi\n
\n"
, testCase "nested " $
convert "*_hi_*" @?=
"hi
\n" , testCase "hr " $ convert "----\n" @?= "