diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 013a9d9ac..e5fc665a7 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -238,7 +238,7 @@ data Reader m = StringReader (ReaderOptions -> String -> m Pandoc) -- | Association list of formats and readers. readers :: PandocMonad m => [(String, Reader m)] -readers = [ ("native" , StringReader $ \_ s -> readNative s) +readers = [ ("native" , StringReader readNative) ,("json" , StringReader $ \o s -> case readJSON o s of Right doc -> return doc diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs index 3e934e43f..1953c0c83 100644 --- a/src/Text/Pandoc/Readers/Native.hs +++ b/src/Text/Pandoc/Readers/Native.hs @@ -32,6 +32,7 @@ module Text.Pandoc.Readers.Native ( readNative ) where import Text.Pandoc.Definition import Text.Pandoc.Shared (safeRead) +import Text.Pandoc.Options (ReaderOptions) import Control.Monad.Except (throwError) import Text.Pandoc.Error @@ -48,9 +49,10 @@ import Text.Pandoc.Class -- > Pandoc nullMeta [Plain [Str "hi"]] -- readNative :: PandocMonad m - => String -- ^ String to parse (assuming @'\n'@ line endings) + => ReaderOptions + -> String -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc -readNative s = +readNative _ s = case maybe (Pandoc nullMeta <$> readBlocks s) Right (safeRead s) of Right doc -> return doc Left _ -> throwError $ PandocParseError "couldn't read native" diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index 04612d49d..cc35c8aa0 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -196,7 +196,7 @@ lhsReaderTest format = testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) norm where normalizer = purely $ \nat -> do - d <- readNative nat + d <- readNative def nat writeNative def $ normalize d norm = if format == "markdown+lhs" then "lhs-test-markdown.native" diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index 22fdf575a..ef060b8ae 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -44,7 +44,7 @@ compareOutput opts docxFile nativeFile = do df <- B.readFile docxFile nf <- Prelude.readFile nativeFile p <- runIOorExplode $ readDocx opts df - df' <- runIOorExplode $ readNative nf + df' <- runIOorExplode $ readNative def nf return $ (noNorm p, noNorm df') testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index c3a44a729..b0e916336 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -63,7 +63,7 @@ compareOdtToNative :: TestCreator compareOdtToNative opts odtPath nativePath = do nativeFile <- Prelude.readFile nativePath odtFile <- B.readFile odtPath - native <- getNoNormVia id "native" <$> runIO (readNative nativeFile) + native <- getNoNormVia id "native" <$> runIO (readNative def nativeFile) odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) return (odt,native) diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs index 44095925f..fd320d224 100644 --- a/tests/Tests/Writers/Docx.hs +++ b/tests/Tests/Writers/Docx.hs @@ -21,9 +21,9 @@ compareOutput opts nativeFileIn nativeFileOut = do nf' <- Prelude.readFile nativeFileOut let wopts = fst opts df <- runIOorExplode $ do - d <- readNative nf + d <- readNative def nf writeDocx wopts{writerUserDataDir = Just (".." </> "data")} d - df' <- runIOorExplode (readNative nf') + df' <- runIOorExplode (readNative def nf') p <- runIOorExplode $ readDocx (snd opts) df return (p, df')