aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README6
-rw-r--r--pandoc.cabal4
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs4
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs25
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs42
-rw-r--r--src/Text/Pandoc/Readers/Org.hs24
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs3
-rw-r--r--stack.yaml4
-rw-r--r--tests/Tests/Old.hs2
-rw-r--r--tests/Tests/Readers/Docx.hs12
-rw-r--r--tests/Tests/Readers/Org.hs27
-rw-r--r--tests/docx/track_changes_move.docxbin0 -> 26151 bytes
-rw-r--r--tests/docx/track_changes_move_accept.native3
-rw-r--r--tests/docx/track_changes_move_all.native4
-rw-r--r--tests/docx/track_changes_move_reject.native3
-rw-r--r--tests/markdown-reader-more.native4
16 files changed, 122 insertions, 45 deletions
diff --git a/README b/README
index 9aaa561bb..b589bc03a 100644
--- a/README
+++ b/README
@@ -538,9 +538,9 @@ General writer options
`--columns=`*NUMBER*
-: Specify length of lines in characters (for text wrapping).
- This affects only the generated source code, not the layout on
- the rendered page.
+: Specify length of lines in characters. This affects text wrapping
+ in the generated source code (see `--wrap`). It also affects
+ calculation of column widths for plain text tables (see [Tables] below).
`--toc`, `--table-of-contents`
diff --git a/pandoc.cabal b/pandoc.cabal
index 8fca917d9..eebcb6a2c 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -257,7 +257,7 @@ Library
text >= 0.11 && < 1.3,
zip-archive >= 0.2.3.4 && < 0.4,
HTTP >= 4000.0.5 && < 4000.4,
- texmath >= 0.8.6.1 && < 0.9,
+ texmath >= 0.8.6.2 && < 0.9,
xml >= 1.3.12 && < 1.4,
random >= 1 && < 1.2,
extensible-exceptions >= 0.1 && < 0.2,
@@ -267,7 +267,7 @@ Library
base64-bytestring >= 0.1 && < 1.1,
zlib >= 0.5 && < 0.7,
highlighting-kate >= 0.6.1 && < 0.7,
- data-default >= 0.4 && < 0.6,
+ data-default >= 0.4 && < 0.7,
temporary >= 1.1 && < 1.3,
blaze-html >= 0.5 && < 0.9,
blaze-markup >= 0.5.1 && < 0.8,
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 364483929..7265ef8dd 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -661,14 +661,14 @@ elemToParPart ns element
| isElem ns "w" "r" element =
elemToRun ns element >>= (\r -> return $ PlainRun r)
elemToParPart ns element
- | isElem ns "w" "ins" element
+ | isElem ns "w" "ins" element || isElem ns "w" "moveTo" element
, Just cId <- findAttr (elemName ns "w" "id") element
, Just cAuthor <- findAttr (elemName ns "w" "author") element
, Just cDate <- findAttr (elemName ns "w" "date") element = do
runs <- mapD (elemToRun ns) (elChildren element)
return $ Insertion cId cAuthor cDate runs
elemToParPart ns element
- | isElem ns "w" "del" element
+ | isElem ns "w" "del" element || isElem ns "w" "moveFrom" element
, Just cId <- findAttr (elemName ns "w" "id") element
, Just cAuthor <- findAttr (elemName ns "w" "author") element
, Just cDate <- findAttr (elemName ns "w" "date") element = do
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index fb936cff7..8ee5da543 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -971,11 +971,20 @@ htmlTag :: Monad m
htmlTag f = try $ do
lookAhead (char '<')
inp <- getInput
- let (next : rest) = canonicalizeTags $ parseTagsOptions
- parseOptions{ optTagWarning = True } inp
+ let (next : _) = canonicalizeTags $ parseTagsOptions
+ parseOptions{ optTagWarning = False } inp
guard $ f next
+ let handleTag tagname = do
+ -- <www.boe.es/buscar/act.php?id=BOE-A-1996-8930#a66>
+ -- should NOT be parsed as an HTML tag, see #2277
+ guard $ not ('.' `elem` tagname)
+ -- <https://example.org> should NOT be a tag either.
+ -- tagsoup will parse it as TagOpen "https:" [("example.org","")]
+ guard $ not (null tagname)
+ guard $ last tagname /= ':'
+ rendered <- manyTill anyChar (char '>')
+ return (next, rendered ++ ">")
case next of
- TagWarning _ -> fail "encountered TagWarning"
TagComment s
| "<!--" `isPrefixOf` inp -> do
count (length s + 4) anyChar
@@ -983,13 +992,9 @@ htmlTag f = try $ do
char '>'
return (next, "<!--" ++ s ++ "-->")
| otherwise -> fail "bogus comment mode, HTML5 parse error"
- _ -> do
- -- we get a TagWarning on things like
- -- <www.boe.es/buscar/act.php?id=BOE-A-1996-8930#a66>
- -- which should NOT be parsed as an HTML tag, see #2277
- guard $ not $ hasTagWarning rest
- rendered <- manyTill anyChar (char '>')
- return (next, rendered ++ ">")
+ TagOpen tagname _attr -> handleTag tagname
+ TagClose tagname -> handleTag tagname
+ _ -> mzero
mkAttr :: [(String, String)] -> Attr
mkAttr attr = (attribsId, attribsClasses, attribsKV)
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index b5d175453..e43714526 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -122,9 +122,6 @@ inList = do
ctx <- stateParserContext <$> getState
guard (ctx == ListItemState)
-isNull :: F Inlines -> Bool
-isNull ils = B.isNull $ runF ils def
-
spnl :: Parser [Char] st ()
spnl = try $ do
skipSpaces
@@ -188,31 +185,38 @@ charsInBalancedBrackets openBrackets =
-- document structure
--
-titleLine :: MarkdownParser (F Inlines)
-titleLine = try $ do
+rawTitleBlockLine :: MarkdownParser String
+rawTitleBlockLine = do
char '%'
skipSpaces
- res <- many $ (notFollowedBy newline >> inline)
- <|> try (endline >> whitespace)
- newline
+ first <- anyLine
+ rest <- many $ try $ do spaceChar
+ notFollowedBy blankline
+ skipSpaces
+ anyLine
+ return $ trim $ unlines (first:rest)
+
+titleLine :: MarkdownParser (F Inlines)
+titleLine = try $ do
+ raw <- rawTitleBlockLine
+ res <- parseFromString (many inline) raw
return $ trimInlinesF $ mconcat res
authorsLine :: MarkdownParser (F [Inlines])
authorsLine = try $ do
- char '%'
- skipSpaces
- authors <- sepEndBy (many (notFollowedBy (satisfy $ \c ->
- c == ';' || c == '\n') >> inline))
- (char ';' <|>
- try (newline >> notFollowedBy blankline >> spaceChar))
- newline
- return $ sequence $ filter (not . isNull) $ map (trimInlinesF . mconcat) authors
+ raw <- rawTitleBlockLine
+ let sep = (char ';' <* spaces) <|> newline
+ let pAuthors = sepEndBy
+ (trimInlinesF . mconcat <$> many
+ (try $ notFollowedBy sep >> inline))
+ sep
+ sequence <$> parseFromString pAuthors raw
dateLine :: MarkdownParser (F Inlines)
dateLine = try $ do
- char '%'
- skipSpaces
- trimInlinesF . mconcat <$> manyTill inline newline
+ raw <- rawTitleBlockLine
+ res <- parseFromString (many inline) raw
+ return $ trimInlinesF $ mconcat res
titleBlock :: MarkdownParser ()
titleBlock = pandocTitleBlock <|> mmdTitleBlock
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 7dd611be3..5e98be31d 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -391,6 +391,9 @@ lookupBlockAttribute key =
type BlockProperties = (Int, String) -- (Indentation, Block-Type)
+updateIndent :: BlockProperties -> Int -> BlockProperties
+updateIndent (_, blkType) indent = (indent, blkType)
+
orgBlock :: OrgParser (F Blocks)
orgBlock = try $ do
blockProp@(_, blkType) <- blockHeaderStart
@@ -407,11 +410,23 @@ orgBlock = try $ do
_ -> withParsed (fmap $ divWithClass blkType)
blockHeaderStart :: OrgParser (Int, String)
-blockHeaderStart = try $ (,) <$> indent <*> blockType
+blockHeaderStart = try $ (,) <$> indentation <*> blockType
where
- indent = length <$> many spaceChar
blockType = map toLower <$> (stringAnyCase "#+begin_" *> orgArgWord)
+indentation :: OrgParser Int
+indentation = try $ do
+ tabStop <- getOption readerTabStop
+ s <- many spaceChar
+ return $ spaceLength tabStop s
+
+spaceLength :: Int -> String -> Int
+spaceLength tabStop s = (sum . map charLen) s
+ where
+ charLen ' ' = 1
+ charLen '\t' = tabStop
+ charLen _ = 0
+
withRaw' :: (String -> F Blocks) -> BlockProperties -> OrgParser (F Blocks)
withRaw' f blockProp = (ignHeaders *> (f <$> rawBlockContent blockProp))
@@ -450,7 +465,8 @@ codeBlock blkProp = do
skipSpaces
(classes, kv) <- codeHeaderArgs <|> (mempty <$ ignHeaders)
id' <- fromMaybe "" <$> lookupBlockAttribute "name"
- content <- rawBlockContent blkProp
+ leadingIndent <- lookAhead indentation
+ content <- rawBlockContent (updateIndent blkProp leadingIndent)
resultsContent <- followingResultsBlock
let includeCode = exportsCode kv
let includeResults = exportsResults kv
@@ -472,7 +488,7 @@ rawBlockContent (indent, blockType) = try $
unlines . map commaEscaped <$> manyTill indentedLine blockEnder
where
indentedLine = try $ ("" <$ blankline) <|> (indentWith indent *> anyLine)
- blockEnder = try $ indentWith indent *> stringAnyCase ("#+end_" <> blockType)
+ blockEnder = try $ skipSpaces *> stringAnyCase ("#+end_" <> blockType)
parsedBlockContent :: BlockProperties -> OrgParser (F Blocks)
parsedBlockContent blkProps = try $ do
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 1b3393853..bb588dbe5 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -508,7 +508,8 @@ blockToLaTeX (RawBlock f x)
blockToLaTeX (BulletList []) = return empty -- otherwise latex error
blockToLaTeX (BulletList lst) = do
incremental <- gets stIncremental
- let inc = if incremental then "[<+->]" else ""
+ beamer <- writerBeamer `fmap` gets stOptions
+ let inc = if beamer && incremental then "[<+->]" else ""
items <- mapM listItemToLaTeX lst
let spacing = if isTightList lst
then text "\\tightlist"
diff --git a/stack.yaml b/stack.yaml
index 1ae854c29..108e40f27 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -8,7 +8,9 @@ flags:
packages:
- '.'
extra-deps:
-- texmath-0.8.6.1
+- texmath-0.8.6.2
+- data-default-0.6.0
+- data-default-instances-base-0.1.0
# to compile against aeson 0.11.0.0:
# - 'aeson-0.11.0.0'
# - 'fail-4.9.0.0'
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index 36bb3398e..b292b1f11 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -57,7 +57,7 @@ tests = [ testGroup "markdown"
"tables.txt" "tables.native"
, test "pipe tables" ["-r", "markdown", "-w", "native", "--columns=80"]
"pipe-tables.txt" "pipe-tables.native"
- , test "more" ["-r", "markdown", "-w", "native", "-S"]
+ , test "more" ["-r", "markdown", "-w", "native", "-s", "-S"]
"markdown-reader-more.txt" "markdown-reader-more.native"
, lhsReaderTest "markdown+lhs"
]
diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs
index e09d56529..aeb6bf939 100644
--- a/tests/Tests/Readers/Docx.hs
+++ b/tests/Tests/Readers/Docx.hs
@@ -266,6 +266,18 @@ tests = [ testGroup "inlines"
"keep deletion (all)"
"docx/track_changes_deletion.docx"
"docx/track_changes_deletion_all.native"
+ , testCompareWithOpts def{readerTrackChanges=AcceptChanges}
+ "move text (accept)"
+ "docx/track_changes_move.docx"
+ "docx/track_changes_move_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=RejectChanges}
+ "move text (reject)"
+ "docx/track_changes_move.docx"
+ "docx/track_changes_move_reject.native"
+ , testCompareWithOpts def{readerTrackChanges=AllChanges}
+ "move text (all)"
+ "docx/track_changes_move.docx"
+ "docx/track_changes_move_all.native"
]
, testGroup "media"
[ testMediaBag
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index b095ac60a..bb9b37d13 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -1054,6 +1054,33 @@ tests =
" where greeting = \"moin\"\n"
in codeBlockWith attr' code'
+ , "Source block with indented code" =:
+ unlines [ " #+BEGIN_SRC haskell"
+ , " main = putStrLn greeting"
+ , " where greeting = \"moin\""
+ , " #+END_SRC" ] =?>
+ let attr' = ("", ["haskell"], [])
+ code' = "main = putStrLn greeting\n" ++
+ " where greeting = \"moin\"\n"
+ in codeBlockWith attr' code'
+
+ , "Source block with tab-indented code" =:
+ unlines [ "\t#+BEGIN_SRC haskell"
+ , "\tmain = putStrLn greeting"
+ , "\t where greeting = \"moin\""
+ , "\t#+END_SRC" ] =?>
+ let attr' = ("", ["haskell"], [])
+ code' = "main = putStrLn greeting\n" ++
+ " where greeting = \"moin\"\n"
+ in codeBlockWith attr' code'
+
+ , "Empty source block" =:
+ unlines [ " #+BEGIN_SRC haskell"
+ , " #+END_SRC" ] =?>
+ let attr' = ("", ["haskell"], [])
+ code' = ""
+ in codeBlockWith attr' code'
+
, "Source block between paragraphs" =:
unlines [ "Low German greeting"
, " #+BEGIN_SRC haskell"
diff --git a/tests/docx/track_changes_move.docx b/tests/docx/track_changes_move.docx
new file mode 100644
index 000000000..b70779fd4
--- /dev/null
+++ b/tests/docx/track_changes_move.docx
Binary files differ
diff --git a/tests/docx/track_changes_move_accept.native b/tests/docx/track_changes_move_accept.native
new file mode 100644
index 000000000..0cf276768
--- /dev/null
+++ b/tests/docx/track_changes_move_accept.native
@@ -0,0 +1,3 @@
+[Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "text."]
+,Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "text",Space,Str "to",Space,Str "be",Space,Str "moved."]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "more",Space,Str "text."]]
diff --git a/tests/docx/track_changes_move_all.native b/tests/docx/track_changes_move_all.native
new file mode 100644
index 000000000..3afae83a5
--- /dev/null
+++ b/tests/docx/track_changes_move_all.native
@@ -0,0 +1,4 @@
+[Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "text."]
+,Para [Span ("",["insertion"],[("author","Jesse Rosenthal"),("date","2016-04-16T08:20:00Z")]) [Str "Here",Space,Str "is",Space,Str "the",Space,Str "text",Space,Str "to",Space,Str "be",Space,Str "moved."]]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "more",Space,Str "text."]
+,Para [Span ("",["deletion"],[("author","Jesse Rosenthal"),("date","2016-04-16T08:20:00Z")]) [Str "Here",Space,Str "is",Space,Str "the",Space,Str "text",Space,Str "to",Space,Str "be",Space,Str "moved."]]]
diff --git a/tests/docx/track_changes_move_reject.native b/tests/docx/track_changes_move_reject.native
new file mode 100644
index 000000000..9c57871b6
--- /dev/null
+++ b/tests/docx/track_changes_move_reject.native
@@ -0,0 +1,3 @@
+[Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "text."]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "more",Space,Str "text."]
+,Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "text",Space,Str "to",Space,Str "be",Space,Str "moved."]]
diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native
index 0148e9394..c38ffe038 100644
--- a/tests/markdown-reader-more.native
+++ b/tests/markdown-reader-more.native
@@ -1,5 +1,5 @@
-[Para [Str "spanning",Space,Str "multiple",Space,Str "lines",SoftBreak,Str "%",Space,Str "Author",Space,Str "One",SoftBreak,Str "Author",Space,Str "Two;",Space,Str "Author",Space,Str "Three;",SoftBreak,Str "Author",Space,Str "Four"]
-,Header 1 ("additional-markdown-reader-tests",[],[]) [Str "Additional",Space,Str "markdown",Space,Str "reader",Space,Str "tests"]
+Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",Space,Str "One"],MetaInlines [Str "Author",Space,Str "Two"],MetaInlines [Str "Author",Space,Str "Three"],MetaInlines [Str "Author",Space,Str "Four"]]),("title",MetaInlines [Str "Title",SoftBreak,Str "spanning",Space,Str "multiple",Space,Str "lines"])]})
+[Header 1 ("additional-markdown-reader-tests",[],[]) [Str "Additional",Space,Str "markdown",Space,Str "reader",Space,Str "tests"]
,Header 2 ("blank-line-before-url-in-link-reference",[],[]) [Str "Blank",Space,Str "line",Space,Str "before",Space,Str "URL",Space,Str "in",Space,Str "link",Space,Str "reference"]
,Para [Link ("",[],[]) [Str "foo"] ("/url",""),Space,Str "and",Space,Link ("",[],[]) [Str "bar"] ("/url","title")]
,Header 2 ("raw-context-environments",[],[]) [Str "Raw",Space,Str "ConTeXt",Space,Str "environments"]