diff options
-rw-r--r-- | pandoc.cabal | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/EPUB.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Textile.hs | 29 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 18 | ||||
-rw-r--r-- | tests/textile-reader.native | 13 | ||||
-rw-r--r-- | tests/textile-reader.textile | 6 |
7 files changed, 49 insertions, 33 deletions
diff --git a/pandoc.cabal b/pandoc.cabal index b5110de3d..4b2da0f9e 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -226,7 +226,7 @@ Library directory >= 1 && < 1.3, bytestring >= 0.9 && < 0.11, text >= 0.11 && < 1.2, - zip-archive >= 0.2.3.2 && < 0.3, + zip-archive >= 0.2.3.4 && < 0.3, old-locale >= 1 && < 1.1, time >= 1.2 && < 1.5, HTTP >= 4000.0.5 && < 4000.3, @@ -405,7 +405,7 @@ Test-Suite test-pandoc HUnit >= 1.2 && < 1.3, containers >= 0.1 && < 0.6, ansi-terminal >= 0.5 && < 0.7, - zip-archive >= 0.2.3.2 && < 0.3 + zip-archive >= 0.2.3.4 && < 0.3 Other-Modules: Tests.Old Tests.Helpers Tests.Arbitrary diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index f900c0adc..d4eef3556 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -95,7 +95,7 @@ fetchImages mimes root arc (query iq -> links) = (mapMaybe getEntry links) where getEntry link = - let abslink = root </> link in + let abslink = normalise (root </> link) in (link , lookup link mimes, ) . fromEntry <$> findEntryByPath abslink arc diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index cd34da942..ee64e8f2a 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -56,7 +56,7 @@ import Text.Pandoc.Builder (Inlines, Blocks, trimInlines) import qualified Text.Pandoc.Builder as B import Text.Pandoc.Options import Text.Pandoc.Parsing -import Text.Pandoc.Readers.HTML ( htmlTag, isInlineTag, isBlockTag ) +import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag ) import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock ) import Text.HTML.TagSoup (parseTags, innerText, fromAttrib, Tag(..)) import Text.HTML.TagSoup.Match @@ -133,12 +133,9 @@ blockParsers = [ codeBlock , rawLaTeXBlock' , maybeExplicitBlock "table" table , maybeExplicitBlock "p" para - , endBlock + , mempty <$ blanklines ] -endBlock :: Parser [Char] ParserState Blocks -endBlock = string "\n\n" >> return mempty - -- | Any block in the order of definition of blockParsers block :: Parser [Char] ParserState Blocks block = do @@ -193,7 +190,7 @@ header = try $ do attr <- attributes char '.' lookAhead whitespace - name <- trimInlines . mconcat <$> manyTill inline blockBreak + name <- trimInlines . mconcat <$> many inline attr' <- registerHeader attr name return $ B.headerWith attr' level name @@ -304,17 +301,12 @@ definitionListItem = try $ do ds <- parseFromString parseBlocks (s ++ "\n\n") return [ds] --- | This terminates a block such as a paragraph. Because of raw html --- blocks support, we have to lookAhead for a rawHtmlBlock. -blockBreak :: Parser [Char] ParserState () -blockBreak = try (newline >> blanklines >> return ()) <|> - try (optional spaces >> lookAhead rawHtmlBlock >> return ()) - -- raw content -- | A raw Html Block, optionally followed by blanklines rawHtmlBlock :: Parser [Char] ParserState Blocks rawHtmlBlock = try $ do + skipMany spaceChar (_,b) <- htmlTag isBlockTag optional blanklines return $ B.rawBlock "html" b @@ -328,7 +320,7 @@ rawLaTeXBlock' = do -- | In textile, paragraphs are separated by blank lines. para :: Parser [Char] ParserState Blocks -para = B.para . trimInlines . mconcat <$> manyTill inline blockBreak +para = B.para . trimInlines . mconcat <$> many1 inline -- Tables @@ -505,11 +497,14 @@ whitespace = many1 spaceChar >> return B.space <?> "whitespace" -- | In Textile, an isolated endline character is a line break endline :: Parser [Char] ParserState Inlines endline = try $ do - newline >> notFollowedBy blankline + newline + notFollowedBy blankline + notFollowedBy listStart + notFollowedBy rawHtmlBlock return B.linebreak rawHtmlInline :: Parser [Char] ParserState Inlines -rawHtmlInline = B.rawInline "html" . snd <$> htmlTag isInlineTag +rawHtmlInline = B.rawInline "html" . snd <$> htmlTag (const True) -- | Raw LaTeX Inline rawLaTeXInline' :: Parser [Char] ParserState Inlines @@ -561,7 +556,9 @@ escapedTag = B.str <$> -- | Any special symbol defined in wordBoundaries symbol :: Parser [Char] ParserState Inlines -symbol = B.str . singleton <$> (oneOf wordBoundaries <|> oneOf markupChars) +symbol = B.str . singleton <$> (notFollowedBy newline *> + notFollowedBy rawHtmlBlock *> + oneOf wordBoundaries) -- | Inline code code :: Parser [Char] ParserState Inlines diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 5e02419d8..38031b7dc 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -842,7 +842,7 @@ inlineToOpenXML opts (Image alt (src, tit)) = do let size = imageSize img let (xpt,ypt) = maybe (120,120) sizeInPoints size -- 12700 emu = 1 pt - let (xemu,yemu) = (xpt * 12700, ypt * 12700) + let (xemu,yemu) = fitToPage (xpt * 12700, ypt * 12700) let cNvPicPr = mknode "pic:cNvPicPr" [] $ mknode "a:picLocks" [("noChangeArrowheads","1"),("noChangeAspect","1")] () let nvPicPr = mknode "pic:nvPicPr" [] @@ -907,3 +907,11 @@ parseXml refArchive distArchive relpath = >>= parseXMLDoc . UTF8.toStringLazy . fromEntry) of Just d -> return d Nothing -> fail $ relpath ++ " corrupt or missing in reference docx" + +-- | Scales the image to fit the page +fitToPage :: (Integer, Integer) -> (Integer, Integer) +fitToPage (x, y) + --5440680 is the emu width size of a letter page in portrait, minus the margins + | x > 5440680 = + (5440680, round $ (5440680 / ((fromIntegral :: Integer -> Double) x)) * (fromIntegral y)) + | otherwise = (x, y) diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index d140932a7..3ed20ae87 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -303,12 +303,16 @@ isLineBreakOrSpace _ = False blockToLaTeX :: Block -- ^ Block to convert -> State WriterState Doc blockToLaTeX Null = return empty -blockToLaTeX (Div (_,classes,_) bs) = do +blockToLaTeX (Div (identifier,classes,_) bs) = do beamer <- writerBeamer `fmap` gets stOptions + ref <- toLabel identifier + let linkAnchor = if null identifier + then empty + else "\\hyperdef{}" <> braces (text ref) contents <- blockListToLaTeX bs if beamer && "notes" `elem` classes -- speaker notes then return $ "\\note" <> braces contents - else return contents + else return (linkAnchor $$ contents) blockToLaTeX (Plain lst) = inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst -- title beginning with fig: indicates that the image is a figure @@ -665,11 +669,11 @@ inlineToLaTeX (Span (id',classes,_) ils) = do let noEmph = "csl-no-emph" `elem` classes let noStrong = "csl-no-strong" `elem` classes let noSmallCaps = "csl-no-smallcaps" `elem` classes - label' <- if null id' - then return empty - else toLabel id' >>= \x -> - return (text "\\label" <> braces (text x)) - fmap (label' <>) + ref <- toLabel id' + let linkAnchor = if null id' + then empty + else "\\hyperdef{}" <> braces (text ref) + fmap (linkAnchor <>) ((if noEmph then inCmd "textup" else id) . (if noStrong then inCmd "textnormal" else id) . (if noSmallCaps then inCmd "textnormal" else id) . diff --git a/tests/textile-reader.native b/tests/textile-reader.native index f82c4a896..0a0b10bd3 100644 --- a/tests/textile-reader.native +++ b/tests/textile-reader.native @@ -67,6 +67,11 @@ Pandoc (Meta {unMeta = fromList []}) ,BulletList [[Plain [Str "one"]] ,[Plain [Str "two",LineBreak,Str "->",Space,Str "and",Space,Str "more"]]] +,Header 2 ("issue-1513",[],[]) [Str "Issue",Space,Str "#1513"] +,Para [Str "List:"] +,BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]]] ,Header 2 ("definition-list",[],[]) [Str "Definition",Space,Str "List"] ,DefinitionList [([Str "coffee"], @@ -145,13 +150,9 @@ Pandoc (Meta {unMeta = fromList []}) ,RawBlock (Format "html") "<div class=\"foobar\">" ,Para [Str "any",Space,Strong [Str "Raw",Space,Str "HTML",Space,Str "Block"],Space,Str "with",Space,Str "bold"] ,RawBlock (Format "html") "</div>" -,Para [Str "Html",Space,Str "blocks",Space,Str "can",Space,Str "be"] -,RawBlock (Format "html") "<div>" -,Para [Str "inlined"] -,RawBlock (Format "html") "</div>" -,Para [Str "as",Space,Str "well."] +,Para [Str "Html",Space,Str "blocks",Space,Str "can",Space,Str "be",Space,RawInline (Format "html") "<div>",Str "inlined",RawInline (Format "html") "</div>",Space,Str "as",Space,Str "well."] ,BulletList - [[Plain [Str "this",Space,Str "<div>",Space,Str "won\8217t",Space,Str "produce",Space,Str "raw",Space,Str "html",Space,Str "blocks",Space,Str "</div>"]] + [[Plain [Str "this",Space,RawInline (Format "html") "<div>",Space,Str "won\8217t",Space,Str "produce",Space,Str "raw",Space,Str "html",Space,Str "blocks",Space,RawInline (Format "html") "</div>"]] ,[Plain [Str "but",Space,Str "this",Space,RawInline (Format "html") "<strong>",Space,Str "will",Space,Str "produce",Space,Str "inline",Space,Str "html",Space,RawInline (Format "html") "</strong>"]]] ,Para [Str "Can",Space,Str "you",Space,Str "prove",Space,Str "that",Space,Str "2",Space,Str "<",Space,Str "3",Space,Str "?"] ,Header 1 ("raw-latex",[],[]) [Str "Raw",Space,Str "LaTeX"] diff --git a/tests/textile-reader.textile b/tests/textile-reader.textile index c0c0659b7..e1e143531 100644 --- a/tests/textile-reader.textile +++ b/tests/textile-reader.textile @@ -123,6 +123,12 @@ h2. Issue #1500 * two -> and more +h2. Issue #1513 + +List: +* one +* two + h2. Definition List - coffee := Hot and black |