Escape starting periods in ms writer code blocks

If a line of ms code block output starts with a period (.), it should
be prepended by '\&' so that it is not interpreted as a roff command.

Fixes #6505
This commit is contained in:
Michael Hoffmann 2020-07-08 23:37:30 +02:00
parent 804e8eeed2
commit 09ea10e2b1
4 changed files with 43 additions and 1 deletions

View file

@ -816,6 +816,7 @@ test-suite test-pandoc
Tests.Writers.FB2 Tests.Writers.FB2
Tests.Writers.Powerpoint Tests.Writers.Powerpoint
Tests.Writers.OOXML Tests.Writers.OOXML
Tests.Writers.Ms
if os(windows) if os(windows)
cpp-options: -D_WINDOWS cpp-options: -D_WINDOWS
default-language: Haskell2010 default-language: Haskell2010

View file

@ -204,7 +204,9 @@ blockToMs opts (CodeBlock attr str) = do
literal ".IP" $$ literal ".IP" $$
literal ".nf" $$ literal ".nf" $$
literal "\\f[C]" $$ literal "\\f[C]" $$
hlCode $$ ((case T.uncons str of
Just ('.',_) -> literal "\\&"
_ -> mempty) <> hlCode) $$
literal "\\f[]" $$ literal "\\f[]" $$
literal ".fi" literal ".fi"
blockToMs opts (LineBlock ls) = do blockToMs opts (LineBlock ls) = do

37
test/Tests/Writers/Ms.hs Normal file
View file

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

View file

@ -37,6 +37,7 @@ import qualified Tests.Writers.JATS
import qualified Tests.Writers.Jira import qualified Tests.Writers.Jira
import qualified Tests.Writers.LaTeX import qualified Tests.Writers.LaTeX
import qualified Tests.Writers.Markdown import qualified Tests.Writers.Markdown
import qualified Tests.Writers.Ms
import qualified Tests.Writers.Muse import qualified Tests.Writers.Muse
import qualified Tests.Writers.Native import qualified Tests.Writers.Native
import qualified Tests.Writers.Org import qualified Tests.Writers.Org
@ -70,6 +71,7 @@ tests pandocPath = testGroup "pandoc tests"
, testGroup "Muse" Tests.Writers.Muse.tests , testGroup "Muse" Tests.Writers.Muse.tests
, testGroup "FB2" Tests.Writers.FB2.tests , testGroup "FB2" Tests.Writers.FB2.tests
, testGroup "PowerPoint" Tests.Writers.Powerpoint.tests , testGroup "PowerPoint" Tests.Writers.Powerpoint.tests
, testGroup "Ms" Tests.Writers.Ms.tests
] ]
, testGroup "Readers" , testGroup "Readers"
[ testGroup "LaTeX" Tests.Readers.LaTeX.tests [ testGroup "LaTeX" Tests.Readers.LaTeX.tests