aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--.github/workflows/ci.yml14
-rw-r--r--CONTRIBUTING.md12
-rw-r--r--MANUAL.txt3
-rw-r--r--benchmark/benchmark-pandoc.hs60
-rw-r--r--data/templates/default.latex3
-rw-r--r--doc/lua-filters.md8
-rw-r--r--pandoc.cabal1
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs3
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs93
-rw-r--r--src/Text/Pandoc/Readers/Docx/Combine.hs101
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs3
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse/Styles.hs18
-rw-r--r--src/Text/Pandoc/Readers/Ipynb.hs3
-rw-r--r--src/Text/Pandoc/Readers/RST.hs7
-rw-r--r--src/Text/Pandoc/Writers/Ipynb.hs7
-rw-r--r--src/Text/Pandoc/Writers/Jira.hs22
-rw-r--r--src/Text/Pandoc/Writers/Ms.hs14
-rw-r--r--test/Tests/Writers/Ms.hs37
-rw-r--r--test/docx/golden/inline_formatting.docxbin9989 -> 9987 bytes
-rw-r--r--test/docx/inline_formatting.native2
-rw-r--r--test/ipynb/simple.out.native6
-rw-r--r--test/lhs-test.latex3
-rw-r--r--test/lhs-test.latex+lhs3
-rw-r--r--test/test-pandoc.hs2
-rw-r--r--test/writer.jira4
-rw-r--r--test/writer.latex3
-rw-r--r--test/writers-lang-and-dir.latex3
27 files changed, 241 insertions, 194 deletions
diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml
index e1c5e9165..1617672ae 100644
--- a/.github/workflows/ci.yml
+++ b/.github/workflows/ci.yml
@@ -61,16 +61,10 @@ jobs:
# need to install older cabal/ghc versions from ppa repository
- name: Install recent cabal/ghc
- run: |
- if [[ ! -d /opt/ghc/${{ matrix.versions.ghc }} ]]
- then
- sudo add-apt-repository ppa:hvr/ghc
- sudo apt-get update
- sudo apt-get install ghc-${{ matrix.versions.ghc }} cabal-install-${{ matrix.versions.cabal }}
- fi
- # Use a GitHub workflow command to add folders to PATH.
- echo "::add-path::/opt/ghc/${{ matrix.versions.ghc }}/bin"
- echo "::add-path::/opt/cabal/${{ matrix.versions.cabal }}/bin"
+ uses: actions/setup-haskell@v1.1
+ with:
+ ghc-version: ${{ matrix.versions.ghc }}
+ cabal-version: ${{ matrix.versions.cabal }}
# declare/restore cached things
# caching doesn't work for scheduled runs yet
diff --git a/CONTRIBUTING.md b/CONTRIBUTING.md
index 23c5c7ba4..94d8f48b0 100644
--- a/CONTRIBUTING.md
+++ b/CONTRIBUTING.md
@@ -17,8 +17,14 @@ Before you submit a bug report, search the [open issues] *and* [closed issues]
to make sure the issue hasn't come up before. Also, check the [User's Guide] and
[FAQs] for anything relevant.
-Make sure you can reproduce the bug with the [latest released version] of pandoc
-(or, even better, the [development version]).
+Make sure you can reproduce the bug with the [latest released
+version] of pandoc---or, even better, the development version,
+since the bug may have been fixed since the last release.
+[Nightly builds] are available, so you don't need to compile
+from source to test againt the development version.
+(To fetch a nightly, visit the link, click the topmost "Nightly"
+in the table, then choose your platform under "Artifacts." Note
+that you must be logged in with a GitHub account.)
Your report should give detailed, *reproducible* instructions, including
@@ -346,7 +352,7 @@ you may want to consider submitting a pull request to the
[open issues]: https://github.com/jgm/pandoc/issues
[closed issues]: https://github.com/jgm/pandoc/issues?q=is%3Aissue+is%3Aclosed
[latest released version]: https://github.com/jgm/pandoc/releases/latest
-[development version]: https://github.com/pandoc-extras/pandoc-nightly/releases/latest
+[Nightly builds]: https://github.com/jgm/pandoc/actions?query=workflow%3ANightly
[pandoc-discuss]: http://groups.google.com/group/pandoc-discuss
[issue tracker]: https://github.com/jgm/pandoc/issues
[User's Guide]: http://pandoc.org/MANUAL.html
diff --git a/MANUAL.txt b/MANUAL.txt
index b9ef68cd2..7d7906f20 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -902,7 +902,7 @@ header when requesting a document from a URL:
downloaded). If you're behind a proxy, you also need to set
the environment variable `http_proxy` to `http://...`.
-`--no-check-certificate
+`--no-check-certificate`
: Disable the certificate verification to allow access to
unsecure HTTP resources (for example when the certificate
@@ -5633,7 +5633,6 @@ seriespage frontmatter
foreword frontmatter
preface frontmatter
seriespage frontmatter
-titlepage frontmatter
appendix backmatter
colophon backmatter
bibliography backmatter
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/data/templates/default.latex b/data/templates/default.latex
index 92ab9fe13..d6cca9c98 100644
--- a/data/templates/default.latex
+++ b/data/templates/default.latex
@@ -339,6 +339,9 @@ $if(babel-newcommands)$
$endif$
\fi
$endif$
+\ifluatex
+ \usepackage{selnolig} % disable illegal ligatures
+\fi
$if(dir)$
\ifxetex
% Load bidi as late as possible as it modifies e.g. graphicx
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/pandoc.cabal b/pandoc.cabal
index a36f3942c..83c7f1805 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -816,6 +816,7 @@ test-suite test-pandoc
Tests.Writers.FB2
Tests.Writers.Powerpoint
Tests.Writers.OOXML
+ Tests.Writers.Ms
if os(windows)
cpp-options: -D_WINDOWS
default-language: Haskell2010
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index ae319b372..b04952c27 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -360,7 +360,7 @@ List of all DocBook tags, with [x] indicating implemented,
[x] refsectioninfo - Meta-information for a refsection
[ ] refsynopsisdiv - A syntactic synopsis of the subject of the reference page
[ ] refsynopsisdivinfo - Meta-information for a RefSynopsisDiv
-[x] releaseinfo - Information about a particular release of a document
+[ ] releaseinfo - Information about a particular release of a document
[ ] remark - A remark (or comment) intended for presentation in a draft
manuscript
[x] replaceable - Content that may or must be replaced by the user
@@ -608,6 +608,7 @@ addMetadataFromElement e = do
addMetaField "author" e
addMetaField "date" e
addMetaField "release" e
+ addMetaField "releaseinfo" e
return mempty
where addMetaField fieldname elt =
case filterChildren (named fieldname) elt of
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index ddec0bdf8..c9aa2f7c5 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -261,46 +261,43 @@ resolveDependentRunStyle rPr
| otherwise = return rPr
runStyleToTransform :: PandocMonad m => RunStyle -> DocxContext m (Inlines -> Inlines)
-runStyleToTransform rPr
- | Just sn <- getStyleName <$> rParentStyle rPr
- , sn `elem` spansToKeep = do
- transform <- runStyleToTransform rPr{rParentStyle = Nothing}
- return $ spanWith ("", [normalizeToClassName sn], []) . transform
- | Just s <- rParentStyle rPr = do
- ei <- extraInfo spanWith s
- transform <- runStyleToTransform rPr{rParentStyle = Nothing}
- return $ ei . transform
- | Just True <- isItalic rPr = do
- transform <- runStyleToTransform rPr{isItalic = Nothing}
- return $ emph . transform
- | Just True <- isBold rPr = do
- transform <- runStyleToTransform rPr{isBold = Nothing}
- return $ strong . transform
- | Just True <- isSmallCaps rPr = do
- transform <- runStyleToTransform rPr{isSmallCaps = Nothing}
- return $ smallcaps . transform
- | Just True <- isStrike rPr = do
- transform <- runStyleToTransform rPr{isStrike = Nothing}
- return $ strikeout . transform
- | Just True <- isRTL rPr = do
- transform <- runStyleToTransform rPr{isRTL = Nothing}
- return $ spanWith ("",[],[("dir","rtl")]) . transform
- | Just False <- isRTL rPr = do
- transform <- runStyleToTransform rPr{isRTL = Nothing}
- inBidi <- asks docxInBidi
- return $ if inBidi
- then spanWith ("",[],[("dir","ltr")]) . transform
- else transform
- | Just SupScrpt <- rVertAlign rPr = do
- transform <- runStyleToTransform rPr{rVertAlign = Nothing}
- return $ superscript . transform
- | Just SubScrpt <- rVertAlign rPr = do
- transform <- runStyleToTransform rPr{rVertAlign = Nothing}
- return $ subscript . transform
- | Just "single" <- rUnderline rPr = do
- transform <- runStyleToTransform rPr{rUnderline = Nothing}
- return $ Pandoc.underline . transform
- | otherwise = return id
+runStyleToTransform rPr' = do
+ opts <- asks docxOptions
+ inBidi <- asks docxInBidi
+ let styles = isEnabled Ext_styles opts
+ ctl = (Just True == isRTL rPr') || (Just True == isForceCTL rPr')
+ italic rPr | ctl = isItalicCTL rPr
+ | otherwise = isItalic rPr
+ bold rPr | ctl = isBoldCTL rPr
+ | otherwise = isBold rPr
+ go rPr
+ | Just sn <- getStyleName <$> rParentStyle rPr
+ , sn `elem` spansToKeep =
+ spanWith ("", [normalizeToClassName sn], [])
+ . go rPr{rParentStyle = Nothing}
+ | styles, Just s <- rParentStyle rPr =
+ spanWith (extraAttr s) . go rPr{rParentStyle = Nothing}
+ | Just True <- italic rPr =
+ emph . go rPr{isItalic = Nothing, isItalicCTL = Nothing}
+ | Just True <- bold rPr =
+ strong . go rPr{isBold = Nothing, isBoldCTL = Nothing}
+ | Just True <- isSmallCaps rPr =
+ smallcaps . go rPr{isSmallCaps = Nothing}
+ | Just True <- isStrike rPr =
+ strikeout . go rPr{isStrike = Nothing}
+ | Just True <- isRTL rPr =
+ spanWith ("",[],[("dir","rtl")]) . go rPr{isRTL = Nothing}
+ | inBidi, Just False <- isRTL rPr =
+ spanWith ("",[],[("dir","ltr")]) . go rPr{isRTL = Nothing}
+ | Just SupScrpt <- rVertAlign rPr =
+ superscript . go rPr{rVertAlign = Nothing}
+ | Just SubScrpt <- rVertAlign rPr = do
+ subscript . go rPr{rVertAlign = Nothing}
+ | Just "single" <- rUnderline rPr = do
+ Pandoc.underline . go rPr{rUnderline = Nothing}
+ | otherwise = id
+ return $ go rPr'
+
runToInlines :: PandocMonad m => Run -> DocxContext m Inlines
runToInlines (Run rs runElems)
@@ -512,13 +509,8 @@ trimSps (Many ils) = Many $ Seq.dropWhileL isSp $Seq.dropWhileR isSp ils
isSp LineBreak = True
isSp _ = False
-extraInfo :: (Eq (StyleName a), PandocMonad m, HasStyleName a)
- => (Attr -> i -> i) -> a -> DocxContext m (i -> i)
-extraInfo f s = do
- opts <- asks docxOptions
- return $ if isEnabled Ext_styles opts
- then f ("", [], [("custom-style", fromStyleName $ getStyleName s)])
- else id
+extraAttr :: (Eq (StyleName a), HasStyleName a) => a -> Attr
+extraAttr s = ("", [], [("custom-style", fromStyleName $ getStyleName s)])
parStyleToTransform :: PandocMonad m => ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform pPr = case pStyle pPr of
@@ -534,8 +526,11 @@ parStyleToTransform pPr = case pStyle pPr of
| otherwise -> do
let pPr' = pPr { pStyle = cs }
transform <- parStyleToTransform pPr'
- ei <- extraInfo divWith c
- return $ ei . (if isBlockQuote c then blockQuote else id) . transform
+ styles <- asks (isEnabled Ext_styles . docxOptions)
+ return $
+ (if styles then divWith (extraAttr c) else id)
+ . (if isBlockQuote c then blockQuote else id)
+ . transform
[]
| Just left <- indentation pPr >>= leftParIndent -> do
let pPr' = pPr { indentation = Nothing }
diff --git a/src/Text/Pandoc/Readers/Docx/Combine.hs b/src/Text/Pandoc/Readers/Docx/Combine.hs
index 54736cd0e..427a73dbe 100644
--- a/src/Text/Pandoc/Readers/Docx/Combine.hs
+++ b/src/Text/Pandoc/Readers/Docx/Combine.hs
@@ -1,10 +1,9 @@
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Readers.Docx.Combine
Copyright : © 2014-2020 Jesse Rosenthal <jrosenthal@jhu.edu>,
- 2014-2020 John MacFarlane <jgm@berkeley.edu>
+ 2014-2020 John MacFarlane <jgm@berkeley.edu>,
+ 2020 Nikolay Yakimov <root@livid.pp.ru>
License : GNU GPL, version 2 or above
Maintainer : Jesse Rosenthal <jrosenthal@jhu.edu>
@@ -59,79 +58,61 @@ module Text.Pandoc.Readers.Docx.Combine ( smushInlines
where
import Data.List
-import Data.Sequence (ViewL (..), ViewR (..), viewl, viewr, (><), (|>))
-import qualified Data.Sequence as Seq (null)
+import Data.Bifunctor
+import Data.Sequence ( ViewL (..), ViewR (..), viewl, viewr, spanr, spanl
+ , (><), (|>) )
import Text.Pandoc.Builder
data Modifier a = Modifier (a -> a)
| AttrModifier (Attr -> a -> a) Attr
- | NullModifier
spaceOutInlinesL :: Inlines -> (Inlines, Inlines)
spaceOutInlinesL ms = (l, stackInlines fs (m' <> r))
- where (l, m, r) = spaceOutInlines ms
- (fs, m') = unstackInlines m
+ where (l, (fs, m'), r) = spaceOutInlines ms
spaceOutInlinesR :: Inlines -> (Inlines, Inlines)
spaceOutInlinesR ms = (stackInlines fs (l <> m'), r)
- where (l, m, r) = spaceOutInlines ms
- (fs, m') = unstackInlines m
+ where (l, (fs, m'), r) = spaceOutInlines ms
-spaceOutInlines :: Inlines -> (Inlines, Inlines, Inlines)
+spaceOutInlines :: Inlines -> (Inlines, ([Modifier Inlines], Inlines), Inlines)
spaceOutInlines ils =
let (fs, ils') = unstackInlines ils
- contents = unMany ils'
- left = case viewl contents of
- (Space :< _) -> space
- _ -> mempty
- right = case viewr contents of
- (_ :> Space) -> space
- _ -> mempty in
- (left, stackInlines fs $ trimInlines . Many $ contents, right)
+ (left, (right, contents')) = second (spanr isSpace) $ spanl isSpace $ unMany ils'
+ -- NOTE: spanr counterintuitively returns suffix as the FIRST tuple element
+ in (Many left, (fs, Many contents'), Many right)
+
+isSpace :: Inline -> Bool
+isSpace Space = True
+isSpace SoftBreak = True
+isSpace _ = False
stackInlines :: [Modifier Inlines] -> Inlines -> Inlines
stackInlines [] ms = ms
-stackInlines (NullModifier : fs) ms = stackInlines fs ms
stackInlines (Modifier f : fs) ms =
- if isEmpty ms
+ if null ms
then stackInlines fs ms
else f $ stackInlines fs ms
stackInlines (AttrModifier f attr : fs) ms = f attr $ stackInlines fs ms
unstackInlines :: Inlines -> ([Modifier Inlines], Inlines)
-unstackInlines ms = case ilModifier ms of
- NullModifier -> ([], ms)
- _ -> (f : fs, ms') where
- f = ilModifier ms
- (fs, ms') = unstackInlines $ ilInnards ms
-
-ilModifier :: Inlines -> Modifier Inlines
-ilModifier ils = case viewl (unMany ils) of
- (x :< xs) | Seq.null xs -> case x of
- (Emph _) -> Modifier emph
- (Strong _) -> Modifier strong
- (SmallCaps _) -> Modifier smallcaps
- (Strikeout _) -> Modifier strikeout
- (Superscript _) -> Modifier superscript
- (Subscript _) -> Modifier subscript
- (Link attr _ tgt) -> Modifier $ linkWith attr (fst tgt) (snd tgt)
- (Span attr _) -> AttrModifier spanWith attr
- _ -> NullModifier
- _ -> NullModifier
-
-ilInnards :: Inlines -> Inlines
-ilInnards ils = case viewl (unMany ils) of
- (x :< xs) | Seq.null xs -> case x of
- (Emph lst) -> fromList lst
- (Strong lst) -> fromList lst
- (SmallCaps lst) -> fromList lst
- (Strikeout lst) -> fromList lst
- (Superscript lst) -> fromList lst
- (Subscript lst) -> fromList lst
- (Link _ lst _) -> fromList lst
- (Span _ lst) -> fromList lst
- _ -> ils
- _ -> ils
+unstackInlines ms = case ilModifierAndInnards ms of
+ Nothing -> ([], ms)
+ Just (f, inner) -> first (f :) $ unstackInlines inner
+
+ilModifierAndInnards :: Inlines -> Maybe (Modifier Inlines, Inlines)
+ilModifierAndInnards ils = case viewl $ unMany ils of
+ x :< xs | null xs -> second fromList <$> case x of
+ Emph lst -> Just (Modifier emph, lst)
+ Strong lst -> Just (Modifier strong, lst)
+ SmallCaps lst -> Just (Modifier smallcaps, lst)
+ Strikeout lst -> Just (Modifier strikeout, lst)
+ Underline lst -> Just (Modifier underline, lst)
+ Superscript lst -> Just (Modifier superscript, lst)
+ Subscript lst -> Just (Modifier subscript, lst)
+ Link attr lst tgt -> Just (Modifier $ linkWith attr (fst tgt) (snd tgt), lst)
+ Span attr lst -> Just (AttrModifier spanWith attr, lst)
+ _ -> Nothing
+ _ -> Nothing
inlinesL :: Inlines -> (Inlines, Inlines)
inlinesL ils = case viewl $ unMany ils of
@@ -161,12 +142,12 @@ combineSingletonInlines x y =
y_rem_attr = filter isAttrModifier y_remaining
in
case null shared of
- True | isEmpty xs && isEmpty ys ->
- stackInlines (x_rem_attr ++ y_rem_attr) mempty
- | isEmpty xs ->
+ True | null xs && null ys ->
+ stackInlines (x_rem_attr <> y_rem_attr) mempty
+ | null xs ->
let (sp, y') = spaceOutInlinesL y in
stackInlines x_rem_attr mempty <> sp <> y'
- | isEmpty ys ->
+ | null ys ->
let (x', sp) = spaceOutInlinesR x in
x' <> sp <> stackInlines y_rem_attr mempty
| otherwise ->
@@ -193,12 +174,8 @@ combineBlocks bs cs = bs <> cs
instance (Monoid a, Eq a) => Eq (Modifier a) where
(Modifier f) == (Modifier g) = f mempty == g mempty
(AttrModifier f attr) == (AttrModifier g attr') = f attr mempty == g attr' mempty
- NullModifier == NullModifier = True
_ == _ = False
-isEmpty :: (Monoid a, Eq a) => a -> Bool
-isEmpty x = x == mempty
-
isAttrModifier :: Modifier a -> Bool
isAttrModifier (AttrModifier _ _) = True
isAttrModifier _ = False
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 199ca6d03..eab4f4e0d 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -259,10 +259,13 @@ newtype Cell = Cell [BodyPart]
leftBiasedMergeRunStyle :: RunStyle -> RunStyle -> RunStyle
leftBiasedMergeRunStyle a b = RunStyle
{ isBold = isBold a <|> isBold b
+ , isBoldCTL = isBoldCTL a <|> isBoldCTL b
, isItalic = isItalic a <|> isItalic b
+ , isItalicCTL = isItalicCTL a <|> isItalicCTL b
, isSmallCaps = isSmallCaps a <|> isSmallCaps b
, isStrike = isStrike a <|> isStrike b
, isRTL = isRTL a <|> isRTL b
+ , isForceCTL = isForceCTL a <|> isForceCTL b
, rVertAlign = rVertAlign a <|> rVertAlign b
, rUnderline = rUnderline a <|> rUnderline b
, rParentStyle = rParentStyle a
diff --git a/src/Text/Pandoc/Readers/Docx/Parse/Styles.hs b/src/Text/Pandoc/Readers/Docx/Parse/Styles.hs
index bfbc65cb0..236167187 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse/Styles.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse/Styles.hs
@@ -44,7 +44,6 @@ module Text.Pandoc.Readers.Docx.Parse.Styles (
) where
import Codec.Archive.Zip
import Control.Applicative ((<|>))
-import Control.Monad.Except
import Data.Function (on)
import Data.String (IsString(..))
import qualified Data.Map as M
@@ -101,10 +100,13 @@ data CharStyle = CharStyle { cStyleId :: CharStyleId
} deriving (Show)
data RunStyle = RunStyle { isBold :: Maybe Bool
+ , isBoldCTL :: Maybe Bool
, isItalic :: Maybe Bool
+ , isItalicCTL :: Maybe Bool
, isSmallCaps :: Maybe Bool
, isStrike :: Maybe Bool
, isRTL :: Maybe Bool
+ , isForceCTL :: Maybe Bool
, rVertAlign :: Maybe VertAlign
, rUnderline :: Maybe String
, rParentStyle :: Maybe CharStyle
@@ -121,10 +123,13 @@ data ParStyle = ParStyle { headingLev :: Maybe (ParaStyleName, Int)
defaultRunStyle :: RunStyle
defaultRunStyle = RunStyle { isBold = Nothing
+ , isBoldCTL = Nothing
, isItalic = Nothing
+ , isItalicCTL = Nothing
, isSmallCaps = Nothing
, isStrike = Nothing
, isRTL = Nothing
+ , isForceCTL = Nothing
, rVertAlign = Nothing
, rUnderline = Nothing
, rParentStyle = Nothing
@@ -240,20 +245,21 @@ elemToCharStyle :: NameSpaces
elemToCharStyle ns element parentStyle
= CharStyle <$> (CharStyleId <$> findAttrTextByName ns "w" "styleId" element)
<*> getElementStyleName ns element
- <*> (Just $ elemToRunStyle ns element parentStyle)
+ <*> Just (elemToRunStyle ns element parentStyle)
elemToRunStyle :: NameSpaces -> Element -> Maybe CharStyle -> RunStyle
elemToRunStyle ns element parentStyle
| Just rPr <- findChildByName ns "w" "rPr" element =
RunStyle
{
- isBold = checkOnOff ns rPr (elemName ns "w" "b") `mplus`
- checkOnOff ns rPr (elemName ns "w" "bCs")
- , isItalic = checkOnOff ns rPr (elemName ns "w" "i") `mplus`
- checkOnOff ns rPr (elemName ns "w" "iCs")
+ isBold = checkOnOff ns rPr (elemName ns "w" "b")
+ , isBoldCTL = checkOnOff ns rPr (elemName ns "w" "bCs")
+ , isItalic = checkOnOff ns rPr (elemName ns "w" "i")
+ , isItalicCTL = checkOnOff ns rPr (elemName ns "w" "iCs")
, isSmallCaps = checkOnOff ns rPr (elemName ns "w" "smallCaps")
, isStrike = checkOnOff ns rPr (elemName ns "w" "strike")
, isRTL = checkOnOff ns rPr (elemName ns "w" "rtl")
+ , isForceCTL = checkOnOff ns rPr (elemName ns "w" "cs")
, rVertAlign =
findChildByName ns "w" "vertAlign" rPr >>=
findAttrByName ns "w" "val" >>=
diff --git a/src/Text/Pandoc/Readers/Ipynb.hs b/src/Text/Pandoc/Readers/Ipynb.hs
index 056fa431c..a245bdad3 100644
--- a/src/Text/Pandoc/Readers/Ipynb.hs
+++ b/src/Text/Pandoc/Readers/Ipynb.hs
@@ -79,8 +79,7 @@ cellToBlocks opts lang c = do
case cellType c of
Ipynb.Markdown -> do
Pandoc _ bs <- walk fixImage <$> readMarkdown opts source
- let kvs' = ("source", source) : kvs
- return $ B.divWith ("",["cell","markdown"],kvs')
+ return $ B.divWith ("",["cell","markdown"],kvs)
$ B.fromList bs
Ipynb.Heading lev -> do
Pandoc _ bs <- readMarkdown opts
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/Ipynb.hs b/src/Text/Pandoc/Writers/Ipynb.hs
index 86e2abbdf..d01d5a7e5 100644
--- a/src/Text/Pandoc/Writers/Ipynb.hs
+++ b/src/Text/Pandoc/Writers/Ipynb.hs
@@ -102,13 +102,10 @@ extractCells _ [] = return []
extractCells opts (Div (_id,classes,kvs) xs : bs)
| "cell" `elem` classes
, "markdown" `elem` classes = do
- let meta = pairsToJSONMeta [(k,v) | (k,v) <- kvs, k /= "source"]
+ let meta = pairsToJSONMeta kvs
(newdoc, attachments) <-
runStateT (walkM addAttachment (Pandoc nullMeta xs)) mempty
- source <- case lookup "source" kvs of
- Just s -> return s
- Nothing -> writeMarkdown opts{ writerTemplate = Nothing }
- newdoc
+ source <- writeMarkdown opts{ writerTemplate = Nothing } newdoc
(Ipynb.Cell{
cellType = Markdown
, cellSource = Source $ breakLines $ T.stripEnd source
diff --git a/src/Text/Pandoc/Writers/Jira.hs b/src/Text/Pandoc/Writers/Jira.hs
index 12348f62b..4f12667d4 100644
--- a/src/Text/Pandoc/Writers/Jira.hs
+++ b/src/Text/Pandoc/Writers/Jira.hs
@@ -194,7 +194,7 @@ toJiraInlines inlines = do
Jira.Monospaced (escapeSpecialChars cs)
Emph xs -> styled Jira.Emphasis xs
Underline xs -> styled Jira.Insert xs
- Image attr _ tgt -> imageToJira attr (fst tgt) (snd tgt)
+ Image attr cap tgt -> imageToJira attr cap (fst tgt) (snd tgt)
LineBreak -> pure . singleton $ Jira.Linebreak
Link attr xs tgt -> toJiraLink attr tgt xs
Math mtype cs -> mathToJira mtype cs
@@ -233,16 +233,18 @@ escapeSpecialChars t = case plainText t of
Left _ -> singleton $ Jira.Str t
imageToJira :: PandocMonad m
- => Attr -> Text -> Text
+ => Attr -> [Inline] -> Text -> Text
-> JiraConverter m [Jira.Inline]
-imageToJira (_, classes, kvs) src title =
- let imgParams = if "thumbnail" `elem` classes
- then [Jira.Parameter "thumbnail" ""]
- else map (uncurry Jira.Parameter) kvs
- imgParams' = if T.null title
- then imgParams
- else Jira.Parameter "title" title : imgParams
- in pure . singleton $ Jira.Image imgParams' (Jira.URL src)
+imageToJira (_, classes, kvs) caption src title =
+ let imageWithParams ps = Jira.Image ps (Jira.URL src)
+ alt = stringify caption
+ in pure . singleton . imageWithParams $
+ if "thumbnail" `elem` classes
+ then [Jira.Parameter "thumbnail" ""]
+ else map (uncurry Jira.Parameter)
+ . (if T.null title then id else (("title", title):))
+ . (if T.null alt then id else (("alt", alt):))
+ $ kvs
-- | Creates a Jira Link element.
toJiraLink :: PandocMonad m
diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs
index 81de40045..561053c88 100644
--- a/src/Text/Pandoc/Writers/Ms.hs
+++ b/src/Text/Pandoc/Writers/Ms.hs
@@ -204,7 +204,9 @@ blockToMs opts (CodeBlock attr str) = do
literal ".IP" $$
literal ".nf" $$
literal "\\f[C]" $$
- hlCode $$
+ ((case T.uncons str of
+ Just ('.',_) -> literal "\\&"
+ _ -> mempty) <> hlCode) $$
literal "\\f[]" $$
literal ".fi"
blockToMs opts (LineBlock ls) = do
@@ -517,11 +519,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 =
diff --git a/test/Tests/Writers/Ms.hs b/test/Tests/Writers/Ms.hs
new file mode 100644
index 000000000..d73603314
--- /dev/null
+++ b/test/Tests/Writers/Ms.hs
@@ -0,0 +1,37 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.Ms (tests) where
+
+import Prelude
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Builder
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test (purely (writeMs def . toPandoc))
+
+tests :: [TestTree]
+tests = [ testGroup "code blocks"
+ [ "basic"
+ =: codeBlock "hello"
+ =?> unlines
+ [ ".IP"
+ , ".nf"
+ , "\\f[C]"
+ , "hello"
+ , "\\f[]"
+ , ".fi"]
+ , "escape starting ."
+ =: codeBlock ". hello"
+ =?> unlines
+ [ ".IP"
+ , ".nf"
+ , "\\f[C]"
+ , "\\&. hello"
+ , "\\f[]"
+ , ".fi"]
+ ]
+ ]
diff --git a/test/docx/golden/inline_formatting.docx b/test/docx/golden/inline_formatting.docx
index 5efe66edd..ddfd45280 100644
--- a/test/docx/golden/inline_formatting.docx
+++ b/test/docx/golden/inline_formatting.docx
Binary files differ
diff --git a/test/docx/inline_formatting.native b/test/docx/inline_formatting.native
index 000896df9..df749ffef 100644
--- a/test/docx/inline_formatting.native
+++ b/test/docx/inline_formatting.native
@@ -1,6 +1,6 @@
Pandoc (Meta {unMeta = fromList []})
[Para [Str "Regular",Space,Str "text",Space,Emph [Str "italics"],Space,Strong [Str "bold",Space,Emph [Str "bold",Space,Str "italics"]],Str "."]
,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "Small",Space,Str "Caps"],Str ",",Space,Str "and",Space,Str "this",Space,Str "is",Space,Strikeout [Str "strikethrough"],Str "."]
-,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Underline [Str "single",Space,Str "underlines",Space,Str "for",Space],Emph [Underline [Str "emphasis"]],Str "."]
+,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Underline [Str "single",Space,Str "underlines",Space,Str "for",Space,Emph [Str "emphasis"]],Str "."]
,Para [Str "Above",Space,Str "the",Space,Str "line",Space,Str "is",Space,Superscript [Str "superscript"],Space,Str "and",Space,Str "below",Space,Str "the",Space,Str "line",Space,Str "is",Space,Subscript [Str "subscript"],Str "."]
,Para [Str "A",Space,Str "line",LineBreak,Str "break."]]
diff --git a/test/ipynb/simple.out.native b/test/ipynb/simple.out.native
index 960230894..4c060b82f 100644
--- a/test/ipynb/simple.out.native
+++ b/test/ipynb/simple.out.native
@@ -1,15 +1,15 @@
Pandoc (Meta {unMeta = fromList [("jupyter",MetaMap (fromList [("nbformat",MetaString "4"),("nbformat_minor",MetaString "5")]))]})
-[Div ("",["cell","markdown"],[("source","Lorem ipsum\n===========\n\n**Lorem ipsum** dolor sit amet, consectetur adipiscing elit. Nunc luctus\nbibendum felis dictum sodales.")])
+[Div ("",["cell","markdown"],[])
[Header 1 ("lorem-ipsum",[],[]) [Str "Lorem",Space,Str "ipsum"]
,Para [Strong [Str "Lorem",Space,Str "ipsum"],Space,Str "dolor",Space,Str "sit",Space,Str "amet,",Space,Str "consectetur",Space,Str "adipiscing",Space,Str "elit.",Space,Str "Nunc",Space,Str "luctus",SoftBreak,Str "bibendum",Space,Str "felis",Space,Str "dictum",Space,Str "sodales."]]
,Div ("",["cell","code"],[])
[CodeBlock ("",["python"],[]) "print(\"hello\")"]
-,Div ("",["cell","markdown"],[("source","Pyout\n-----")])
+,Div ("",["cell","markdown"],[])
[Header 2 ("pyout",[],[]) [Str "Pyout"]]
,Div ("",["cell","code"],[("execution_count","2")])
[CodeBlock ("",["python"],[]) "from IPython.display import HTML\nHTML(\"\"\"\n<script>\nconsole.log(\"hello\");\n</script>\n<b>HTML</b>\n\"\"\")"
,Div ("",["output","execute_result"],[("execution_count","2")])
[RawBlock (Format "html") "<script>\nconsole.log(\"hello\");\n</script>\n<b>HTML</b>\nhello"]]
-,Div ("",["cell","markdown"],[("source","Image\n-----\n\nThis image ![the moon](attachment:lalune.jpg) will be included as a cell\nattachment."),("tags","[\"foo\",\"bar\"]")])
+,Div ("",["cell","markdown"],[("tags","[\"foo\",\"bar\"]")])
[Header 2 ("image",[],[]) [Str "Image"]
,Para [Str "This",Space,Str "image",Space,Image ("",[],[]) [Str "the",Space,Str "moon"] ("lalune.jpg",""),Space,Str "will",Space,Str "be",Space,Str "included",Space,Str "as",Space,Str "a",Space,Str "cell",SoftBreak,Str "attachment."]]]
diff --git a/test/lhs-test.latex b/test/lhs-test.latex
index 48d557b27..5dade622f 100644
--- a/test/lhs-test.latex
+++ b/test/lhs-test.latex
@@ -81,6 +81,9 @@
\providecommand{\tightlist}{%
\setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
\setcounter{secnumdepth}{-\maxdimen} % remove section numbering
+\ifluatex
+ \usepackage{selnolig} % disable illegal ligatures
+\fi
\author{}
\date{}
diff --git a/test/lhs-test.latex+lhs b/test/lhs-test.latex+lhs
index 806cf598d..cd229e107 100644
--- a/test/lhs-test.latex+lhs
+++ b/test/lhs-test.latex+lhs
@@ -48,6 +48,9 @@
\providecommand{\tightlist}{%
\setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
\setcounter{secnumdepth}{-\maxdimen} % remove section numbering
+\ifluatex
+ \usepackage{selnolig} % disable illegal ligatures
+\fi
\author{}
\date{}
diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs
index ff7661094..d0a1a6f18 100644
--- a/test/test-pandoc.hs
+++ b/test/test-pandoc.hs
@@ -37,6 +37,7 @@ import qualified Tests.Writers.JATS
import qualified Tests.Writers.Jira
import qualified Tests.Writers.LaTeX
import qualified Tests.Writers.Markdown
+import qualified Tests.Writers.Ms
import qualified Tests.Writers.Muse
import qualified Tests.Writers.Native
import qualified Tests.Writers.Org
@@ -70,6 +71,7 @@ tests pandocPath = testGroup "pandoc tests"
, testGroup "Muse" Tests.Writers.Muse.tests
, testGroup "FB2" Tests.Writers.FB2.tests
, testGroup "PowerPoint" Tests.Writers.Powerpoint.tests
+ , testGroup "Ms" Tests.Writers.Ms.tests
]
, testGroup "Readers"
[ testGroup "LaTeX" Tests.Readers.LaTeX.tests
diff --git a/test/writer.jira b/test/writer.jira
index 14080c230..aff0dc320 100644
--- a/test/writer.jira
+++ b/test/writer.jira
@@ -513,9 +513,9 @@ or here: <http://example.com/>
h1. {anchor:images}Images
From "Voyage dans la Lune" by Georges Melies \(1902):
-!lalune.jpg|title=fig:Voyage dans la Lune!
+!lalune.jpg|title=fig:Voyage dans la Lune, alt=lalune!
-Here is a movie !movie.jpg! icon.
+Here is a movie !movie.jpg|alt=movie! icon.
----
h1. {anchor:footnotes}Footnotes
diff --git a/test/writer.latex b/test/writer.latex
index e859e2d2e..05dccbb1f 100644
--- a/test/writer.latex
+++ b/test/writer.latex
@@ -63,6 +63,9 @@
\providecommand{\tightlist}{%
\setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
\setcounter{secnumdepth}{-\maxdimen} % remove section numbering
+\ifluatex
+ \usepackage{selnolig} % disable illegal ligatures
+\fi
\title{Pandoc Test Suite}
\author{John MacFarlane \and Anonymous}
diff --git a/test/writers-lang-and-dir.latex b/test/writers-lang-and-dir.latex
index a9eefb32f..2e29bb196 100644
--- a/test/writers-lang-and-dir.latex
+++ b/test/writers-lang-and-dir.latex
@@ -66,6 +66,9 @@
\newcommand{\textfrench}[2][]{\foreignlanguage{french}{#2}}
\newenvironment{french}[2][]{\begin{otherlanguage}{french}}{\end{otherlanguage}}
\fi
+\ifluatex
+ \usepackage{selnolig} % disable illegal ligatures
+\fi
\ifxetex
% Load bidi as late as possible as it modifies e.g. graphicx
\usepackage{bidi}