From 1fde92053fb1763c6af913aa9628827dff9ef899 Mon Sep 17 00:00:00 2001 From: mb21 Date: Sun, 10 Jan 2016 13:30:32 +0100 Subject: LaTeX writer: figure label --- src/Text/Pandoc/Writers/LaTeX.hs | 43 ++++++++++++++++++++++------------------ 1 file changed, 24 insertions(+), 19 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 2dcbf62bf..7b2911bcf 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -408,7 +408,7 @@ blockToLaTeX (Div (identifier,classes,kvs) bs) = do blockToLaTeX (Plain lst) = inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst -- title beginning with fig: indicates that the image is a figure -blockToLaTeX (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do +blockToLaTeX (Para [Image attr@(ident, _, _) txt (src,'f':'i':'g':':':tit)]) = do inNote <- gets stInNote modify $ \st -> st{ stInMinipage = True, stNotes = [] } capt <- inlineListToLaTeX txt @@ -420,13 +420,14 @@ blockToLaTeX (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do else brackets <$> inlineListToLaTeX (walk deNote txt) img <- inlineToLaTeX (Image attr txt (src,tit)) let footnotes = notesToLaTeX notes + figure <- refLabel ident $ cr <> + "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$ + ("\\caption" <> captForLof <> braces capt) $$ + "\\end{figure}" <> cr return $ if inNote -- can't have figures in notes then "\\begin{center}" $$ img $+$ capt $$ "\\end{center}" - else "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$ - ("\\caption" <> captForLof <> braces capt) $$ - "\\end{figure}" $$ - footnotes + else figure $$ footnotes -- . . . indicates pause in beamer slides blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do beamer <- writerBeamer `fmap` gets stOptions @@ -717,9 +718,8 @@ sectionHeader :: Bool -- True for unnumbered -> Int -> [Inline] -> State WriterState Doc -sectionHeader unnumbered ref level lst = do +sectionHeader unnumbered ident level lst = do txt <- inlineListToLaTeX lst - lab <- text `fmap` toLabel ref plain <- stringToLaTeX TextString $ foldl (++) "" $ map stringify lst let noNote (Note _) = Str "" noNote x = x @@ -742,16 +742,6 @@ sectionHeader unnumbered ref level lst = do book <- gets stBook opts <- gets stOptions let level' = if book || writerChapters opts then level - 1 else level - internalLinks <- gets stInternalLinks - let refLabel x = (if ref `elem` internalLinks - then text "\\hypertarget" - <> braces lab - <> braces x - else x) - let headerWith x y = refLabel $ text x <> y <> - if null ref - then empty - else text "\\label" <> braces lab let sectionType = case level' of 0 | writerBeamer opts -> "part" | otherwise -> "chapter" @@ -767,16 +757,31 @@ sectionHeader unnumbered ref level lst = do -- needed for \paragraph, \subparagraph in quote environment -- see http://tex.stackexchange.com/questions/169830/ else empty + stuffing' <- refLabel ident $ text ('\\':sectionType) <> stuffing return $ if level' > 5 then txt - else prefix $$ - headerWith ('\\':sectionType) stuffing + else prefix $$ stuffing' $$ if unnumbered then "\\addcontentsline{toc}" <> braces (text sectionType) <> braces txtNoNotes else empty +-- | Append label to x and wrap in hypertarget +refLabel :: String -> Doc -> State WriterState Doc +refLabel ident x = do + ref <- text `fmap` toLabel ident + internalLinks <- gets stInternalLinks + let hypertarget y = if ident `elem` internalLinks + then text "\\hypertarget" + <> braces ref + <> braces y + else y + label = if null ident + then empty + else text "\\label" <> braces ref + return $ hypertarget $ x <> label + -- | Convert list of inline elements to LaTeX. inlineListToLaTeX :: [Inline] -- ^ Inlines to convert -> State WriterState Doc -- cgit v1.2.3 From 0b9c54d9f31db88d5cd8e888921dffc2a108f8d4 Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Tue, 8 Mar 2016 00:27:09 -0500 Subject: Docx reader: update feature checklist. The feature checklist in the source code was out of date. Update. --- src/Text/Pandoc/Readers/Docx.hs | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index eb71d8dd8..c399a2174 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -50,8 +50,7 @@ implemented, [-] means partially implemented): * Inlines - [X] Str - - [X] Emph (From italics. `underline` currently read as span. In - future, it might optionally be emph as well) + - [X] Emph (italics and underline both read as Emph) - [X] Strong - [X] Strikeout - [X] Superscript @@ -62,11 +61,10 @@ implemented, [-] means partially implemented): - [X] Code (styled with `VerbatimChar`) - [X] Space - [X] LineBreak (these are invisible in Word: entered with Shift-Return) - - [ ] Math + - [X] Math - [X] Link (links to an arbitrary bookmark create a span with the target as id and "anchor" class) - - [-] Image (Links to path in archive. Future option for - data-encoded URI likely.) + - [X] Image - [X] Note (Footnotes and Endnotes are silently combined.) -} -- cgit v1.2.3 From 6bfaa5ad15d2c3acfc61ddf5ec442ca733016373 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 8 Mar 2016 10:08:14 -0800 Subject: DokuWiki writer: use $$ for display math. --- src/Text/Pandoc/Writers/DokuWiki.hs | 5 ++++- tests/writer.dokuwiki | 2 +- 2 files changed, 5 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index f1088b158..56e2b9027 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -452,8 +452,11 @@ inlineToDokuWiki _ (Code _ str) = inlineToDokuWiki _ (Str str) = return $ escapeString str -inlineToDokuWiki _ (Math _ str) = return $ "$" ++ str ++ "$" +inlineToDokuWiki _ (Math mathType str) = return $ delim ++ str ++ delim -- note: str should NOT be escaped + where delim = case mathType of + DisplayMath -> "$$" + InlineMath -> "$" inlineToDokuWiki _ (RawInline f str) | f == Format "dokuwiki" = return str diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki index fe1f8296a..79fcdde8a 100644 --- a/tests/writer.dokuwiki +++ b/tests/writer.dokuwiki @@ -459,7 +459,7 @@ Ellipses…and…and…. * $\alpha \wedge \omega$ * $223$ * $p$-Tree - * Here’s some display math: $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$ + * Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ * Here’s one that has a line break in it: $\alpha + \omega \times x^2$. These shouldn’t be math: -- cgit v1.2.3 From 4ed64835cb475f3da80ed7b729516c7a90891d94 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 9 Mar 2016 08:33:13 -0800 Subject: Markdown reader: don't cross line boundary parsing pipe table row. Previously an emph element could be parsed across the newline at the end of the pipe table row. I thought this would help with #2765, but it doesn't. --- src/Text/Pandoc/Readers/Markdown.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 587726084..0eeda0fee 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1372,7 +1372,13 @@ sepPipe = try $ do -- parse a row, also returning probable alignments for org-table cells pipeTableRow :: MarkdownParser (F [Blocks]) -pipeTableRow = do +pipeTableRow = try $ do + scanForPipe + raw <- anyLine + parseFromString pipeTableRow' (raw ++ "\n") + +pipeTableRow' :: MarkdownParser (F [Blocks]) +pipeTableRow' = do skipMany spaceChar openPipe <- (True <$ char '|') <|> return False let cell = mconcat <$> -- cgit v1.2.3 From 6e950a8eb5001314869013395c9c72ee05079110 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 9 Mar 2016 08:44:31 -0800 Subject: Markdown reader: allow `+` separators in pipe table cells. We already allowed them in the header, but not in the body rows, for some reason. This gives compatibility with org-mode tables. --- src/Text/Pandoc/Readers/Markdown.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 0eeda0fee..6caf1728c 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1382,16 +1382,14 @@ pipeTableRow' = do skipMany spaceChar openPipe <- (True <$ char '|') <|> return False let cell = mconcat <$> - many (notFollowedBy (blankline <|> char '|') >> inline) - first <- cell - rest <- many $ sepPipe *> cell + many (notFollowedBy (blankline <|> oneOf "+|") >> inline) + cells <- cell `sepBy1` sepPipe -- surrounding pipes needed for a one-column table: - guard $ not (null rest && not openPipe) + guard $ not (length cells == 1 && not openPipe) optional (char '|') blankline - let cells = sequence (first:rest) return $ do - cells' <- cells + cells' <- sequence cells return $ map (\ils -> case trimInlines ils of -- cgit v1.2.3 From 54a68616d7f9259840fd8a884d806782a73236a9 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 9 Mar 2016 10:11:32 -0800 Subject: Markdown reader: Clean up pipe table parsing. --- src/Text/Pandoc/Readers/Markdown.hs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 6caf1728c..c99838352 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1354,16 +1354,18 @@ pipeTable = try $ do nonindentSpaces lookAhead nonspaceChar (heads,(aligns, seplengths)) <- (,) <$> pipeTableRow <*> pipeBreak + let heads' = take (length aligns) <$> heads lines' <- many pipeTableRow + let lines'' = map (take (length aligns) <$>) lines' let maxlength = maximum $ - map (\x -> length . stringify $ runF x def) (heads : lines') + map (\x -> length . stringify $ runF x def) (heads' : lines'') numColumns <- getOption readerColumns let widths = if maxlength > numColumns then map (\len -> fromIntegral (len + 1) / fromIntegral numColumns) seplengths else replicate (length aligns) 0.0 - return $ (aligns, widths, heads, sequence lines') + return $ (aligns, widths, heads', sequence lines'') sepPipe :: MarkdownParser () sepPipe = try $ do @@ -1375,19 +1377,17 @@ pipeTableRow :: MarkdownParser (F [Blocks]) pipeTableRow = try $ do scanForPipe raw <- anyLine - parseFromString pipeTableRow' (raw ++ "\n") + parseFromString pipeTableRow' raw pipeTableRow' :: MarkdownParser (F [Blocks]) pipeTableRow' = do skipMany spaceChar openPipe <- (True <$ char '|') <|> return False - let cell = mconcat <$> - many (notFollowedBy (blankline <|> oneOf "+|") >> inline) - cells <- cell `sepBy1` sepPipe + let cell = mconcat <$> (many (notFollowedBy (char '|') >> inline)) + cells <- cell `sepEndBy1` (char '|') -- surrounding pipes needed for a one-column table: guard $ not (length cells == 1 && not openPipe) - optional (char '|') - blankline + spaces >> eof return $ do cells' <- sequence cells return $ map -- cgit v1.2.3 From 2b55b76ebec87f4d35b2e641e054bd6dfc74be09 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 9 Mar 2016 11:46:00 -0800 Subject: Markdown reader: Improved pipe table parsing. Fixes #2765. Added test case. --- src/Text/Pandoc/Readers/Markdown.hs | 30 +++++++++++++++--------------- tests/pipe-tables.native | 16 +++++++++++++++- tests/pipe-tables.txt | 8 ++++++++ 3 files changed, 38 insertions(+), 16 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index c99838352..b5d175453 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1376,25 +1376,25 @@ sepPipe = try $ do pipeTableRow :: MarkdownParser (F [Blocks]) pipeTableRow = try $ do scanForPipe - raw <- anyLine - parseFromString pipeTableRow' raw - -pipeTableRow' :: MarkdownParser (F [Blocks]) -pipeTableRow' = do skipMany spaceChar openPipe <- (True <$ char '|') <|> return False - let cell = mconcat <$> (many (notFollowedBy (char '|') >> inline)) - cells <- cell `sepEndBy1` (char '|') + -- split into cells + let chunk = void (code <|> rawHtmlInline <|> escapedChar <|> rawLaTeXInline') + <|> void (noneOf "|\n\r") + let cellContents = ((trim . snd) <$> withRaw (many chunk)) >>= + parseFromString pipeTableCell + cells <- cellContents `sepEndBy1` (char '|') -- surrounding pipes needed for a one-column table: guard $ not (length cells == 1 && not openPipe) - spaces >> eof - return $ do - cells' <- sequence cells - return $ map - (\ils -> - case trimInlines ils of - ils' | B.isNull ils' -> mempty - | otherwise -> B.plain $ ils') cells' + blankline + return $ sequence cells + +pipeTableCell :: MarkdownParser (F Blocks) +pipeTableCell = do + result <- many inline + if null result + then return mempty + else return $ B.plain . mconcat <$> sequence result pipeTableHeaderPart :: Parser [Char] st (Alignment, Int) pipeTableHeaderPart = try $ do diff --git a/tests/pipe-tables.native b/tests/pipe-tables.native index 6cd37f6ff..63c2c17bc 100644 --- a/tests/pipe-tables.native +++ b/tests/pipe-tables.native @@ -98,4 +98,18 @@ ,Para [Str "Pipe",Space,Str "table",Space,Str "with",Space,Str "no",Space,Str "body:"] ,Table [] [AlignDefault] [0.0] [[Plain [Str "Header"]]] - []] + [] +,Para [Str "Pipe",Space,Str "table",Space,Str "with",Space,Str "tricky",Space,Str "cell",Space,Str "contents",Space,Str "(see",Space,Str "#2765):"] +,Table [] [AlignLeft,AlignRight,AlignRight] [0.0,0.0,0.0] + [[] + ,[Plain [Str "IP_gene8-_1st"]] + ,[Plain [Str "IP_gene8+_1st"]]] + [[[Plain [Str "IP_gene8-_1st"]] + ,[Plain [Str "1.0000000"]] + ,[Plain [Str "0.4357325"]]] + ,[[Plain [Str "IP_gene8+_1st"]] + ,[Plain [Str "0.4357325"]] + ,[Plain [Str "1.0000000"]]] + ,[[Plain [Str "foo",Code ("",[],[]) "bar|baz"]] + ,[Plain [Str "and|escaped"]] + ,[Plain [Str "3.0000000"]]]]] diff --git a/tests/pipe-tables.txt b/tests/pipe-tables.txt index e93f64af9..c27c71113 100644 --- a/tests/pipe-tables.txt +++ b/tests/pipe-tables.txt @@ -72,3 +72,11 @@ Pipe table with no body: | Header | | ------ | +Pipe table with tricky cell contents (see #2765): + +| | IP_gene8-_1st| IP_gene8+_1st| +|:--------------|-------------:|-------------:| +|IP_gene8-_1st | 1.0000000| 0.4357325| +|IP_gene8+_1st | 0.4357325| 1.0000000| +|foo`bar|baz` | and\|escaped | 3.0000000| + -- cgit v1.2.3 From 139fa54d48a878c91f6e56c17ee50e9d589d379f Mon Sep 17 00:00:00 2001 From: mb21 Date: Wed, 9 Mar 2016 23:16:02 +0100 Subject: Docx Writer: handle image alt text closes #2754 --- src/Text/Pandoc/Writers/Docx.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 150e19043..a841e1b66 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -1103,7 +1103,7 @@ inlineToOpenXML opts (Link _ txt (src,_)) = do M.insert src i extlinks } return i return [ mknode "w:hyperlink" [("r:id",id')] contents ] -inlineToOpenXML opts (Image attr alt (src, tit)) = do +inlineToOpenXML opts (Image attr alt (src, _)) = do -- first, check to see if we've already done this image pageWidth <- gets stPrintWidth imgs <- gets stImages @@ -1154,7 +1154,7 @@ inlineToOpenXML opts (Image attr alt (src, tit)) = do mknode "wp:inline" [] [ mknode "wp:extent" [("cx",show xemu),("cy",show yemu)] () , mknode "wp:effectExtent" [("b","0"),("l","0"),("r","0"),("t","0")] () - , mknode "wp:docPr" [("descr",tit),("id","1"),("name","Picture")] () + , mknode "wp:docPr" [("descr",stringify alt),("id","1"),("name","Picture")] () , graphic ] let imgext = case mt >>= extensionFromMimeType of Just x -> '.':x -- cgit v1.2.3 From a485c42d78d8bc819f7ad1bef137d54a324c5ea9 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 10 Mar 2016 19:59:55 -0800 Subject: Fixed behavior of base tag. + If the base path does not end with slash, the last component will be replaced. E.g. base = `http://example.com/foo` combines with `bar.html` to give `http://example.com/bar.html`. + If the href begins with a slash, the whole path of the base is replaced. E.g. base = `http://example.com/foo/` combines with `/bar.html` to give `http://example.com/bar.html`. Closes #2777. --- src/Text/Pandoc/Readers/HTML.hs | 28 +++++++++++----------------- tests/Tests/Readers/HTML.hs | 5 ++++- 2 files changed, 15 insertions(+), 18 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 69df13aac..959a2d16f 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -63,7 +63,7 @@ import Debug.Trace (trace) import Text.TeXMath (readMathML, writeTeX) import Data.Default (Default (..), def) import Control.Monad.Reader (Reader,ask, asks, local, runReader) -import Network.URI (isURI) +import Network.URI (URI, parseURIReference, nonStrictRelativeTo) import Text.Pandoc.Error import Text.Pandoc.CSS (foldOrElse, pickStyleAttrProps) import Text.Pandoc.Compat.Monoid ((<>)) @@ -103,7 +103,7 @@ data HTMLState = HTMLState { parserState :: ParserState, noteTable :: [(String, Blocks)], - baseHref :: Maybe String, + baseHref :: Maybe URI, identifiers :: Set.Set String, headerMap :: M.Map Inlines String } @@ -145,15 +145,9 @@ pHead = pInTags "head" $ pTitle <|> pMetaTag <|> pBaseTag <|> (mempty <$ pAnyTag return mempty pBaseTag = do bt <- pSatisfy (~== TagOpen "base" []) - let baseH = fromAttrib "href" bt - if null baseH - then return mempty - else do - let baseH' = case reverse baseH of - '/':_ -> baseH - _ -> baseH ++ "/" - updateState $ \st -> st{ baseHref = Just baseH' } - return mempty + updateState $ \st -> st{ baseHref = + parseURIReference $ fromAttrib "href" bt } + return mempty block :: TagParser Blocks block = do @@ -610,9 +604,9 @@ pLink = try $ do tag <- pSatisfy $ tagOpenLit "a" (const True) mbBaseHref <- baseHref <$> getState let url' = fromAttrib "href" tag - let url = case (isURI url', mbBaseHref) of - (False, Just h) -> h ++ url' - _ -> url' + let url = case (parseURIReference url', mbBaseHref) of + (Just rel, Just bs) -> show (rel `nonStrictRelativeTo` bs) + _ -> url' let title = fromAttrib "title" tag let uid = fromAttrib "id" tag let cls = words $ fromAttrib "class" tag @@ -624,9 +618,9 @@ pImage = do tag <- pSelfClosing (=="img") (isJust . lookup "src") mbBaseHref <- baseHref <$> getState let url' = fromAttrib "src" tag - let url = case (isURI url', mbBaseHref) of - (False, Just h) -> h ++ url' - _ -> url' + let url = case (parseURIReference url', mbBaseHref) of + (Just rel, Just bs) -> show (rel `nonStrictRelativeTo` bs) + _ -> url' let title = fromAttrib "title" tag let alt = fromAttrib "alt" tag let uid = fromAttrib "id" tag diff --git a/tests/Tests/Readers/HTML.hs b/tests/Tests/Readers/HTML.hs index 2eb87a2f3..ff27b8aed 100644 --- a/tests/Tests/Readers/HTML.hs +++ b/tests/Tests/Readers/HTML.hs @@ -15,11 +15,14 @@ html = handleError . readHtml def tests :: [Test] tests = [ testGroup "base tag" [ test html "simple" $ - "\"Stickman\"" =?> + "\"Stickman\"" =?> plain (image "http://www.w3schools.com/images/stickman.gif" "" (text "Stickman")) , test html "slash at end of base" $ "\"Stickman\"" =?> plain (image "http://www.w3schools.com/images/stickman.gif" "" (text "Stickman")) + , test html "slash at beginning of href" $ + "\"Stickman\"" =?> + plain (image "http://www.w3schools.com/stickman.gif" "" (text "Stickman")) , test html "absolute URL" $ "\"Stickman\"" =?> plain (image "http://example.com/stickman.gif" "" (text "Stickman")) -- cgit v1.2.3 From 102ba9ecb869da80fac03480b2dd03a695a4f78c Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Thu, 10 Mar 2016 15:19:55 -0500 Subject: Docx Reader: Add state to the parser, for warnings In order to be able to collect warnings during parsing, we add a state monad transformer to the D monad. At the moment, this only includes a list of warning strings (nothing currently triggers them, however). We use StateT instead of WriterT to correspond more closely with the warnings behavior in T.P.Parsing. --- src/Text/Pandoc/Readers/Docx/Parse.hs | 25 +++++++++++++++++++------ 1 file changed, 19 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index eec8b12c9..e4cfe4930 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -50,6 +50,7 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..) , Row(..) , Cell(..) , archiveToDocx + , archiveToDocxWithWarnings ) where import Codec.Archive.Zip import Text.XML.Light @@ -60,6 +61,7 @@ import Data.Bits ((.|.)) import qualified Data.ByteString.Lazy as B import qualified Text.Pandoc.UTF8 as UTF8 import Control.Monad.Reader +import Control.Monad.State import Control.Applicative ((<|>)) import qualified Data.Map as M import Text.Pandoc.Compat.Except @@ -81,16 +83,20 @@ data ReaderEnv = ReaderEnv { envNotes :: Notes } deriving Show +data ReaderState = ReaderState { stateWarnings :: [String] } + deriving Show + + data DocxError = DocxError | WrongElem deriving Show instance Error DocxError where noMsg = WrongElem -type D = ExceptT DocxError (Reader ReaderEnv) +type D = ExceptT DocxError (ReaderT ReaderEnv (State ReaderState)) -runD :: D a -> ReaderEnv -> Either DocxError a -runD dx re = runReader (runExceptT dx) re +runD :: D a -> ReaderEnv -> ReaderState -> (Either DocxError a, ReaderState) +runD dx re rs = runState (runReaderT (runExceptT dx) re) rs maybeToD :: Maybe a -> D a maybeToD (Just a) = return a @@ -257,7 +263,10 @@ type Author = String type ChangeDate = String archiveToDocx :: Archive -> Either DocxError Docx -archiveToDocx archive = do +archiveToDocx archive = fst <$> archiveToDocxWithWarnings archive + +archiveToDocxWithWarnings :: Archive -> Either DocxError (Docx, [String]) +archiveToDocxWithWarnings archive = do let notes = archiveToNotes archive numbering = archiveToNumbering archive rels = archiveToRelationships archive @@ -265,8 +274,12 @@ archiveToDocx archive = do (styles, parstyles) = archiveToStyles archive rEnv = ReaderEnv notes numbering rels media Nothing styles parstyles InDocument - doc <- runD (archiveToDocument archive) rEnv - return $ Docx doc + rState = ReaderState { stateWarnings = [] } + (eitherDoc, st) = runD (archiveToDocument archive) rEnv rState + case eitherDoc of + Right doc -> Right (Docx doc, stateWarnings st) + Left e -> Left e + archiveToDocument :: Archive -> D Document -- cgit v1.2.3 From ee03e954d0d3cb76971c91001348762f55224890 Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Sat, 12 Mar 2016 10:18:01 -0500 Subject: Add readDocxWithWarnings The regular readDocx just becomes a special case. --- src/Text/Pandoc/Readers/Docx.hs | 21 +++++++++++++++------ 1 file changed, 15 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index c399a2174..604bc20de 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -69,7 +69,8 @@ implemented, [-] means partially implemented): -} module Text.Pandoc.Readers.Docx - ( readDocx + ( readDocxWithWarnings + , readDocx ) where import Codec.Archive.Zip @@ -96,14 +97,22 @@ import qualified Data.Sequence as Seq (null) import Text.Pandoc.Error import Text.Pandoc.Compat.Except +readDocxWithWarnings :: ReaderOptions + -> B.ByteString + -> Either PandocError (Pandoc, MediaBag, [String]) +readDocxWithWarnings opts bytes = + case archiveToDocxWithWarnings (toArchive bytes) of + Right (docx, warnings) -> do + (meta, blks, mediaBag) <- docxToOutput opts docx + return (Pandoc meta blks, mediaBag, warnings) + Left _ -> Left (ParseFailure "couldn't parse docx file") + readDocx :: ReaderOptions -> B.ByteString -> Either PandocError (Pandoc, MediaBag) -readDocx opts bytes = - case archiveToDocx (toArchive bytes) of - Right docx -> (\(meta, blks, mediaBag) -> (Pandoc meta blks, mediaBag)) - <$> (docxToOutput opts docx) - Left _ -> Left (ParseFailure "couldn't parse docx file") +readDocx opts bytes = do + (pandoc, mediaBag, _) <- readDocxWithWarnings opts bytes + return (pandoc, mediaBag) data DState = DState { docxAnchorMap :: M.Map String String , docxMediaBag :: MediaBag -- cgit v1.2.3 From 5c055b4cf3cdfac534a74c5c5775aa2d58889150 Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Sat, 20 Feb 2016 21:27:08 -0500 Subject: Introduce file-scope parsing (parse-before-combine) Traditionally pandoc operates on multiple files by first concetenating them (around extra line breaks) and then processing the joined file. So it only parses a multi-file document at the document scope. This has the benefit that footnotes and links can be in different files, but it also introduces a couple of difficulties: - it is difficult to join files with footnotes without some sort of preprocessing, which makes it difficult to write academic documents in small pieces. - it makes it impossible to process multiple binary input files, which can't be catted. - it makes it impossible to process files from different input formats. This commit introduces alternative method. Instead of catting the files first, it parses the files first, and then combines the parsed output. This makes it impossible to have links across multiple files, and auto-identified headers won't work correctly if headers in multiple files have the same name. On the other hand, footnotes across multiple files will work correctly and will allow more freedom for input formats. Since ByteStringReaders can currently only read one binary file, and will ignore subsequent files, we also changes the behavior to automatically parse before combining if using the ByteStringReader. If we use one file, it will work as normal. If there is more than one file it will combine them after parsing (assuming that the format is the same). Note that this is intended to be an optional method, defaulting to off. Turn it on with `--file-scope`. --- pandoc.hs | 27 +++++++++++++++++++++++---- src/Text/Pandoc/Options.hs | 2 ++ 2 files changed, 25 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/pandoc.hs b/pandoc.hs index 72a7592d8..59277690a 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -215,6 +215,7 @@ data Opt = Opt , optExtractMedia :: Maybe FilePath -- ^ Path to extract embedded media , optTrace :: Bool -- ^ Print debug information , optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes. + , optFileScope :: Bool -- ^ Parse input files before combining , optKaTeXStylesheet :: Maybe String -- ^ Path to stylesheet for KaTeX , optKaTeXJS :: Maybe String -- ^ Path to js file for KaTeX } @@ -278,6 +279,7 @@ defaultOpts = Opt , optExtractMedia = Nothing , optTrace = False , optTrackChanges = AcceptChanges + , optFileScope = False , optKaTeXStylesheet = Nothing , optKaTeXJS = Nothing } @@ -387,6 +389,11 @@ options = "accept|reject|all") "" -- "Accepting or reject MS Word track-changes."" + , Option "" ["file-scope"] + (NoArg + (\opt -> return opt { optFileScope = True })) + "" -- "Parse input files before combining" + , Option "" ["extract-media"] (ReqArg (\arg opt -> @@ -1117,6 +1124,7 @@ convertWithOpts opts args = do , optExtractMedia = mbExtractMedia , optTrace = trace , optTrackChanges = trackChanges + , optFileScope = fileScope , optKaTeXStylesheet = katexStylesheet , optKaTeXJS = katexJS } = opts @@ -1269,6 +1277,7 @@ convertWithOpts opts args = do , readerDefaultImageExtension = defaultImageExtension , readerTrace = trace , readerTrackChanges = trackChanges + , readerFileScope = fileScope } when (not (isTextFormat format) && outputFile == "-") $ @@ -1301,13 +1310,23 @@ convertWithOpts opts args = do then handleIncludes else return . Right - (doc, media) <- fmap handleError $ - case reader of + let sourceToDoc :: [FilePath] -> IO (Pandoc, MediaBag) + sourceToDoc sources' = fmap handleError $ + case reader of StringReader r-> do - srcs <- convertTabs . intercalate "\n" <$> readSources sources + srcs <- convertTabs . intercalate "\n" <$> readSources sources' doc <- handleIncludes' srcs either (return . Left) (\s -> fmap (,mempty) <$> r readerOpts s) doc - ByteStringReader r -> readFiles sources >>= r readerOpts + ByteStringReader r -> readFiles sources' >>= r readerOpts + + -- We parse first if fileScope is set OR if the reader is a + -- BSReader. So, if it's a StringReader AND not fileScope, we + -- don't. + (doc, media) <- case reader of + (StringReader _) | not fileScope -> sourceToDoc sources + _ -> do + pairs <- mapM (\s -> sourceToDoc [s]) sources + return (mconcat $ map fst pairs, mconcat $ map snd pairs) let writerOptions = def { writerStandalone = standalone', writerTemplate = templ, diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 333f499fb..b5736c63d 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -264,6 +264,7 @@ data ReaderOptions = ReaderOptions{ , readerDefaultImageExtension :: String -- ^ Default extension for images , readerTrace :: Bool -- ^ Print debugging info , readerTrackChanges :: TrackChanges + , readerFileScope :: Bool -- ^ Parse before combining } deriving (Show, Read, Data, Typeable, Generic) instance Default ReaderOptions @@ -280,6 +281,7 @@ instance Default ReaderOptions , readerDefaultImageExtension = "" , readerTrace = False , readerTrackChanges = AcceptChanges + , readerFileScope = False } -- -- cgit v1.2.3 From 855c8b43f0497125f8d24b113ce0df92ed7d074b Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Wed, 16 Mar 2016 12:50:32 -0400 Subject: Docx reader: Don't make numbered heads into lists. Word uses list numbering styles to number its headings. We only call something a numbered list if it does not also heave a heading style. --- src/Text/Pandoc/Readers/Docx/Parse.hs | 14 ++++++++------ 1 file changed, 8 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index e4cfe4930..cbdd86221 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -589,12 +589,14 @@ elemToBodyPart ns element sty <- asks envParStyles let parstyle = elemToParagraphStyle ns element sty parparts <- mapD (elemToParPart ns) (elChildren element) - case pNumInfo parstyle of - Just (numId, lvl) -> do - num <- asks envNumbering - let levelInfo = lookupLevel numId lvl num - return $ ListItem parstyle numId lvl levelInfo parparts - Nothing -> return $ Paragraph parstyle parparts + -- Word uses list enumeration for numbered headings, so we only + -- want to infer a list from the styles if it is NOT a heading. + case pHeading parstyle of + Nothing | Just (numId, lvl) <- pNumInfo parstyle -> do + num <- asks envNumbering + let levelInfo = lookupLevel numId lvl num + return $ ListItem parstyle numId lvl levelInfo parparts + _ -> return $ Paragraph parstyle parparts elemToBodyPart ns element | isElem ns "w" "tbl" element = do let caption' = findChild (elemName ns "w" "tblPr") element -- cgit v1.2.3 From 28c7617f19c4d6dd69e2aa9c904af13e11e4e639 Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Fri, 18 Mar 2016 09:38:26 -0400 Subject: Docx reader: Handle alternate content Some word functions -- especially graphics -- give various choices for content so there can be backwards compatibility. This follows the largely undocumented feature by working through the choices until we find one that works. Note that we had to split out the processing of child elems of runs into a separate function so we can recurse properly. Any processing of an element *within* a run (other than a plain run) should go into `childElemToRun`. --- src/Text/Pandoc/Readers/Docx/Parse.hs | 51 +++++++++++++++++++++++++---------- 1 file changed, 37 insertions(+), 14 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index cbdd86221..364483929 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -717,36 +717,58 @@ elemToExtent drawingElem = getDim at = findElement (QName "extent" (Just wp_ns) (Just "wp")) drawingElem >>= findAttr (QName at Nothing Nothing) >>= safeRead -elemToRun :: NameSpaces -> Element -> D Run -elemToRun ns element - | isElem ns "w" "r" element - , Just drawingElem <- findChild (elemName ns "w" "drawing") element = + +childElemToRun :: NameSpaces -> Element -> D Run +childElemToRun ns element + | isElem ns "w" "drawing" element = let a_ns = "http://schemas.openxmlformats.org/drawingml/2006/main" - drawing = findElement (QName "blip" (Just a_ns) (Just "a")) drawingElem + drawing = findElement (QName "blip" (Just a_ns) (Just "a")) element >>= findAttr (QName "embed" (lookup "r" ns) (Just "r")) in case drawing of Just s -> expandDrawingId s >>= - (\(fp, bs) -> return $ InlineDrawing fp bs $ elemToExtent drawingElem) + (\(fp, bs) -> return $ InlineDrawing fp bs $ elemToExtent element) Nothing -> throwError WrongElem -elemToRun ns element - | isElem ns "w" "r" element - , Just ref <- findChild (elemName ns "w" "footnoteReference") element - , Just fnId <- findAttr (elemName ns "w" "id") ref = do +childElemToRun ns element + | isElem ns "w" "footnoteReference" element + , Just fnId <- findAttr (elemName ns "w" "id") element = do notes <- asks envNotes case lookupFootnote fnId notes of Just e -> do bps <- local (\r -> r {envLocation=InFootnote}) $ mapD (elemToBodyPart ns) (elChildren e) return $ Footnote bps Nothing -> return $ Footnote [] -elemToRun ns element - | isElem ns "w" "r" element - , Just ref <- findChild (elemName ns "w" "endnoteReference") element - , Just enId <- findAttr (elemName ns "w" "id") ref = do +childElemToRun ns element + | isElem ns "w" "endnoteReference" element + , Just enId <- findAttr (elemName ns "w" "id") element = do notes <- asks envNotes case lookupEndnote enId notes of Just e -> do bps <- local (\r -> r {envLocation=InEndnote}) $ mapD (elemToBodyPart ns) (elChildren e) return $ Endnote bps Nothing -> return $ Endnote [] +childElemToRun _ _ = throwError WrongElem + +elemToRun :: NameSpaces -> Element -> D Run +elemToRun ns element + | isElem ns "w" "r" element + , Just altCont <- findChild (elemName ns "mc" "AlternateContent") element = + do let choices = findChildren (elemName ns "mc" "Choice") altCont + choiceChildren = map head $ filter (not . null) $ map elChildren choices + outputs <- mapD (childElemToRun ns) choiceChildren + case outputs of + r : _ -> return r + [] -> throwError WrongElem +elemToRun ns element + | isElem ns "w" "r" element + , Just drawingElem <- findChild (elemName ns "w" "drawing") element = + childElemToRun ns drawingElem +elemToRun ns element + | isElem ns "w" "r" element + , Just ref <- findChild (elemName ns "w" "footnoteReference") element = + childElemToRun ns ref +elemToRun ns element + | isElem ns "w" "r" element + , Just ref <- findChild (elemName ns "w" "endnoteReference") element = + childElemToRun ns ref elemToRun ns element | isElem ns "w" "r" element = do runElems <- elemToRunElems ns element @@ -955,3 +977,4 @@ elemToRunElems _ _ = throwError WrongElem setFont :: Maybe Font -> ReaderEnv -> ReaderEnv setFont f s = s{envFont = f} + -- cgit v1.2.3 From e821b05125c8b18a1c09a5d4fd62ee7483704bbb Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 18 Mar 2016 16:16:18 -0700 Subject: LaTeX writer: Avoid double toprule in headerless table with caption. Closes #2742. --- src/Text/Pandoc/Writers/LaTeX.hs | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 4e4279ec5..52f525fe7 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -571,18 +571,21 @@ blockToLaTeX (Header level (id',classes,_) lst) = do blockToLaTeX (Table caption aligns widths heads rows) = do headers <- if all null heads then return empty - else ($$ "\\midrule\n") `fmap` - (tableRowToLaTeX True aligns widths) heads + else do + contents <- (tableRowToLaTeX True aligns widths) heads + return ("\\toprule" $$ contents $$ "\\midrule") let endhead = if all null heads then empty else text "\\endhead" + let endfirsthead = if all null heads + then empty + else text "\\endfirsthead" captionText <- inlineListToLaTeX caption let capt = if isEmpty captionText then empty - else text "\\caption" <> braces captionText - <> "\\tabularnewline\n\\toprule\n" - <> headers - <> "\\endfirsthead" + else text "\\caption" <> braces captionText <> "\\tabularnewline" + $$ headers + $$ endfirsthead rows' <- mapM (tableRowToLaTeX False aligns widths) rows let colDescriptors = text $ concat $ map toColDescriptor aligns modify $ \s -> s{ stTable = True } @@ -590,7 +593,7 @@ blockToLaTeX (Table caption aligns widths heads rows) = do braces ("@{}" <> colDescriptors <> "@{}") -- the @{} removes extra space at beginning and end $$ capt - $$ "\\toprule" + $$ (if all null heads then "\\toprule" else empty) $$ headers $$ endhead $$ vcat rows' -- cgit v1.2.3 From 976e7e2054c2a4c889c3f02b83fdd092513f22b4 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 18 Mar 2016 16:36:56 -0700 Subject: ConTeXt writer: fix whitespace at line beginning in line blocks. Add a `\strut` after `\crlf` before space. Closes #2744, #2745. Thanks to @c-foster. This uses the fix suggested by @c-foster. Mid-line spaces are still not supported, because of limitations of the Markdown parser. --- src/Text/Pandoc/Writers/ConTeXt.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 498e2d10f..8d54d62bd 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -279,7 +279,17 @@ blockListToConTeXt lst = liftM vcat $ mapM blockToConTeXt lst -- | Convert list of inline elements to ConTeXt. inlineListToConTeXt :: [Inline] -- ^ Inlines to convert -> State WriterState Doc -inlineListToConTeXt lst = liftM hcat $ mapM inlineToConTeXt lst +inlineListToConTeXt lst = liftM hcat $ mapM inlineToConTeXt $ addStruts lst + -- We add a \strut after a line break that precedes a space, + -- or the space gets swallowed + where addStruts (LineBreak : s : xs) | isSpacey s = + LineBreak : RawInline (Format "context") "\\strut " : s : + addStruts xs + addStruts (x:xs) = x : addStruts xs + addStruts [] = [] + isSpacey Space = True + isSpacey (Str ('\160':_)) = True + isSpacey _ = False -- | Convert inline element to ConTeXt inlineToConTeXt :: Inline -- ^ Inline to convert -- cgit v1.2.3 From 44f95484a4b4544ef41dab087af92a80fc5996cd Mon Sep 17 00:00:00 2001 From: Mauro Bieg Date: Fri, 19 Feb 2016 10:10:12 +0100 Subject: LaTeX Writer: fix polyglossia to babel env mapping allow for optional argument in square brackets, closes #2728 --- src/Text/Pandoc/Writers/LaTeX.hs | 2 +- tests/writers-lang-and-dir.latex | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 0f47132b3..3f7c28e81 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -223,7 +223,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do ++ poly ++ "}{##2}}}\n" else "\\newcommand{\\text" ++ poly ++ "}[2][]{\\foreignlanguage{" ++ babel ++ "}{#2}}\n" ++ - "\\newenvironment{" ++ poly ++ "}[1]{\\begin{otherlanguage}{" + "\\newenvironment{" ++ poly ++ "}[2][]{\\begin{otherlanguage}{" ++ babel ++ "}}{\\end{otherlanguage}}\n" ) -- eliminate duplicates that have same polyglossia name diff --git a/tests/writers-lang-and-dir.latex b/tests/writers-lang-and-dir.latex index 056809a5e..db2611cff 100644 --- a/tests/writers-lang-and-dir.latex +++ b/tests/writers-lang-and-dir.latex @@ -29,14 +29,14 @@ \ifnum 0\ifxetex 1\fi\ifluatex 1\fi=0 % if pdftex \usepackage[shorthands=off,ngerman,british,ngerman,spanish,french,main=english]{babel} \newcommand{\textgerman}[2][]{\foreignlanguage{ngerman}{#2}} - \newenvironment{german}[1]{\begin{otherlanguage}{ngerman}}{\end{otherlanguage}} + \newenvironment{german}[2][]{\begin{otherlanguage}{ngerman}}{\end{otherlanguage}} \newcommand{\textenglish}[2][]{\foreignlanguage{british}{#2}} - \newenvironment{english}[1]{\begin{otherlanguage}{british}}{\end{otherlanguage}} + \newenvironment{english}[2][]{\begin{otherlanguage}{british}}{\end{otherlanguage}} \let\oritextspanish\textspanish \AddBabelHook{spanish}{beforeextras}{\renewcommand{\textspanish}{\oritextspanish}} \AddBabelHook{spanish}{afterextras}{\renewcommand{\textspanish}[2][]{\foreignlanguage{spanish}{##2}}} \newcommand{\textfrench}[2][]{\foreignlanguage{french}{#2}} - \newenvironment{french}[1]{\begin{otherlanguage}{french}}{\end{otherlanguage}} + \newenvironment{french}[2][]{\begin{otherlanguage}{french}}{\end{otherlanguage}} \else \usepackage{polyglossia} \setmainlanguage[]{english} -- cgit v1.2.3 From b1ffdf3b01c5acec18ee5f776841f478eb7b7810 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 22 Mar 2016 16:56:10 -0700 Subject: Fixed bug in Markdown raw HTML parsing. This was a regression, with the rewrite of `htmlInBalanced` (from `Text.Pandoc.Readers.HTML`) in 1.17. It caused newlines to be omitted in raw HTML blocks. Closes #2804. --- src/Text/Pandoc/Readers/HTML.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 959a2d16f..fb936cff7 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -939,7 +939,7 @@ htmlInBalanced f = try $ do (TagClose _ : TagPosition er ec : _) -> do let ls = er - sr let cs = ec - sc - lscontents <- concat <$> count ls anyLine + lscontents <- unlines <$> count ls anyLine cscontents <- count cs anyChar (_,closetag) <- htmlTag (~== TagClose tn) return (lscontents ++ cscontents ++ closetag) -- cgit v1.2.3 From 499985c1a30cb711b1dcf9ae80ccb876ae31f0ec Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 22 Mar 2016 17:20:39 -0700 Subject: Updated copyright dates to include 2016. --- pandoc.cabal | 2 +- src/Text/Pandoc.hs | 4 ++-- src/Text/Pandoc/Asciify.hs | 4 ++-- src/Text/Pandoc/Error.hs | 4 ++-- src/Text/Pandoc/Highlighting.hs | 4 ++-- src/Text/Pandoc/ImageSize.hs | 4 ++-- src/Text/Pandoc/MIME.hs | 4 ++-- src/Text/Pandoc/Options.hs | 4 ++-- src/Text/Pandoc/PDF.hs | 4 ++-- src/Text/Pandoc/Parsing.hs | 4 ++-- src/Text/Pandoc/Pretty.hs | 4 ++-- src/Text/Pandoc/Process.hs | 4 ++-- src/Text/Pandoc/SelfContained.hs | 4 ++-- src/Text/Pandoc/Shared.hs | 4 ++-- src/Text/Pandoc/Slides.hs | 4 ++-- src/Text/Pandoc/Templates.hs | 4 ++-- src/Text/Pandoc/UTF8.hs | 4 ++-- src/Text/Pandoc/UUID.hs | 4 ++-- src/Text/Pandoc/XML.hs | 4 ++-- 19 files changed, 37 insertions(+), 37 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/pandoc.cabal b/pandoc.cabal index e91d007a9..08f1950b4 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -4,7 +4,7 @@ Cabal-Version: >= 1.10 Build-Type: Custom License: GPL License-File: COPYING -Copyright: (c) 2006-2015 John MacFarlane +Copyright: (c) 2006-2016 John MacFarlane Author: John MacFarlane Maintainer: John MacFarlane Bug-Reports: https://github.com/jgm/pandoc/issues diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index d59ee7846..b67a53f5b 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ScopedTypeVariables, FlexibleInstances #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Asciify.hs b/src/Text/Pandoc/Asciify.hs index c183458e4..8eb1ba663 100644 --- a/src/Text/Pandoc/Asciify.hs +++ b/src/Text/Pandoc/Asciify.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2013-2015 John MacFarlane +Copyright (C) 2013-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Asciify - Copyright : Copyright (C) 2013-2015 John MacFarlane + Copyright : Copyright (C) 2013-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index 0a4e08175..792098b35 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Module : Text.Pandoc.Error - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs index ecfef1832..1b9e92ae2 100644 --- a/src/Text/Pandoc/Highlighting.hs +++ b/src/Text/Pandoc/Highlighting.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2008-2015 John MacFarlane +Copyright (C) 2008-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Highlighting - Copyright : Copyright (C) 2008-2015 John MacFarlane + Copyright : Copyright (C) 2008-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index 571fdd665..90dfbb5fb 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings, ScopedTypeVariables, CPP #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} {- - Copyright (C) 2011-2015 John MacFarlane + Copyright (C) 2011-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ {- | Module : Text.Pandoc.ImageSize -Copyright : Copyright (C) 2011-2015 John MacFarlane +Copyright : Copyright (C) 2011-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs index 6fd9ac373..1164e04b3 100644 --- a/src/Text/Pandoc/MIME.hs +++ b/src/Text/Pandoc/MIME.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2011-2015 John MacFarlane +Copyright (C) 2011-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.MIME - Copyright : Copyright (C) 2011-2015 John MacFarlane + Copyright : Copyright (C) 2011-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index b5736c63d..171210962 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-} {- -Copyright (C) 2012-2015 John MacFarlane +Copyright (C) 2012-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Options - Copyright : Copyright (C) 2012-2015 John MacFarlane + Copyright : Copyright (C) 2012-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index da4ee4e33..4dbe1f000 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings, CPP, ScopedTypeVariables #-} {- -Copyright (C) 2012-2015 John MacFarlane +Copyright (C) 2012-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.PDF - Copyright : Copyright (C) 2012-2015 John MacFarlane + Copyright : Copyright (C) 2012-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 325231846..7bf827019 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -5,7 +5,7 @@ , MultiParamTypeClasses , FlexibleInstances #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -24,7 +24,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Parsing - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs index 88b7dd09e..f3ef0ef10 100644 --- a/src/Text/Pandoc/Pretty.hs +++ b/src/Text/Pandoc/Pretty.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GeneralizedNewtypeDeriving, CPP #-} {- -Copyright (C) 2010-2015 John MacFarlane +Copyright (C) 2010-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111(-1)307 USA {- | Module : Text.Pandoc.Pretty - Copyright : Copyright (C) 2010-2015 John MacFarlane + Copyright : Copyright (C) 2010-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Process.hs b/src/Text/Pandoc/Process.hs index e5245638d..bc71f1392 100644 --- a/src/Text/Pandoc/Process.hs +++ b/src/Text/Pandoc/Process.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2013-2015 John MacFarlane +Copyright (C) 2013-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Process - Copyright : Copyright (C) 2013-2015 John MacFarlane + Copyright : Copyright (C) 2013-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index 390a7a21a..d08d636df 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2011-2015 John MacFarlane +Copyright (C) 2011-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.SelfContained - Copyright : Copyright (C) 2011-2015 John MacFarlane + Copyright : Copyright (C) 2011-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 075d76847..d6b088338 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -2,7 +2,7 @@ FlexibleContexts, ScopedTypeVariables, PatternGuards, ViewPatterns #-} {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Shared - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Slides.hs b/src/Text/Pandoc/Slides.hs index 1a27ab5ac..e19dba3e2 100644 --- a/src/Text/Pandoc/Slides.hs +++ b/src/Text/Pandoc/Slides.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2012-2015 John MacFarlane +Copyright (C) 2012-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Slides - Copyright : Copyright (C) 2012-2015 John MacFarlane + Copyright : Copyright (C) 2012-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index a010433fa..925925872 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -1,7 +1,7 @@ {-# LANGUAGE TypeSynonymInstances, FlexibleInstances, CPP, OverloadedStrings, GeneralizedNewtypeDeriving #-} {- -Copyright (C) 2009-2015 John MacFarlane +Copyright (C) 2009-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Templates - Copyright : Copyright (C) 2009-2015 John MacFarlane + Copyright : Copyright (C) 2009-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs index de3314a0d..87ed5312b 100644 --- a/src/Text/Pandoc/UTF8.hs +++ b/src/Text/Pandoc/UTF8.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} {- -Copyright (C) 2010-2015 John MacFarlane +Copyright (C) 2010-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.UTF8 - Copyright : Copyright (C) 2010-2015 John MacFarlane + Copyright : Copyright (C) 2010-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/UUID.hs b/src/Text/Pandoc/UUID.hs index 463be044c..5d05fa303 100644 --- a/src/Text/Pandoc/UUID.hs +++ b/src/Text/Pandoc/UUID.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2010-2015 John MacFarlane +Copyright (C) 2010-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.UUID - Copyright : Copyright (C) 2010-2015 John MacFarlane + Copyright : Copyright (C) 2010-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane diff --git a/src/Text/Pandoc/XML.hs b/src/Text/Pandoc/XML.hs index 70d8efba6..4cc2141b4 100644 --- a/src/Text/Pandoc/XML.hs +++ b/src/Text/Pandoc/XML.hs @@ -1,5 +1,5 @@ {- -Copyright (C) 2006-2015 John MacFarlane +Copyright (C) 2006-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -18,7 +18,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.XML - Copyright : Copyright (C) 2006-2015 John MacFarlane + Copyright : Copyright (C) 2006-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane -- cgit v1.2.3 From bb6897a13ed8ec9fd2d15930bd013bc7b315120e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 24 Mar 2016 09:41:45 -0700 Subject: LaTeX writer: Fixed position of label in figures. Partially addresses #2813. This isn't perfect, because now the hypertarget is in the wrong place -- when you link to the figure, the screen is positioned with the caption at the top, and most of the figure off screen. So this needs a bit more tweaking. --- src/Text/Pandoc/Writers/LaTeX.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 0f47132b3..a63aca1c5 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -415,10 +415,10 @@ blockToLaTeX (Para [Image attr@(ident, _, _) txt (src,'f':'i':'g':':':tit)]) = d else brackets <$> inlineListToLaTeX (walk deNote txt) img <- inlineToLaTeX (Image attr txt (src,tit)) let footnotes = notesToLaTeX notes - figure <- refLabel ident $ cr <> + caption <- refLabel ident ("\\caption" <> captForLof <> braces capt) + let figure = cr <> "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$ - ("\\caption" <> captForLof <> braces capt) $$ - "\\end{figure}" <> cr + caption $$ "\\end{figure}" <> cr return $ if inNote -- can't have figures in notes then "\\begin{center}" $$ img $+$ capt $$ "\\end{center}" -- cgit v1.2.3 From f47b369f37484c153a1d12ca8049c384fb16929b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 24 Mar 2016 16:44:33 -0700 Subject: LaTeX writer: better positioning for hypertarget in figures. Closes #2813. --- src/Text/Pandoc/Writers/LaTeX.hs | 39 +++++++++++++++++++++++---------------- 1 file changed, 23 insertions(+), 16 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index a63aca1c5..dd5b14424 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -409,16 +409,20 @@ blockToLaTeX (Para [Image attr@(ident, _, _) txt (src,'f':'i':'g':':':tit)]) = d capt <- inlineListToLaTeX txt notes <- gets stNotes modify $ \st -> st{ stInMinipage = False, stNotes = [] } + ref <- text `fmap` toLabel ident + internalLinks <- gets stInternalLinks + -- We can't have footnotes in the list of figures, so remove them: captForLof <- if null notes then return empty else brackets <$> inlineListToLaTeX (walk deNote txt) img <- inlineToLaTeX (Image attr txt (src,tit)) let footnotes = notesToLaTeX notes - caption <- refLabel ident ("\\caption" <> captForLof <> braces capt) - let figure = cr <> + lab <- labelFor ident + let caption = "\\caption" <> captForLof <> braces capt <> lab + figure <- hypertarget ident (cr <> "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$ - caption $$ "\\end{figure}" <> cr + caption $$ "\\end{figure}" <> cr) return $ if inNote -- can't have figures in notes then "\\begin{center}" $$ img $+$ capt $$ "\\end{center}" @@ -755,7 +759,8 @@ sectionHeader unnumbered ident level lst = do -- needed for \paragraph, \subparagraph in quote environment -- see http://tex.stackexchange.com/questions/169830/ else empty - stuffing' <- refLabel ident $ text ('\\':sectionType) <> stuffing + lab <- labelFor ident + stuffing' <- hypertarget ident $ text ('\\':sectionType) <> stuffing <> lab return $ if level' > 5 then txt else prefix $$ stuffing' @@ -765,20 +770,22 @@ sectionHeader unnumbered ident level lst = do braces txtNoNotes else empty --- | Append label to x and wrap in hypertarget -refLabel :: String -> Doc -> State WriterState Doc -refLabel ident x = do +hypertarget :: String -> Doc -> State WriterState Doc +hypertarget ident x = do ref <- text `fmap` toLabel ident internalLinks <- gets stInternalLinks - let hypertarget y = if ident `elem` internalLinks - then text "\\hypertarget" - <> braces ref - <> braces y - else y - label = if null ident - then empty - else text "\\label" <> braces ref - return $ hypertarget $ x <> label + return $ + if ident `elem` internalLinks + then text "\\hypertarget" + <> braces ref + <> braces x + else x + +labelFor :: String -> State WriterState Doc +labelFor "" = return empty +labelFor ident = do + ref <- text `fmap` toLabel ident + return $ text "\\label" <> braces ref -- | Convert list of inline elements to LaTeX. inlineListToLaTeX :: [Inline] -- ^ Inlines to convert -- cgit v1.2.3 From 9742c486478e414b495670377923c44c840b9e01 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 25 Mar 2016 09:05:38 -0700 Subject: Removed two superfluous lines. --- src/Text/Pandoc/Writers/LaTeX.hs | 2 -- 1 file changed, 2 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index dd5b14424..693de93fa 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -409,8 +409,6 @@ blockToLaTeX (Para [Image attr@(ident, _, _) txt (src,'f':'i':'g':':':tit)]) = d capt <- inlineListToLaTeX txt notes <- gets stNotes modify $ \st -> st{ stInMinipage = False, stNotes = [] } - ref <- text `fmap` toLabel ident - internalLinks <- gets stInternalLinks -- We can't have footnotes in the list of figures, so remove them: captForLof <- if null notes -- cgit v1.2.3 From f74498cb47d360f58e5c28ad848c94197978cc6e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 26 Mar 2016 13:14:50 -0700 Subject: EPUB writer: set 'navpage' variable on nav page. This allows templates to treat it differently. --- src/Text/Pandoc/Writers/EPUB.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 804dbb926..90f502f6f 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -667,7 +667,8 @@ writeEPUB opts doc@(Pandoc meta _) = do ] ] else [] - let navData = renderHtml $ writeHtml opts' + let navData = renderHtml $ writeHtml + opts'{ writerVariables = ("navpage","true"):vars } (Pandoc (setMeta "title" (walk removeNote $ fromList $ docTitle' meta) nullMeta) (navBlocks ++ landmarks)) -- cgit v1.2.3 From 0c37a7c4881fd5018fd5b60588c9899b11bbb86a Mon Sep 17 00:00:00 2001 From: Andrew Dunning Date: Wed, 30 Mar 2016 14:15:47 +0100 Subject: Recognize `la-x-classic` as Classical Latin. This allows one to access the hyphenation patterns at , using its private language tag. --- src/Text/Pandoc/Writers/LaTeX.hs | 2 ++ 1 file changed, 2 insertions(+) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 693de93fa..9526333c1 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -1153,6 +1153,7 @@ toPolyglossia ("en":"UK":_) = ("english", "variant=british") toPolyglossia ("en":"US":_) = ("english", "variant=american") toPolyglossia ("grc":_) = ("greek", "variant=ancient") toPolyglossia ("hsb":_) = ("usorbian", "") +toPolyglossia ("la":"x-classic":_) = ("latin", "variant=classic") toPolyglossia ("sl":_) = ("slovenian", "") toPolyglossia x = (commonFromBcp47 x, "") @@ -1177,6 +1178,7 @@ toBabel ("fr":"CA":_) = "canadien" toBabel ("fra":"aca":_) = "acadian" toBabel ("grc":_) = "polutonikogreek" toBabel ("hsb":_) = "uppersorbian" +toBabel ("la":"x-classic":_) = "classiclatin" toBabel ("sl":_) = "slovene" toBabel x = commonFromBcp47 x -- cgit v1.2.3 From 9765ef2ce6abda60be0fa9f50571e752bd42009c Mon Sep 17 00:00:00 2001 From: Andrew Dunning Date: Thu, 31 Mar 2016 02:51:23 +0100 Subject: LaTeX writer: Add missing languages. Updates the list from the hyphenation files at . --- src/Text/Pandoc/Writers/LaTeX.hs | 24 +++++++++++++++++------- tests/writers-lang-and-dir.latex | 2 +- 2 files changed, 18 insertions(+), 8 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 9526333c1..1b3393853 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -1125,7 +1125,7 @@ toPolyglossiaEnv l = -- Takes a list of the constituents of a BCP 47 language code and -- converts it to a Polyglossia (language, options) tuple --- http://mirrors.concertpass.com/tex-archive/macros/latex/contrib/polyglossia/polyglossia.pdf +-- http://mirrors.ctan.org/macros/latex/contrib/polyglossia/polyglossia.pdf toPolyglossia :: [String] -> (String, String) toPolyglossia ("ar":"DZ":_) = ("arabic", "locale=algeria") toPolyglossia ("ar":"IQ":_) = ("arabic", "locale=mashriq") @@ -1153,18 +1153,21 @@ toPolyglossia ("en":"UK":_) = ("english", "variant=british") toPolyglossia ("en":"US":_) = ("english", "variant=american") toPolyglossia ("grc":_) = ("greek", "variant=ancient") toPolyglossia ("hsb":_) = ("usorbian", "") -toPolyglossia ("la":"x-classic":_) = ("latin", "variant=classic") +toPolyglossia ("la":"x":"classic":_) = ("latin", "variant=classic") toPolyglossia ("sl":_) = ("slovenian", "") toPolyglossia x = (commonFromBcp47 x, "") -- Takes a list of the constituents of a BCP 47 language code and -- converts it to a Babel language string. --- http://mirrors.concertpass.com/tex-archive/macros/latex/required/babel/base/babel.pdf --- Note that the PDF unfortunately does not contain a complete list of supported languages. +-- http://mirrors.ctan.org/macros/latex/required/babel/base/babel.pdf +-- List of supported languages (slightly outdated): +-- http://tug.ctan.org/language/hyph-utf8/doc/generic/hyph-utf8/hyphenation.pdf toBabel :: [String] -> String toBabel ("de":"1901":_) = "german" toBabel ("de":"AT":"1901":_) = "austrian" toBabel ("de":"AT":_) = "naustrian" +toBabel ("de":"CH":"1901":_) = "swissgerman" +toBabel ("de":"CH":_) = "nswissgerman" toBabel ("de":_) = "ngerman" toBabel ("dsb":_) = "lowersorbian" toBabel ("el":"polyton":_) = "polutonikogreek" @@ -1178,7 +1181,7 @@ toBabel ("fr":"CA":_) = "canadien" toBabel ("fra":"aca":_) = "acadian" toBabel ("grc":_) = "polutonikogreek" toBabel ("hsb":_) = "uppersorbian" -toBabel ("la":"x-classic":_) = "classiclatin" +toBabel ("la":"x":"classic":_) = "classiclatin" toBabel ("sl":_) = "slovene" toBabel x = commonFromBcp47 x @@ -1187,12 +1190,15 @@ toBabel x = commonFromBcp47 x -- https://tools.ietf.org/html/bcp47#section-2.1 commonFromBcp47 :: [String] -> String commonFromBcp47 [] = "" -commonFromBcp47 ("pt":"BR":_) = "brazilian" +commonFromBcp47 ("pt":"BR":_) = "brazilian" +commonFromBcp47 ("sr":"Cyrl":_) = "serbianc" +commonFromBcp47 ("zh":"Latn":"pinyin":_) = "pinyin" commonFromBcp47 x = fromIso $ head x where fromIso "af" = "afrikaans" fromIso "am" = "amharic" fromIso "ar" = "arabic" + fromIso "as" = "assamese" fromIso "ast" = "asturian" fromIso "bg" = "bulgarian" fromIso "bn" = "bengali" @@ -1216,12 +1222,13 @@ commonFromBcp47 x = fromIso $ head x fromIso "fur" = "friulan" fromIso "ga" = "irish" fromIso "gd" = "scottish" + fromIso "gez" = "ethiopic" fromIso "gl" = "galician" fromIso "he" = "hebrew" fromIso "hi" = "hindi" fromIso "hr" = "croatian" - fromIso "hy" = "armenian" fromIso "hu" = "magyar" + fromIso "hy" = "armenian" fromIso "ia" = "interlingua" fromIso "id" = "indonesian" fromIso "ie" = "interlingua" @@ -1229,6 +1236,7 @@ commonFromBcp47 x = fromIso $ head x fromIso "it" = "italian" fromIso "jp" = "japanese" fromIso "km" = "khmer" + fromIso "kmr" = "kurmanji" fromIso "kn" = "kannada" fromIso "ko" = "korean" fromIso "la" = "latin" @@ -1244,6 +1252,7 @@ commonFromBcp47 x = fromIso $ head x fromIso "no" = "norsk" fromIso "nqo" = "nko" fromIso "oc" = "occitan" + fromIso "pa" = "panjabi" fromIso "pl" = "polish" fromIso "pms" = "piedmontese" fromIso "pt" = "portuguese" @@ -1260,6 +1269,7 @@ commonFromBcp47 x = fromIso $ head x fromIso "ta" = "tamil" fromIso "te" = "telugu" fromIso "th" = "thai" + fromIso "ti" = "ethiopic" fromIso "tk" = "turkmen" fromIso "tr" = "turkish" fromIso "uk" = "ukrainian" diff --git a/tests/writers-lang-and-dir.latex b/tests/writers-lang-and-dir.latex index 056809a5e..dbe58ebf0 100644 --- a/tests/writers-lang-and-dir.latex +++ b/tests/writers-lang-and-dir.latex @@ -27,7 +27,7 @@ breaklinks=true} \urlstyle{same} % don't use monospace font for urls \ifnum 0\ifxetex 1\fi\ifluatex 1\fi=0 % if pdftex - \usepackage[shorthands=off,ngerman,british,ngerman,spanish,french,main=english]{babel} + \usepackage[shorthands=off,ngerman,british,nswissgerman,spanish,french,main=english]{babel} \newcommand{\textgerman}[2][]{\foreignlanguage{ngerman}{#2}} \newenvironment{german}[1]{\begin{otherlanguage}{ngerman}}{\end{otherlanguage}} \newcommand{\textenglish}[2][]{\foreignlanguage{british}{#2}} -- cgit v1.2.3 From 773bbb8fc73a3b6598188dbae64a841eb6680b38 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 10 Apr 2016 07:39:36 -0700 Subject: Markdown + HTML readers: be more forgiving about unescaped &. We are now more forgiving about parsing invalid HTML with unescaped `&` as raw HTML. (Previously any unescaped `&` would cause pandoc not to recognize the string as raw HTML.) Closes #2410. --- src/Text/Pandoc/Readers/HTML.hs | 25 +++++++++++++++---------- 1 file changed, 15 insertions(+), 10 deletions(-) (limited to 'src/Text/Pandoc') 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 + -- + -- should NOT be parsed as an HTML tag, see #2277 + guard $ not ('.' `elem` tagname) + -- 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 | "") | otherwise -> fail "bogus comment mode, HTML5 parse error" - _ -> do - -- we get a TagWarning on things like - -- - -- 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) -- cgit v1.2.3 From 4b49f923cbfd74287742f7d9634406580d48515b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 10 Apr 2016 09:13:53 -0700 Subject: Markdown reader: Fix pandoc title blocks with lines ending in 2 spaces. Closes #2799. Also added -s to markdown-reader-more test. --- src/Text/Pandoc/Readers/Markdown.hs | 42 ++++++++++++++++++++----------------- tests/Tests/Old.hs | 2 +- tests/markdown-reader-more.native | 4 ++-- 3 files changed, 26 insertions(+), 22 deletions(-) (limited to 'src/Text/Pandoc') 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/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/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"] -- cgit v1.2.3 From a385ee1d4fad05eb2cd45a9206182e90cd856012 Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Fri, 15 Apr 2016 14:09:18 -0400 Subject: Docx Reader: parse `moveTo` and `moveFrom` `moveTo` and `moveFrom` are track-changes tags that are used when a block of text is moved in the document. We now recognize these tags and treat them the same as `insert` and `delete`, respectively. So, `--track-changes=accept` will show the moved version, while `--track-changes=reject` will show the original version. --- src/Text/Pandoc/Readers/Docx/Parse.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc') 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 -- cgit v1.2.3 From 1bfe39e24cb58c361a05f419ef9a4a5263f558f6 Mon Sep 17 00:00:00 2001 From: Emanuel Evans Date: Sun, 24 Apr 2016 21:58:53 -0700 Subject: Ignore leading space in org code blocks Fixes #2862 Also fix up tab handling for leading whitespace in code blocks. --- src/Text/Pandoc/Readers/Org.hs | 24 ++++++++++++++++++++---- tests/Tests/Readers/Org.hs | 27 +++++++++++++++++++++++++++ 2 files changed, 47 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc') 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/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" -- cgit v1.2.3 From 1985164816e49386e256d53d2846c90dc4168fd5 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 26 Apr 2016 21:50:37 -0700 Subject: LaTeX writer: ignore --incremental unless -t beamer. Closes #2843. --- src/Text/Pandoc/Writers/LaTeX.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 9526333c1..5b3283573 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" -- cgit v1.2.3 From 32f1b0a5f14c93271aaf42acaa9d06c4e59c1604 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 27 Apr 2016 17:25:45 -0700 Subject: Revert "LaTeX writer: Add `\strut` to fix multiline tables" This reverts commit 4c684561ee0665b014e887ae559b7020e4e9f2d3. See https://groups.google.com/d/msg/pandoc-discuss/u6J-_aCProU/UufN3IYRAgAJ This should fix uneven spacing issues in multiline tables. --- src/Text/Pandoc/Writers/LaTeX.hs | 3 +- tests/tables.latex | 90 ++++++++++++++++++++-------------------- 2 files changed, 46 insertions(+), 47 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 948bbedaa..038f27480 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -669,8 +669,7 @@ tableCellToLaTeX header (width, align, blocks) = do AlignDefault -> "\\raggedright" return $ ("\\begin{minipage}" <> valign <> braces (text (printf "%.2f\\columnwidth" width)) <> - (halign <> "\\strut" <> cr <> cellContents <> cr) <> - "\\strut\\end{minipage}") $$ + (halign <> cr <> cellContents <> cr) <> "\\end{minipage}") $$ notesToLaTeX notes notesToLaTeX :: [Doc] -> Doc diff --git a/tests/tables.latex b/tests/tables.latex index 96cbc9579..9f3f97e53 100644 --- a/tests/tables.latex +++ b/tests/tables.latex @@ -52,47 +52,47 @@ Multiline table with caption: \begin{longtable}[]{@{}clrl@{}} \caption{Here's the caption. It may span multiple lines.}\tabularnewline \toprule -\begin{minipage}[b]{0.13\columnwidth}\centering\strut +\begin{minipage}[b]{0.13\columnwidth}\centering Centered Header -\strut\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright Left Aligned -\strut\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft\strut +\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft Right Aligned -\strut\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright Default aligned -\strut\end{minipage}\tabularnewline +\end{minipage}\tabularnewline \midrule \endfirsthead \toprule -\begin{minipage}[b]{0.13\columnwidth}\centering\strut +\begin{minipage}[b]{0.13\columnwidth}\centering Centered Header -\strut\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright Left Aligned -\strut\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft\strut +\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft Right Aligned -\strut\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright Default aligned -\strut\end{minipage}\tabularnewline +\end{minipage}\tabularnewline \midrule \endhead -\begin{minipage}[t]{0.13\columnwidth}\centering\strut +\begin{minipage}[t]{0.13\columnwidth}\centering First -\strut\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright row -\strut\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut +\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 12.0 -\strut\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright Example of a row that spans multiple lines. -\strut\end{minipage}\tabularnewline -\begin{minipage}[t]{0.13\columnwidth}\centering\strut +\end{minipage}\tabularnewline +\begin{minipage}[t]{0.13\columnwidth}\centering Second -\strut\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright row -\strut\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut +\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 5.0 -\strut\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright Here's another one. Note the blank line between rows. -\strut\end{minipage}\tabularnewline +\end{minipage}\tabularnewline \bottomrule \end{longtable} @@ -100,35 +100,35 @@ Multiline table without caption: \begin{longtable}[]{@{}clrl@{}} \toprule -\begin{minipage}[b]{0.13\columnwidth}\centering\strut +\begin{minipage}[b]{0.13\columnwidth}\centering Centered Header -\strut\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright Left Aligned -\strut\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft\strut +\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft Right Aligned -\strut\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright Default aligned -\strut\end{minipage}\tabularnewline +\end{minipage}\tabularnewline \midrule \endhead -\begin{minipage}[t]{0.13\columnwidth}\centering\strut +\begin{minipage}[t]{0.13\columnwidth}\centering First -\strut\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright row -\strut\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut +\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 12.0 -\strut\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright Example of a row that spans multiple lines. -\strut\end{minipage}\tabularnewline -\begin{minipage}[t]{0.13\columnwidth}\centering\strut +\end{minipage}\tabularnewline +\begin{minipage}[t]{0.13\columnwidth}\centering Second -\strut\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright row -\strut\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut +\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 5.0 -\strut\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright Here's another one. Note the blank line between rows. -\strut\end{minipage}\tabularnewline +\end{minipage}\tabularnewline \bottomrule \end{longtable} @@ -146,23 +146,23 @@ Multiline table without column headers: \begin{longtable}[]{@{}clrl@{}} \toprule -\begin{minipage}[t]{0.13\columnwidth}\centering\strut +\begin{minipage}[t]{0.13\columnwidth}\centering First -\strut\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright row -\strut\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut +\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 12.0 -\strut\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright Example of a row that spans multiple lines. -\strut\end{minipage}\tabularnewline -\begin{minipage}[t]{0.13\columnwidth}\centering\strut +\end{minipage}\tabularnewline +\begin{minipage}[t]{0.13\columnwidth}\centering Second -\strut\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright row -\strut\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut +\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft 5.0 -\strut\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut +\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright Here's another one. Note the blank line between rows. -\strut\end{minipage}\tabularnewline +\end{minipage}\tabularnewline \bottomrule \end{longtable} -- cgit v1.2.3 From 271cb4d8457b2252cddc76a476f3681e8b2a1486 Mon Sep 17 00:00:00 2001 From: Ivo Clarysse Date: Fri, 29 Apr 2016 14:00:46 -0700 Subject: Add docbook5 writer support --- src/Text/Pandoc.hs | 2 + src/Text/Pandoc/Options.hs | 2 + src/Text/Pandoc/Writers/Docbook.hs | 10 +- tests/Tests/Old.hs | 3 + tests/tables.docbook5 | 432 +++++++++++ tests/writer.docbook5 | 1394 ++++++++++++++++++++++++++++++++++++ 6 files changed, 1840 insertions(+), 3 deletions(-) create mode 100644 tests/tables.docbook5 create mode 100644 tests/writer.docbook5 (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index b67a53f5b..58f666939 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -291,6 +291,8 @@ writers = [ writeHtmlString o{ writerSlideVariant = RevealJsSlides , writerHtml5 = True }) ,("docbook" , PureStringWriter writeDocbook) + ,("docbook5" , PureStringWriter $ \o -> + writeDocbook o{ writerDocBook5 = True }) ,("opml" , PureStringWriter writeOPML) ,("opendocument" , PureStringWriter writeOpenDocument) ,("latex" , PureStringWriter writeLaTeX) diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 171210962..fcf6537c0 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -357,6 +357,7 @@ data WriterOptions = WriterOptions , writerSourceURL :: Maybe String -- ^ Absolute URL + directory of 1st source file , writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory , writerCiteMethod :: CiteMethod -- ^ How to print cites + , writerDocBook5 :: Bool -- ^ Produce DocBook5 , writerHtml5 :: Bool -- ^ Produce HTML5 , writerHtmlQTags :: Bool -- ^ Use @@ tags for quotes in HTML , writerBeamer :: Bool -- ^ Produce beamer LaTeX slide show @@ -403,6 +404,7 @@ instance Default WriterOptions where , writerSourceURL = Nothing , writerUserDataDir = Nothing , writerCiteMethod = Citeproc + , writerDocBook5 = False , writerHtml5 = False , writerHtmlQTags = False , writerBeamer = False diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 2aaebf99f..5528714a2 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -112,7 +112,9 @@ elementToDocbook opts lvl (Sec _ _num (id',_,_) title elements) = else elements tag = case lvl of n | n == 0 -> "chapter" - | n >= 1 && n <= 5 -> "sect" ++ show n + | n >= 1 && n <= 5 -> if writerDocBook5 opts + then "section" + else "sect" ++ show n | otherwise -> "simplesect" in inTags True tag [("id", writerIdentifierPrefix opts ++ id') | not (null id')] $ @@ -227,9 +229,11 @@ blockToDocbook opts (OrderedList (start, numstyle, _) (first:rest)) = blockToDocbook opts (DefinitionList lst) = let attribs = [("spacing", "compact") | isTightList $ concatMap snd lst] in inTags True "variablelist" attribs $ deflistItemsToDocbook opts lst -blockToDocbook _ (RawBlock f str) +blockToDocbook opts (RawBlock f str) | f == "docbook" = text str -- raw XML block - | f == "html" = text str -- allow html for backwards compatibility + | f == "html" = if writerDocBook5 opts + then empty -- No html in Docbook5 + else text str -- allow html for backwards compatibility | otherwise = empty blockToDocbook _ HorizontalRule = empty -- not semantic blockToDocbook opts (Table caption aligns widths headers rows) = diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index b292b1f11..4e0eb46a4 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -108,6 +108,9 @@ tests = [ testGroup "markdown" , test "reader" ["-r", "docbook", "-w", "native", "-s"] "docbook-xref.docbook" "docbook-xref.native" ] + , testGroup "docbook5" + [ testGroup "writer" $ writerTests "docbook5" + ] , testGroup "native" [ testGroup "writer" $ writerTests "native" , test "reader" ["-r", "native", "-w", "native", "-s"] diff --git a/tests/tables.docbook5 b/tests/tables.docbook5 new file mode 100644 index 000000000..6224cf222 --- /dev/null +++ b/tests/tables.docbook5 @@ -0,0 +1,432 @@ + + Simple table with caption: + + + + Demonstration of simple table syntax. + + + + + + + + + + Right + + + Left + + + Center + + + Default + + + + + + + 12 + + + 12 + + + 12 + + + 12 + + + + + 123 + + + 123 + + + 123 + + + 123 + + + + + 1 + + + 1 + + + 1 + + + 1 + + + + +
+ + Simple table without caption: + + + + + + + + + + + Right + + + Left + + + Center + + + Default + + + + + + + 12 + + + 12 + + + 12 + + + 12 + + + + + 123 + + + 123 + + + 123 + + + 123 + + + + + 1 + + + 1 + + + 1 + + + 1 + + + + + + + Simple table indented two spaces: + + + + Demonstration of simple table syntax. + + + + + + + + + + Right + + + Left + + + Center + + + Default + + + + + + + 12 + + + 12 + + + 12 + + + 12 + + + + + 123 + + + 123 + + + 123 + + + 123 + + + + + 1 + + + 1 + + + 1 + + + 1 + + + + +
+ + Multiline table with caption: + + + + Here's the caption. It may span multiple lines. + + + + + + + + + + Centered Header + + + Left Aligned + + + Right Aligned + + + Default aligned + + + + + + + First + + + row + + + 12.0 + + + Example of a row that spans multiple lines. + + + + + Second + + + row + + + 5.0 + + + Here's another one. Note the blank line between rows. + + + + +
+ + Multiline table without caption: + + + + + + + + + + + Centered Header + + + Left Aligned + + + Right Aligned + + + Default aligned + + + + + + + First + + + row + + + 12.0 + + + Example of a row that spans multiple lines. + + + + + Second + + + row + + + 5.0 + + + Here's another one. Note the blank line between rows. + + + + + + + Table without column headers: + + + + + + + + + + + 12 + + + 12 + + + 12 + + + 12 + + + + + 123 + + + 123 + + + 123 + + + 123 + + + + + 1 + + + 1 + + + 1 + + + 1 + + + + + + + Multiline table without column headers: + + + + + + + + + + + First + + + row + + + 12.0 + + + Example of a row that spans multiple lines. + + + + + Second + + + row + + + 5.0 + + + Here's another one. Note the blank line between rows. + + + + + diff --git a/tests/writer.docbook5 b/tests/writer.docbook5 new file mode 100644 index 000000000..494489ab5 --- /dev/null +++ b/tests/writer.docbook5 @@ -0,0 +1,1394 @@ + + +
+ + Pandoc Test Suite + + + John + MacFarlane + + + + Anonymous + + + July 17, 2006 + + + This is a set of tests for pandoc. Most of them are adapted from John + Gruber’s markdown test suite. + +
+ Headers + +
+
+ Level 1 +
+ Level 2 with <emphasis>emphasis</emphasis> +
+ Level 3 + + with no blank line + +
+
+
+ Level 2 + + with no blank line + +
+
+
+ Paragraphs + + Here’s a regular paragraph. + + + In Markdown 1.0.0 and earlier. Version 8. This line turns into a list + item. Because a hard-wrapped line in the middle of a paragraph looked like + a list item. + + + Here’s one with a bullet. * criminey. + +There should be a hard line break +here. +
+
+ Block Quotes + + E-mail style: + +
+ + This is a block quote. It is pretty short. + +
+
+ + Code in a block quote: + + +sub status { + print "working"; +} + + + A list: + + + + + item one + + + + + item two + + + + + Nested block quotes: + +
+ + nested + +
+
+ + nested + +
+
+ + This should not be a block quote: 2 > 1. + + + And a following paragraph. + +
+
+ Code Blocks + + Code: + + +---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab + + + And: + + + this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{ + +
+
+ Lists +
+ Unordered + + Asterisks tight: + + + + + asterisk 1 + + + + + asterisk 2 + + + + + asterisk 3 + + + + + Asterisks loose: + + + + + asterisk 1 + + + + + asterisk 2 + + + + + asterisk 3 + + + + + Pluses tight: + + + + + Plus 1 + + + + + Plus 2 + + + + + Plus 3 + + + + + Pluses loose: + + + + + Plus 1 + + + + + Plus 2 + + + + + Plus 3 + + + + + Minuses tight: + + + + + Minus 1 + + + + + Minus 2 + + + + + Minus 3 + + + + + Minuses loose: + + + + + Minus 1 + + + + + Minus 2 + + + + + Minus 3 + + + +
+
+ Ordered + + Tight: + + + + + First + + + + + Second + + + + + Third + + + + + and: + + + + + One + + + + + Two + + + + + Three + + + + + Loose using tabs: + + + + + First + + + + + Second + + + + + Third + + + + + and using spaces: + + + + + One + + + + + Two + + + + + Three + + + + + Multiple paragraphs: + + + + + Item 1, graf one. + + + Item 1. graf two. The quick brown fox jumped over the lazy dog’s + back. + + + + + Item 2. + + + + + Item 3. + + + +
+
+ Nested + + + + Tab + + + + + Tab + + + + + Tab + + + + + + + + + Here’s another: + + + + + First + + + + + Second: + + + + + Fee + + + + + Fie + + + + + Foe + + + + + + + Third + + + + + Same thing but with paragraphs: + + + + + First + + + + + Second: + + + + + Fee + + + + + Fie + + + + + Foe + + + + + + + Third + + + +
+
+ Tabs and spaces + + + + this is a list item indented with tabs + + + + + this is a list item indented with spaces + + + + + this is an example list item indented with tabs + + + + + this is an example list item indented with spaces + + + + + +
+
+ Fancy list markers + + + + begins with 2 + + + + + and now 3 + + + with a continuation + + + + + sublist with roman numerals, starting with 4 + + + + + more items + + + + + a subsublist + + + + + a subsublist + + + + + + + + + Nesting: + + + + + Upper Alpha + + + + + Upper Roman. + + + + + Decimal start with 6 + + + + + Lower alpha with paren + + + + + + + + + + + Autonumbering: + + + + + Autonumber. + + + + + More. + + + + + Nested. + + + + + + + Should not be a list item: + + + M.A. 2007 + + + B. Williams + +
+
+
+ Definition Lists + + Tight using spaces: + + + + + apple + + + + red fruit + + + + + + orange + + + + orange fruit + + + + + + banana + + + + yellow fruit + + + + + + Tight using tabs: + + + + + apple + + + + red fruit + + + + + + orange + + + + orange fruit + + + + + + banana + + + + yellow fruit + + + + + + Loose: + + + + + apple + + + + red fruit + + + + + + orange + + + + orange fruit + + + + + + banana + + + + yellow fruit + + + + + + Multiple blocks with italics: + + + + + apple + + + + red fruit + + + contains seeds, crisp, pleasant to taste + + + + + + orange + + + + orange fruit + + +{ orange code block } + +
+ + orange block quote + +
+
+
+
+ + Multiple definitions, tight: + + + + + apple + + + + red fruit + + + computer + + + + + + orange + + + + orange fruit + + + bank + + + + + + Multiple definitions, loose: + + + + + apple + + + + red fruit + + + computer + + + + + + orange + + + + orange fruit + + + bank + + + + + + Blank line after term, indented marker, alternate markers: + + + + + apple + + + + red fruit + + + computer + + + + + + orange + + + + orange fruit + + + + + sublist + + + + + sublist + + + + + + +
+
+ HTML Blocks + + Simple block on one line: + + + foo + + + And nested without indentation: + + + foo + + + bar + + + Interpreted markdown in a table: + + This is emphasized + And this is strong + + Here’s a simple block: + + + foo + + + This should be a code block, though: + + +<div> + foo +</div> + + + As should this: + + +<div>foo</div> + + + Now, nested: + + + foo + + + This should just be an HTML comment: + + + Multiline: + + + Code block: + + +<!-- Comment --> + + + Just plain comment, with trailing spaces on the line: + + + Code: + + +<hr /> + + + Hr’s: + +
+
+ Inline Markup + + This is emphasized, and so is + this. + + + This is strong, and so + is this. + + + An emphasized link. + + + This is strong and + em. + + + So is this word. + + + This is strong and + em. + + + So is this word. + + + This is code: >, $, + \, \$, + <html>. + + + This is + strikeout. + + + Superscripts: abcd + ahello + ahello there. + + + Subscripts: H2O, H23O, + Hmany of themO. + + + These should not be superscripts or subscripts, because of the unescaped + spaces: a^b c^d, a~b c~d. + +
+
+ Smart quotes, ellipses, dashes + + Hello, said the spider. Shelob is my + name. + + + A, B, and C are letters. + + + Oak, elm, and beech are names + of trees. So is pine. + + + He said, I want to go. Were you alive in the + 70’s? + + + Here is some quoted code and a + quoted + link. + + + Some dashes: one—two — three—four — five. + + + Dashes between numbers: 5–7, 255–66, 1987–1999. + + + Ellipses…and…and…. + +
+
+ LaTeX + + + + + + + + 2 + 2 = 4 + + + + + x ∈ y + + + + + α ∧ ω + + + + + 223 + + + + + p-Tree + + + + + Here’s some display math: + $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ + + + + + Here’s one that has a line break in it: + α + ω × x2. + + + + + These shouldn’t be math: + + + + + To get the famous equation, write $e = mc^2$. + + + + + $22,000 is a lot of money. So is $34,000. (It + worked if lot is emphasized.) + + + + + Shoes ($20) and socks ($5). + + + + + Escaped $: $73 this should be + emphasized 23$. + + + + + Here’s a LaTeX table: + +
+
+ Special Characters + + Here is some unicode: + + + + + I hat: Î + + + + + o umlaut: ö + + + + + section: § + + + + + set membership: ∈ + + + + + copyright: © + + + + + AT&T has an ampersand in their name. + + + AT&T is another way to write it. + + + This & that. + + + 4 < 5. + + + 6 > 5. + + + Backslash: \ + + + Backtick: ` + + + Asterisk: * + + + Underscore: _ + + + Left brace: { + + + Right brace: } + + + Left bracket: [ + + + Right bracket: ] + + + Left paren: ( + + + Right paren: ) + + + Greater-than: > + + + Hash: # + + + Period: . + + + Bang: ! + + + Plus: + + + + Minus: - + +
+ +
+ Images + + From Voyage dans la Lune by Georges Melies (1902): + +
+ lalune + + + + + lalune + +
+ + Here is a movie + + + + icon. + +
+
+ Footnotes + + Here is a footnote reference, + + Here is the footnote. It can go anywhere after the footnote reference. + It need not be placed at the end of the document. + + and another. + + Here’s the long note. This one contains multiple blocks. + + + Subsequent blocks are indented to show that they belong to the + footnote (as with list items). + + + { <code> } + + + If you want, you can indent every line, but you can also be lazy and + just indent the first line of each block. + + This should not be a footnote reference, + because it contains a space.[^my note] Here is an inline note. + + This is easier to type. Inline notes may contain + links and ] + verbatim characters, as well as [bracketed text]. + + + +
+ + Notes can go in quotes. + + In quote. + + + +
+ + + + And in list items. + + In list. + + + + + + + This paragraph should not be part of the note, as it is not indented. + +
+
-- cgit v1.2.3 From aa4a1d527a3ecbc291a70a872f06fa7a525d8e39 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 29 Apr 2016 14:54:54 -0700 Subject: HTML writer: ensure mathjax link is added when math appears in footnote. Previously if a document only had math in a footnote, the MathJax link would not be added. Closes #2881. --- src/Text/Pandoc/Writers/HTML.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index c5b6a6db2..d8b8384e7 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -855,13 +855,12 @@ inlineToHtml opts inline = (Note contents) | writerIgnoreNotes opts -> return mempty | otherwise -> do - st <- get - let notes = stNotes st + notes <- gets stNotes let number = (length notes) + 1 let ref = show number htmlContents <- blockListToNote opts ref contents -- push contents onto front of notes - put $ st {stNotes = (htmlContents:notes)} + modify $ \st -> st {stNotes = (htmlContents:notes)} let revealSlash = ['/' | writerSlideVariant opts == RevealJsSlides] let link = H.a ! A.href (toValue $ "#" ++ -- cgit v1.2.3 From 987ec3a7523f4fe529575004d76d93680f127fa3 Mon Sep 17 00:00:00 2001 From: Ivo Clarysse Date: Fri, 29 Apr 2016 15:43:15 -0700 Subject: Write out Docbook 5 namespace --- src/Text/Pandoc.hs | 2 +- src/Text/Pandoc/Options.hs | 4 ++-- src/Text/Pandoc/Writers/Docbook.hs | 11 +++++++---- 3 files changed, 10 insertions(+), 7 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 58f666939..0330c46e2 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -292,7 +292,7 @@ writers = [ , writerHtml5 = True }) ,("docbook" , PureStringWriter writeDocbook) ,("docbook5" , PureStringWriter $ \o -> - writeDocbook o{ writerDocBook5 = True }) + writeDocbook o{ writerDocbook5 = True }) ,("opml" , PureStringWriter writeOPML) ,("opendocument" , PureStringWriter writeOpenDocument) ,("latex" , PureStringWriter writeLaTeX) diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index fcf6537c0..701cd8bd1 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -357,7 +357,7 @@ data WriterOptions = WriterOptions , writerSourceURL :: Maybe String -- ^ Absolute URL + directory of 1st source file , writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory , writerCiteMethod :: CiteMethod -- ^ How to print cites - , writerDocBook5 :: Bool -- ^ Produce DocBook5 + , writerDocbook5 :: Bool -- ^ Produce DocBook5 , writerHtml5 :: Bool -- ^ Produce HTML5 , writerHtmlQTags :: Bool -- ^ Use @@ tags for quotes in HTML , writerBeamer :: Bool -- ^ Produce beamer LaTeX slide show @@ -404,7 +404,7 @@ instance Default WriterOptions where , writerSourceURL = Nothing , writerUserDataDir = Nothing , writerCiteMethod = Citeproc - , writerDocBook5 = False + , writerDocbook5 = False , writerHtml5 = False , writerHtmlQTags = False , writerBeamer = False diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 5528714a2..79ccde9af 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -112,12 +112,15 @@ elementToDocbook opts lvl (Sec _ _num (id',_,_) title elements) = else elements tag = case lvl of n | n == 0 -> "chapter" - | n >= 1 && n <= 5 -> if writerDocBook5 opts + | n >= 1 && n <= 5 -> if writerDocbook5 opts then "section" else "sect" ++ show n | otherwise -> "simplesect" - in inTags True tag [("id", writerIdentifierPrefix opts ++ id') | - not (null id')] $ + idAttr = [("id", writerIdentifierPrefix opts ++ id') | not (null id')] + nsAttr = if writerDocbook5 opts && lvl == 0 then [("xmlns", "http://docbook.org/ns/docbook")] + else [] + attribs = nsAttr ++ idAttr + in inTags True tag attribs $ inTagsSimple "title" (inlinesToDocbook opts title) $$ vcat (map (elementToDocbook opts (lvl + 1)) elements') @@ -231,7 +234,7 @@ blockToDocbook opts (DefinitionList lst) = in inTags True "variablelist" attribs $ deflistItemsToDocbook opts lst blockToDocbook opts (RawBlock f str) | f == "docbook" = text str -- raw XML block - | f == "html" = if writerDocBook5 opts + | f == "html" = if writerDocbook5 opts then empty -- No html in Docbook5 else text str -- allow html for backwards compatibility | otherwise = empty -- cgit v1.2.3 From fd36e6b64a516ffd281af0667afc6d9c00a70d64 Mon Sep 17 00:00:00 2001 From: Ivo Clarysse Date: Fri, 29 Apr 2016 16:06:55 -0700 Subject: Docbook5 writer: Properly handle ulink/link --- src/Text/Pandoc/Writers/Docbook.hs | 4 ++- tests/writer.docbook5 | 67 +++++++++++++++++++------------------- 2 files changed, 37 insertions(+), 34 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 79ccde9af..9acfe289a 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -351,7 +351,9 @@ inlineToDocbook opts (Link attr txt (src, _)) | otherwise = (if isPrefixOf "#" src then inTags False "link" $ ("linkend", drop 1 src) : idAndRole attr - else inTags False "ulink" $ ("url", src) : idAndRole attr ) $ + else if writerDocbook5 opts + then inTags False "link" $ ("xlink:href", src) : idAndRole attr + else inTags False "ulink" $ ("url", src) : idAndRole attr ) $ inlinesToDocbook opts txt inlineToDocbook opts (Image attr _ (src, tit)) = let titleDoc = if null tit diff --git a/tests/writer.docbook5 b/tests/writer.docbook5 index 494489ab5..5261a35be 100644 --- a/tests/writer.docbook5 +++ b/tests/writer.docbook5 @@ -22,7 +22,8 @@
Headers