Added ReaderOptions parameter to readNative.

This makes it similar to the other readers -- even
though ReaderOptions is essentially ignored, the uniformity
is nice.
This commit is contained in:
John MacFarlane 2016-12-10 16:52:35 +01:00
parent 6643e401ee
commit 2e7b0c7eda
6 changed files with 10 additions and 8 deletions

View file

@ -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

View file

@ -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"

View file

@ -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"

View file

@ -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

View file

@ -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)

View file

@ -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')