diff options
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 144 | ||||
-rw-r--r-- | tests/tables.context | 2 | ||||
-rw-r--r-- | tests/writer.context | 167 |
3 files changed, 151 insertions, 162 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index a3a30f0a0..8e0387a84 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2007-2010 John MacFarlane <jgm@berkeley.edu> @@ -31,9 +32,9 @@ module Text.Pandoc.Writers.ConTeXt ( writeConTeXt ) where import Text.Pandoc.Definition import Text.Pandoc.Shared import Text.Printf ( printf ) -import Data.List ( isSuffixOf, intercalate, intersperse ) +import Data.List ( intercalate ) import Control.Monad.State -import Text.PrettyPrint.HughesPJ hiding ( Str ) +import Text.Pandoc.Pretty import Text.Pandoc.Templates ( renderTemplate ) data WriterState = @@ -56,15 +57,18 @@ writeConTeXt options document = pandocToConTeXt :: WriterOptions -> Pandoc -> State WriterState String pandocToConTeXt options (Pandoc (Meta title authors date) blocks) = do + let colwidth = if writerWrapText options + then Just $ writerColumns options + else Nothing titletext <- if null title then return "" - else liftM render $ inlineListToConTeXt title - authorstext <- mapM (liftM render . inlineListToConTeXt) authors + else liftM (render colwidth) $ inlineListToConTeXt title + authorstext <- mapM (liftM (render colwidth) . inlineListToConTeXt) authors datetext <- if null date then return "" - else liftM render $ inlineListToConTeXt date - body <- blockListToConTeXt blocks - let main = render $ body $$ text "" + else liftM (render colwidth) $ inlineListToConTeXt date + body <- blockListToConTeXt blocks + let main = render colwidth $ body let context = writerVariables options ++ [ ("toc", if writerTableOfContents options then "yes" else "") , ("body", main) @@ -104,32 +108,26 @@ stringToConTeXt = concatMap escapeCharForConTeXt -- | Convert Pandoc block element to ConTeXt. blockToConTeXt :: Block - -> State WriterState BlockWrapper -blockToConTeXt Null = return $ Reg empty -blockToConTeXt (Plain lst) = do - st <- get - let options = stOptions st - contents <- wrapTeXIfNeeded options False inlineListToConTeXt lst - return $ Reg contents + -> State WriterState Doc +blockToConTeXt Null = return empty +blockToConTeXt (Plain lst) = inlineListToConTeXt lst blockToConTeXt (Para [Image txt (src,_)]) = do capt <- inlineListToConTeXt txt - return $ Pad $ text "\\placefigure[here,nonumber]{" <> capt <> - text "}{\\externalfigure[" <> text src <> text "]}" + return $ blankline $$ "\\placefigure[here,nonumber]" <> braces capt <> + braces ("\\externalfigure" <> brackets (text src)) <> blankline blockToConTeXt (Para lst) = do - st <- get - let options = stOptions st - contents <- wrapTeXIfNeeded options False inlineListToConTeXt lst - return $ Pad contents + contents <- inlineListToConTeXt lst + return $ contents <> blankline blockToConTeXt (BlockQuote lst) = do contents <- blockListToConTeXt lst - return $ Pad $ text "\\startblockquote" $$ contents $$ text "\\stopblockquote" -blockToConTeXt (CodeBlock _ str) = - return $ Reg $ text $ "\\starttyping\n" ++ str ++ "\n\\stoptyping\n" - -- \n because \stoptyping can't have anything after it, inc. } -blockToConTeXt (RawHtml _) = return $ Reg empty -blockToConTeXt (BulletList lst) = do + return $ "\\startblockquote" $$ nest 0 contents $$ "\\stopblockquote" <> blankline +blockToConTeXt (CodeBlock _ str) = + return $ "\\starttyping" <> cr <> flush (text str) <> cr <> "\\stoptyping" <> blankline + -- blankline because \stoptyping can't have anything after it, inc. '}' +blockToConTeXt (RawHtml _) = return empty +blockToConTeXt (BulletList lst) = do contents <- mapM listItemToConTeXt lst - return $ Pad $ text "\\startitemize" $$ vcat contents $$ text "\\stopitemize" + return $ "\\startitemize" $$ vcat contents $$ text "\\stopitemize" <> blankline blockToConTeXt (OrderedList (start, style', delim) lst) = do st <- get let level = stOrderedListLevel st @@ -161,20 +159,20 @@ blockToConTeXt (OrderedList (start, style', delim) lst) = do LowerAlpha -> "[a]" UpperAlpha -> "[A]" let specs = style'' ++ specs2 - return $ Pad $ text ("\\startitemize" ++ specs) $$ vcat contents $$ - text "\\stopitemize" + return $ "\\startitemize" <> text specs $$ vcat contents $$ + "\\stopitemize" <> blankline blockToConTeXt (DefinitionList lst) = - mapM defListItemToConTeXt lst >>= return . Pad . wrappedBlocksToDoc -blockToConTeXt HorizontalRule = return $ Pad $ text "\\thinrule" + liftM vcat $ mapM defListItemToConTeXt lst +blockToConTeXt HorizontalRule = return $ "\\thinrule" <> blankline blockToConTeXt (Header level lst) = do contents <- inlineListToConTeXt lst st <- get let opts = stOptions st let base = if writerNumberSections opts then "section" else "subject" - return $ Pad $ if level >= 1 && level <= 5 - then char '\\' <> text (concat (replicate (level - 1) "sub")) <> - text base <> char '{' <> contents <> char '}' - else contents + return $ if level >= 1 && level <= 5 + then char '\\' <> text (concat (replicate (level - 1) "sub")) <> + text base <> char '{' <> contents <> char '}' <> blankline + else contents <> blankline blockToConTeXt (Table caption aligns widths heads rows) = do let colDescriptor colWidth alignment = (case alignment of AlignLeft -> 'l' @@ -188,80 +186,83 @@ blockToConTeXt (Table caption aligns widths heads rows) = do zipWith colDescriptor widths aligns) headers <- if all null heads then return empty - else liftM ($$ text "\\HL") $ tableRowToConTeXt heads + else liftM ($$ "\\HL") $ tableRowToConTeXt heads captionText <- inlineListToConTeXt caption let captionText' = if null caption then text "none" else captionText rows' <- mapM tableRowToConTeXt rows - return $ Pad $ text "\\placetable[here]{" <> captionText' <> char '}' $$ - text "\\starttable[" <> text colDescriptors <> char ']' $$ - text "\\HL" $$ headers $$ - vcat rows' $$ text "\\HL\n\\stoptable" + return $ "\\placetable[here]" <> braces captionText' $$ + "\\starttable" <> brackets (text colDescriptors) $$ + "\\HL" $$ headers $$ + vcat rows' $$ "\\HL" $$ "\\stoptable" <> blankline tableRowToConTeXt :: [[Block]] -> State WriterState Doc tableRowToConTeXt cols = do cols' <- mapM blockListToConTeXt cols - return $ (vcat (map (text "\\NC " <>) cols')) $$ - text "\\NC\\AR" + return $ (vcat (map ("\\NC " <>) cols')) $$ "\\NC\\AR" listItemToConTeXt :: [Block] -> State WriterState Doc listItemToConTeXt list = blockListToConTeXt list >>= - return . (text "\\item" $$) . (nest 2) + return . ("\\item" $$) . (nest 2) -defListItemToConTeXt :: ([Inline], [[Block]]) -> State WriterState BlockWrapper +defListItemToConTeXt :: ([Inline], [[Block]]) -> State WriterState Doc defListItemToConTeXt (term, defs) = do term' <- inlineListToConTeXt term - def' <- liftM (vcat . intersperse (text "")) $ mapM blockListToConTeXt defs - return $ Pad $ text "\\startdescr{" <> term' <> char '}' $$ def' $$ text "\\stopdescr" + def' <- liftM vsep $ mapM blockListToConTeXt defs + return $ "\\startdescr" <> braces term' $$ nest 2 def' $$ + "\\stopdescr" <> blankline -- | Convert list of block elements to ConTeXt. blockListToConTeXt :: [Block] -> State WriterState Doc -blockListToConTeXt lst = mapM blockToConTeXt lst >>= return . wrappedBlocksToDoc +blockListToConTeXt lst = liftM vcat $ mapM blockToConTeXt lst -- | Convert list of inline elements to ConTeXt. inlineListToConTeXt :: [Inline] -- ^ Inlines to convert -> State WriterState Doc -inlineListToConTeXt lst = mapM inlineToConTeXt lst >>= return . hcat +inlineListToConTeXt lst = liftM hcat $ mapM inlineToConTeXt lst -- | Convert inline element to ConTeXt inlineToConTeXt :: Inline -- ^ Inline to convert -> State WriterState Doc inlineToConTeXt (Emph lst) = do contents <- inlineListToConTeXt lst - return $ text "{\\em " <> contents <> char '}' + return $ braces $ "\\em " <> contents inlineToConTeXt (Strong lst) = do contents <- inlineListToConTeXt lst - return $ text "{\\bf " <> contents <> char '}' + return $ braces $ "\\bf " <> contents inlineToConTeXt (Strikeout lst) = do contents <- inlineListToConTeXt lst - return $ text "\\overstrikes{" <> contents <> char '}' + return $ "\\overstrikes" <> braces contents inlineToConTeXt (Superscript lst) = do contents <- inlineListToConTeXt lst - return $ text "\\high{" <> contents <> char '}' + return $ "\\high" <> braces contents inlineToConTeXt (Subscript lst) = do contents <- inlineListToConTeXt lst - return $ text "\\low{" <> contents <> char '}' + return $ "\\low" <> braces contents inlineToConTeXt (SmallCaps lst) = do contents <- inlineListToConTeXt lst - return $ text "{\\sc " <> contents <> char '}' -inlineToConTeXt (Code str) = return $ text $ "\\type{" ++ str ++ "}" + return $ braces $ "\\sc " <> contents +inlineToConTeXt (Code str) = + return $ "\\type" <> braces (text str) inlineToConTeXt (Quoted SingleQuote lst) = do contents <- inlineListToConTeXt lst - return $ text "\\quote{" <> contents <> char '}' + return $ "\\quote" <> braces contents inlineToConTeXt (Quoted DoubleQuote lst) = do contents <- inlineListToConTeXt lst - return $ text "\\quotation{" <> contents <> char '}' + return $ "\\quotation" <> braces contents inlineToConTeXt (Cite _ lst) = inlineListToConTeXt lst inlineToConTeXt Apostrophe = return $ char '\'' -inlineToConTeXt EmDash = return $ text "---" -inlineToConTeXt EnDash = return $ text "--" -inlineToConTeXt Ellipses = return $ text "\\ldots{}" +inlineToConTeXt EmDash = return "---" +inlineToConTeXt EnDash = return "--" +inlineToConTeXt Ellipses = return "\\ldots{}" inlineToConTeXt (Str str) = return $ text $ stringToConTeXt str -inlineToConTeXt (Math InlineMath str) = return $ char '$' <> text str <> char '$' -inlineToConTeXt (Math DisplayMath str) = return $ text "\\startformula " <> text str <> text " \\stopformula" +inlineToConTeXt (Math InlineMath str) = + return $ char '$' <> text str <> char '$' +inlineToConTeXt (Math DisplayMath str) = + return $ text "\\startformula " <> text str <> text " \\stopformula" inlineToConTeXt (TeX str) = return $ text str inlineToConTeXt (HtmlInline _) = return empty -inlineToConTeXt (LineBreak) = return $ text "\\crlf\n" -inlineToConTeXt Space = return $ char ' ' +inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr +inlineToConTeXt Space = return space inlineToConTeXt (Link [Code str] (src, tit)) = -- since ConTeXt has its own inlineToConTeXt (Link [Str str] (src, tit)) -- way of printing links... inlineToConTeXt (Link txt (src, _)) = do @@ -270,15 +271,12 @@ inlineToConTeXt (Link txt (src, _)) = do put $ st {stNextRef = next + 1} let ref = show next label <- inlineListToConTeXt txt - return $ text "\\useURL[" <> text ref <> text "][" <> text src <> - text "][][" <> label <> text "]\\from[" <> text ref <> char ']' + return $ "\\useURL" <> brackets (text ref) <> brackets (text src) <> + brackets empty <> brackets label <> + "\\from" <> brackets (text ref) inlineToConTeXt (Image _ (src, _)) = do - return $ text "{\\externalfigure[" <> text src <> text "]}" + return $ braces $ "\\externalfigure" <> brackets (text src) inlineToConTeXt (Note contents) = do contents' <- blockListToConTeXt contents - let rawnote = stripTrailingNewlines $ render contents' - -- note: a \n before } is needed when note ends with a \stoptyping - let optNewline = "\\stoptyping" `isSuffixOf` rawnote - return $ text "\\footnote{" <> - text rawnote <> (if optNewline then char '\n' else empty) <> char '}' - + return $ text "\\footnote{" <> + nest 2 contents' <> char '}' <> cr diff --git a/tests/tables.context b/tests/tables.context index 20f7ceedb..a280cc285 100644 --- a/tests/tables.context +++ b/tests/tables.context @@ -172,4 +172,4 @@ Multiline table without column headers: \NC Here's another one. Note the blank line between rows. \NC\AR \HL -\stoptable +\stoptable
\ No newline at end of file diff --git a/tests/writer.context b/tests/writer.context index e8fc17114..2a47f9f23 100644 --- a/tests/writer.context +++ b/tests/writer.context @@ -61,8 +61,8 @@ after={\blank[medium]}, \blank[3*medium] \stopalignment -This is a set of tests for pandoc. Most of them are adapted from -John Gruber's markdown test suite. +This is a set of tests for pandoc. Most of them are adapted from John Gruber's +markdown test suite. \thinrule @@ -94,9 +94,9 @@ with no blank line 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. +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. @@ -293,9 +293,8 @@ Multiple paragraphs: \startitemize[n][stopper=.] \item Item 1, graf one. - - Item 1. graf two. The quick brown fox jumped over the lazy dog's - back. + + Item 1. graf two. The quick brown fox jumped over the lazy dog's back. \item Item 2. \item @@ -343,7 +342,7 @@ Same thing but with paragraphs: First \item Second: - + \startitemize \item Fee @@ -363,7 +362,7 @@ Same thing but with paragraphs: this is a list item indented with tabs \item this is a list item indented with spaces - + \startitemize \item this is an example list item indented with tabs @@ -379,9 +378,9 @@ Same thing but with paragraphs: begins with 2 \item and now 3 - + with a continuation - + \startitemize[r][start=4,stopper=.,width=2.0em] \item sublist with roman numerals, starting with 4 @@ -441,110 +440,110 @@ B. Williams Tight using spaces: \startdescr{apple} -red fruit + red fruit \stopdescr \startdescr{orange} -orange fruit + orange fruit \stopdescr \startdescr{banana} -yellow fruit + yellow fruit \stopdescr Tight using tabs: \startdescr{apple} -red fruit + red fruit \stopdescr \startdescr{orange} -orange fruit + orange fruit \stopdescr \startdescr{banana} -yellow fruit + yellow fruit \stopdescr Loose: \startdescr{apple} -red fruit + red fruit \stopdescr \startdescr{orange} -orange fruit + orange fruit \stopdescr \startdescr{banana} -yellow fruit + yellow fruit \stopdescr Multiple blocks with italics: \startdescr{{\em apple}} -red fruit + red fruit -contains seeds, crisp, pleasant to taste + contains seeds, crisp, pleasant to taste \stopdescr \startdescr{{\em orange}} -orange fruit + orange fruit -\starttyping + \starttyping { orange code block } -\stoptyping + \stoptyping -\startblockquote -orange block quote -\stopblockquote + \startblockquote + orange block quote + \stopblockquote \stopdescr Multiple definitions, tight: \startdescr{apple} -red fruit + red fruit -computer + computer \stopdescr \startdescr{orange} -orange fruit + orange fruit -bank + bank \stopdescr Multiple definitions, loose: \startdescr{apple} -red fruit + red fruit -computer + computer \stopdescr \startdescr{orange} -orange fruit + orange fruit -bank + bank \stopdescr Blank line after term, indented marker, alternate markers: \startdescr{apple} -red fruit + red fruit -computer + computer \stopdescr \startdescr{orange} -orange fruit + orange fruit -\startitemize[n][stopper=.] -\item - sublist -\item - sublist -\stopitemize + \startitemize[n][stopper=.] + \item + sublist + \item + sublist + \stopitemize \stopdescr \subject{HTML Blocks} @@ -618,8 +617,7 @@ So is {\bf {\em this}} word. So is {\bf {\em this}} word. -This is code: \type{>}, \type{$}, \type{\}, \type{\$}, -\type{<html>}. +This is code: \type{>}, \type{$}, \type{\}, \type{\$}, \type{<html>}. \overstrikes{This is {\em strikeout}.} @@ -627,27 +625,25 @@ Superscripts: a\high{bc}d a\high{{\em hello}} a\high{hello~there}. Subscripts: H\low{2}O, H\low{23}O, H\low{many~of~them}O. -These should not be superscripts or subscripts, because of the -unescaped spaces: a\letterhat{}b c\letterhat{}d, a\lettertilde{}b -c\lettertilde{}d. +These should not be superscripts or subscripts, because of the unescaped +spaces: a\letterhat{}b c\letterhat{}d, a\lettertilde{}b c\lettertilde{}d. \thinrule \subject{Smart quotes, ellipses, dashes} -\quotation{Hello,} said the spider. -\quotation{\quote{Shelob} is my name.} +\quotation{Hello,} said the spider. \quotation{\quote{Shelob} is my name.} \quote{A}, \quote{B}, and \quote{C} are letters. -\quote{Oak,} \quote{elm,} and \quote{beech} are names of trees. So -is \quote{pine.} +\quote{Oak,} \quote{elm,} and \quote{beech} are names of trees. So is +\quote{pine.} -\quote{He said, \quotation{I want to go.}} Were you alive in the -70's? +\quote{He said, \quotation{I want to go.}} Were you alive in the 70's? Here is some quoted \quote{\type{code}} and a -\quotation{\useURL[3][http://example.com/?foo=1&bar=2][][quoted link]\from[3]}. +\quotation{\useURL[3][http://example.com/?foo=1&bar=2][][quoted +link]\from[3]}. Some dashes: one---two --- three---four --- five. @@ -676,8 +672,7 @@ Ellipses\ldots{}and\ldots{}and\ldots{}. Here's some display math: \startformula \frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h} \stopformula \item - Here's one that has a line break in it: - $\alpha + \omega \times x^2$. + Here's one that has a line break in it: $\alpha + \omega \times x^2$. \stopitemize These shouldn't be math: @@ -817,16 +812,16 @@ Foo \useURL[22][/url/][][biz]\from[22]. \subsubject{With ampersands} -Here's a -\useURL[23][http://example.com/?foo=1&bar=2][][link with an ampersand in the URL]\from[23]. +Here's a \useURL[23][http://example.com/?foo=1&bar=2][][link with an ampersand +in the URL]\from[23]. Here's a link with an amersand in the link text: \useURL[24][http://att.com/][][AT\&T]\from[24]. Here's an \useURL[25][/script?foo=1&bar=2][][inline link]\from[25]. -Here's an -\useURL[26][/script?foo=1&bar=2][][inline link in pointy braces]\from[26]. +Here's an \useURL[26][/script?foo=1&bar=2][][inline link in pointy +braces]\from[26]. \subsubject{Autolinks} @@ -846,8 +841,7 @@ An e-mail address: \useURL[29][mailto:nobody@nowhere.net][][nobody@nowhere.net]\from[29] \startblockquote -Blockquoted: -\useURL[30][http://example.com/][][http://example.com/]\from[30] +Blockquoted: \useURL[30][http://example.com/][][http://example.com/]\from[30] \stopblockquote Auto-links should not occur here: \type{<http://example.com/>} @@ -870,39 +864,36 @@ Here is a movie {\externalfigure[movie.jpg]} icon. \subject{Footnotes} -Here is a footnote reference, -\footnote{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. -\footnote{Here's the long note. This one contains multiple blocks. +Here is a footnote reference,\footnote{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.\footnote{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). + Subsequent blocks are indented to show that they belong to the footnote (as + with list items). -\starttyping + \starttyping { <code> } -\stoptyping + \stoptyping -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 {\em not} be a footnote reference, because it contains -a space.{[}\letterhat{}my note{]} Here is an inline note. -\footnote{This is {\em easier} to type. Inline notes may contain -\useURL[31][http://google.com][][links]\from[31] and \type{]} -verbatim characters, as well as {[}bracketed text{]}.} + 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 {\em not} be a footnote reference, because it contains a +space.{[}\letterhat{}my note{]} Here is an inline note.\footnote{This is + {\em easier} to type. Inline notes may contain + \useURL[31][http://google.com][][links]\from[31] and \type{]} verbatim + characters, as well as {[}bracketed text{]}.} \startblockquote -Notes can go in quotes. -\footnote{In quote.} +Notes can go in quotes.\footnote{In quote.} \stopblockquote \startitemize[n][stopper=.] \item - And in list items. - \footnote{In list.} + And in list items.\footnote{In list.} \stopitemize -This paragraph should not be part of the note, as it is not -indented. +This paragraph should not be part of the note, as it is not indented. \stoptext |