Muse reader: enable round trip test

Closes #4107
This commit is contained in:
Alexander Krotov 2017-12-30 20:31:34 +03:00
parent bbfb6f0c3c
commit 551aec7b01

View file

@ -5,13 +5,13 @@ import Data.List (intersperse)
import Data.Text (Text)
import qualified Data.Text as T
import Test.Tasty
-- import Test.Tasty.QuickCheck
import Test.Tasty.QuickCheck
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
import Text.Pandoc.Shared (underlineSpan)
-- import Text.Pandoc.Walk (walk)
import Text.Pandoc.Walk (walk)
amuse :: Text -> Pandoc
amuse = purely $ readMuse def { readerExtensions = extensionsFromList [Ext_amuse]}
@ -27,19 +27,19 @@ infix 4 =:
spcSep :: [Inlines] -> Inlines
spcSep = mconcat . intersperse space
{-
-- Tables and code blocks don't round-trip yet
-- Tables and definition lists don't round-trip yet
removeTables :: Block -> Block
removeTables (Table{}) = Para [Str "table was here"]
removeTables x = x
makeRoundTrip :: Block -> Block
makeRoundTrip (Table{}) = Para [Str "table was here"]
makeRoundTrip (DefinitionList{}) = Para [Str "deflist was here"]
makeRoundTrip x = x
-- Demand that any AST produced by Muse reader and written by Muse writer can be read back exactly the same way.
-- Currently we remove code blocks and tables and compare third rewrite to the second.
-- First and second rewrites are not equal yet.
roundTrip :: Block -> Bool
roundTrip b = d'' == d'''
where d = walk removeTables $ Pandoc nullMeta [b]
where d = walk makeRoundTrip $ Pandoc nullMeta [b]
d' = rewrite d
d'' = rewrite d'
d''' = rewrite d''
@ -47,7 +47,6 @@ roundTrip b = d'' == d'''
(purely $ writeMuse def { writerExtensions = extensionsFromList [Ext_amuse]
, writerWrapText = WrapPreserve
})
-}
tests :: [TestTree]
tests =
@ -200,7 +199,7 @@ tests =
]
, testGroup "Blocks"
[ -- testProperty "Round trip" roundTrip,
[ testProperty "Round trip" roundTrip,
"Block elements end paragraphs" =:
T.unlines [ "First paragraph"
, "----"