aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--benchmark/benchmark-pandoc.hs60
-rw-r--r--doc/lua-filters.md8
-rw-r--r--src/Text/Pandoc/Readers/RST.hs7
-rw-r--r--src/Text/Pandoc/Writers/Ms.hs10
4 files changed, 48 insertions, 37 deletions
diff --git a/benchmark/benchmark-pandoc.hs b/benchmark/benchmark-pandoc.hs
index 967728f5d..3e7b663b4 100644
--- a/benchmark/benchmark-pandoc.hs
+++ b/benchmark/benchmark-pandoc.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE TupleSections #-}
{-
Copyright (C) 2012-2019 John MacFarlane <jgm@berkeley.edu>
@@ -21,39 +20,49 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
import Prelude
import Text.Pandoc
import Text.Pandoc.MIME
-import Text.Pandoc.Error (PandocError(..))
-import Control.Monad.Except (throwError)
+import Control.Monad.Except (throwError, liftIO)
import qualified Text.Pandoc.UTF8 as UTF8
import qualified Data.ByteString as B
import qualified Data.Text as T
import Criterion.Main
import Criterion.Types (Config(..))
import Data.List (intersect)
-import Data.Maybe (mapMaybe)
+import Data.Maybe (mapMaybe, catMaybes)
import System.Environment (getArgs)
import qualified Data.ByteString.Lazy as BL
+data Input = InputText {unInputText :: T.Text}
+ | InputBS {unInputBS :: BL.ByteString}
+
readerBench :: Pandoc
-> T.Text
- -> Maybe Benchmark
-readerBench doc name =
- case res of
- Right (readerFun, inp) ->
- Just $ bench (T.unpack $ name <> " reader")
- $ nf (\i -> either (error . show) id $ runPure (readerFun i))
- inp
- Left _ -> Nothing
- where res = runPure $ do
- (rdr, rexts) <- getReader name
+ -> IO (Maybe Benchmark)
+readerBench doc name = do
+ let (rdr, rexts) = either (error . show) id . runPure $ getReader name
+ res <- runIO $ do
(wtr, wexts) <- getWriter name
case (rdr, wtr) of
(TextReader r, TextWriter w) -> do
- setResourcePath ["../test"]
+ setResourcePath ["./test"]
inp <- w def{ writerWrapText = WrapAuto
, writerExtensions = wexts } doc
- return $ (r def{ readerExtensions = rexts }, inp)
- _ -> throwError $ PandocSomeError $ "not a text format: "
+ return (r def{ readerExtensions = rexts } . unInputText, InputText inp)
+ (ByteStringReader r, ByteStringWriter w) -> do
+ setResourcePath ["./test"]
+ tmpl <- Just <$> compileDefaultTemplate name
+ inp <- w def{ writerWrapText = WrapAuto
+ , writerExtensions = wexts
+ , writerTemplate = tmpl } doc
+ liftIO $ BL.writeFile "/tmp/test.odt" inp
+ return (r def{ readerExtensions = rexts } . unInputBS, InputBS inp)
+ _ -> throwError $ PandocSomeError $ "text/bytestring format mismatch: "
<> name
+ return $ case res of
+ Right (readerFun, inp) ->
+ Just $ bench (T.unpack $ name <> " reader")
+ $ nf (\i -> either (error . show) id $ runPure (readerFun i))
+ inp
+ Left _ -> Nothing
getImages :: IO [(FilePath, MimeType, BL.ByteString)]
getImages = do
@@ -89,22 +98,23 @@ main :: IO ()
main = do
args <- filter (\x -> T.take 1 x /= "-") . fmap T.pack <$> getArgs
print args
- let matchReader (n, TextReader _) =
+ let matchReader (n, _) =
null args || ("reader" `elem` args && n `elem` args)
- matchReader _ = False
- let matchWriter (n, TextWriter _) =
+ matchWriter (n, TextWriter _) =
null args || ("writer" `elem` args && n `elem` args)
matchWriter _ = False
- let matchedReaders = map fst $ (filter matchReader readers
+ allWriters = map fst (writers :: [(T.Text, Writer PandocPure)])
+ matchedReaders = map fst (filter matchReader readers
:: [(T.Text, Reader PandocPure)])
- let matchedWriters = map fst $ (filter matchWriter writers
+ matchedWriters = map fst (filter matchWriter writers
:: [(T.Text, Writer PandocPure)])
inp <- UTF8.toText <$> B.readFile "test/testsuite.txt"
let opts = def
let doc = either (error . show) id $ runPure $ readMarkdown opts inp
- let readerBs = mapMaybe (readerBench doc)
- $ filter (/="haddock")
- (matchedReaders `intersect` matchedWriters)
+ readerBs <- fmap catMaybes
+ $ mapM (readerBench doc)
+ $ filter (/="haddock")
+ (matchedReaders `intersect` allWriters)
-- we need the corresponding writer to generate
-- input for the reader
let writerBs = mapMaybe (writerBench doc) matchedWriters
diff --git a/doc/lua-filters.md b/doc/lua-filters.md
index c5f7d2713..cc49da09b 100644
--- a/doc/lua-filters.md
+++ b/doc/lua-filters.md
@@ -138,7 +138,7 @@ elements.
## Filters on element sequences
-For some filtering tasks, the it is necessary to know the order
+For some filtering tasks, it is necessary to know the order
in which elements occur in the document. It is not enough then to
inspect a single element at a time.
@@ -1127,7 +1127,7 @@ A [table cell]{#type-table-cell} is a list of blocks.
*[Alignment]{#type-alignment}* is a string value indicating the
horizontal alignment of a table column. `AlignLeft`,
-`AlignRight`, and `AlignCenter` leads cell content tob be
+`AlignRight`, and `AlignCenter` leads cell content to be
left-aligned, right-aligned, and centered, respectively. The
default alignment is `AlignDefault` (often equivalent to
centered).
@@ -3035,7 +3035,7 @@ methods and convenience functions.
[`pandoc.List:insert ([pos], value)`]{#pandoc.list:insert}
: Inserts element `value` at position `pos` in list, shifting
- elements to the next-greater indix if necessary.
+ elements to the next-greater index if necessary.
This function is identical to
[`table.insert`](https://www.lua.org/manual/5.3/manual.html#6.6).
@@ -3082,7 +3082,7 @@ methods and convenience functions.
Parameters:
`pos`:
- : position of the list value that will be remove; defaults
+ : position of the list value that will be removed; defaults
to the index of the last element
Returns: the removed element
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index e558836a1..7c25be486 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -223,7 +223,8 @@ rawFieldListItem minIndent = try $ do
first <- anyLine
rest <- option "" $ try $ do lookAhead (count indent (char ' ') >> spaceChar)
indentedBlock
- let raw = (if T.null first then "" else first <> "\n") <> rest <> "\n"
+ let raw = (if T.null first then "" else first <> "\n") <> rest <>
+ (if T.null first && T.null rest then "" else "\n")
return (name, raw)
fieldListItem :: PandocMonad m => Int -> RSTParser m (Inlines, [Blocks])
@@ -484,7 +485,7 @@ includeDirective top fields body = do
Just patt -> drop 1 .
dropWhile (not . (patt `T.isInfixOf`))
Nothing -> id) $ contentLines'
- let contents' = T.unlines contentLines'' <> "\n"
+ let contents' = T.unlines contentLines''
case lookup "code" fields of
Just lang -> do
let classes = maybe [] T.words (lookup "class" fields)
@@ -494,7 +495,7 @@ includeDirective top fields body = do
Just _ -> return $ B.rawBlock "rst" contents'
Nothing -> do
setPosition $ newPos (T.unpack f) 1 1
- setInput contents'
+ setInput $ contents' <> "\n"
bs <- optional blanklines >>
(mconcat <$> many block)
setInput oldInput
diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs
index 81de40045..d38b874d4 100644
--- a/src/Text/Pandoc/Writers/Ms.hs
+++ b/src/Text/Pandoc/Writers/Ms.hs
@@ -517,11 +517,11 @@ toMacro sty toktype =
msFormatter :: WriterOptions -> FormatOptions -> [SourceLine] -> Doc Text
msFormatter opts _fmtopts =
- vcat . map fmtLine
- where fmtLine = hcat . map fmtToken
- fmtToken (toktype, tok) = literal "\\*" <>
- brackets (literal (tshow toktype) <> literal " \""
- <> literal (escapeStr opts tok) <> literal "\"")
+ literal . T.intercalate "\n" . map fmtLine
+ where
+ fmtLine = mconcat . map fmtToken
+ fmtToken (toktype, tok) =
+ "\\*[" <> (tshow toktype) <> " \"" <> (escapeStr opts tok) <> "\"]"
highlightCode :: PandocMonad m => WriterOptions -> Attr -> Text -> MS m (Doc Text)
highlightCode opts attr str =