diff options
-rw-r--r-- | MANUAL.txt | 43 | ||||
-rw-r--r-- | changelog | 65 | ||||
-rw-r--r-- | man/pandoc.1 | 52 | ||||
-rw-r--r-- | pandoc.cabal | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/ImageSize.hs | 7 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Creole.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 14 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/FB2.hs | 32 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/JATS.hs | 55 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 18 | ||||
-rw-r--r-- | test/Tests/Readers/Creole.hs | 15 | ||||
-rw-r--r-- | test/Tests/Writers/FB2.hs | 34 | ||||
-rw-r--r-- | test/command/3596.md | 6 | ||||
-rw-r--r-- | test/command/4012.md | 8 | ||||
-rw-r--r-- | test/command/4016.md | 47 | ||||
-rw-r--r-- | test/command/4019.md | 8 | ||||
-rw-r--r-- | test/command/latex-command-comment.md | 7 | ||||
-rw-r--r-- | test/test-pandoc.hs | 2 | ||||
-rw-r--r-- | test/writer.fb2 | 90 | ||||
-rw-r--r-- | test/writer.jats | 12 |
23 files changed, 375 insertions, 166 deletions
diff --git a/MANUAL.txt b/MANUAL.txt index fc33b3433..5a89dda0d 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -1,6 +1,6 @@ % Pandoc User's Guide % John MacFarlane -% October 27, 2017 +% October 31, 2017 Synopsis ======== @@ -206,7 +206,7 @@ the LaTeX engine requires [`fontspec`]. `xelatex` uses `dir` variable set). If the `mathspec` variable is set, `xelatex` will use [`mathspec`] instead of [`unicode-math`]. The [`upquote`] and [`microtype`] packages are used if -available, and [`csquotes`] will be used for [smart punctuation] +available, and [`csquotes`] will be used for [typography] if added to the template or included in any header file. The [`natbib`], [`biblatex`], [`bibtex`], and [`biber`] packages can optionally be used for [citation rendering]. These are included @@ -2888,16 +2888,20 @@ Attributes can be attached to verbatim text, just as with ### Small caps ### -To write small caps, you can use an HTML span tag: +To write small caps, use the `smallcaps` class: - <span style="font-variant:small-caps;">Small caps</span> + [Small caps]{.smallcaps} + +Or, without the `bracketed_spans` extension: -(The semicolon is optional and there may be space after the -colon.) This will work in all output formats that support small caps. + <span class="smallcaps">Small caps</span> + +For compatibility with other Markdown flavors, CSS is also supported: + + <span style="font-variant:small-caps;">Small caps</span> -Alternatively, you can also use the new `bracketed_spans` syntax: +This will work in all output formats that support small caps. - [Small caps]{style="font-variant:small-caps;"} Math ---- @@ -3082,7 +3086,7 @@ starts with a fence containing at least three consecutive colons plus some attributes. The attributes may optionally be followed by another string of consecutive colons. The attribute syntax is exactly as in fenced code blocks (see -[Extension-fenced_code_attributes], above). As with fenced +[Extension: `fenced_code_attributes`]). As with fenced code blocks, one can use either attributes in curly braces or a single unbraced word, which will be treated as a class name. The Div ends with another line containing a string of at @@ -4042,18 +4046,35 @@ Speaker notes reveal.js has good support for speaker notes. You can add notes to your Markdown document thus: - <div class="notes"> + ::: notes + This is my note. - It can contain Markdown - like this list - </div> + ::: To show the notes window, press `s` while viewing the presentation. Notes are not yet supported for other slide formats, but the notes will not appear on the slides themselves. +Columns +------- + +To put material in side by side columns, you can use a native +div container with class `columns`, containing two or more div +containers with class `column` and a `width` attribute: + + :::::::::::::: {.columns} + ::: {.column width="40%"} + contents... + ::: + ::: {.column width="60%"} + contents... + ::: + :::::::::::::: + Frame attributes in beamer -------------------------- @@ -1,3 +1,52 @@ +pandoc (2.0.1) + + * Fixed regression in parsing of HTML comments in markdown and other + non-HTML formats (`Text.Pandoc.Readers.HTML.htmlTag`) (#4019). + The parser stopped at the first `>` character, even if it wasn't + the end of the comment. + + * Creole reader (Sascha Wilde): + + + Fix some minor typos and formatting. + + Add additional test on nowiki-block after para. + + Fix lists with trailing white space. + + * LaTeX reader: handle `%` comment right after command. + For example, `\emph%`. + + * Markdown reader: make sure fenced div closers work in lists. + Previously the following failed: + + ::: {.class} + 1. one + 2. two + ::: + + and you needed a blank line before the closing `:::`. + + * Make `fenced_divs` affect the Markdown writer. If `fenced_divs` is + enabled, Divs will be rendered as fenced divs. + + * LaTeX/Beamer writer: support "blocks" inside columns and other Divs + (#4016). + + * JATS writer: Properly pass through author metadata (#4020). + + * FB2 writer: write blocks outside of `<p>` in definitions + (Alexander Krotov). + + * `Text.Pandoc.ImageSize`: Add `Millimeter` constructor to `Dimension` + (#4012) [API change]. Now sizes given in 'mm' are no longer converted + to 'cm'. + + * Revise documentation of small caps syntax (Andrew Dunning, #4013). + + * Fix broken reference links in manual (Andrew Dunning, #4014) + + * Fixed example of slide columns structure in changelog (#4015). + Also documented this feature in MANUAL.txt. + + pandoc (2.0.0.1) * EPUB writer: @@ -75,14 +124,14 @@ pandoc (2.0) * Implement multicolumn support for slide formats (#1710). The structure expected is: - <div class="columns"> - <div class="column" width="40%"> - contents... - </div> - <div class="column" width="60%"> - contents... - </div> - </div> + :::::::::::::: {.columns} + ::: {.column width="40%"} + contents... + ::: + ::: {.column width="60%"} + contents... + ::: + :::::::::::::: Support has been added for beamer and all HTML slide formats. diff --git a/man/pandoc.1 b/man/pandoc.1 index ccabf76d7..9d0d20128 100644 --- a/man/pandoc.1 +++ b/man/pandoc.1 @@ -1,5 +1,5 @@ .\"t -.TH PANDOC 1 "October 27, 2017" "pandoc 2.0" +.TH PANDOC 1 "October 31, 2017" "pandoc 2.0.1" .SH NAME pandoc - general markup converter .SH SYNOPSIS @@ -200,8 +200,8 @@ requires \f[C]fontspec\f[]. If the \f[C]mathspec\f[] variable is set, \f[C]xelatex\f[] will use \f[C]mathspec\f[] instead of \f[C]unicode\-math\f[]. The \f[C]upquote\f[] and \f[C]microtype\f[] packages are used if -available, and \f[C]csquotes\f[] will be used for [smart punctuation] if -added to the template or included in any header file. +available, and \f[C]csquotes\f[] will be used for typography if added to +the template or included in any header file. The \f[C]natbib\f[], \f[C]biblatex\f[], \f[C]bibtex\f[], and \f[C]biber\f[] packages can optionally be used for citation rendering. These are included with all recent versions of TeX Live. @@ -3572,24 +3572,31 @@ blocks: .fi .SS Small caps .PP -To write small caps, you can use an HTML span tag: +To write small caps, use the \f[C]smallcaps\f[] class: .IP .nf \f[C] -<span\ style="font\-variant:small\-caps;">Small\ caps</span> +[Small\ caps]{.smallcaps} \f[] .fi .PP -(The semicolon is optional and there may be space after the colon.) This -will work in all output formats that support small caps. +Or, without the \f[C]bracketed_spans\f[] extension: +.IP +.nf +\f[C] +<span\ class="smallcaps">Small\ caps</span> +\f[] +.fi .PP -Alternatively, you can also use the new \f[C]bracketed_spans\f[] syntax: +For compatibility with other Markdown flavors, CSS is also supported: .IP .nf \f[C] -[Small\ caps]{style="font\-variant:small\-caps;"} +<span\ style="font\-variant:small\-caps;">Small\ caps</span> \f[] .fi +.PP +This will work in all output formats that support small caps. .SS Math .SS Extension: \f[C]tex_math_dollars\f[] .PP @@ -3814,8 +3821,8 @@ A Div starts with a fence containing at least three consecutive colons plus some attributes. The attributes may optionally be followed by another string of consecutive colons. -The attribute syntax is exactly as in fenced code blocks (see -[Extension\-fenced_code_attributes], above). +The attribute syntax is exactly as in fenced code blocks (see Extension: +\f[C]fenced_code_attributes\f[]). As with fenced code blocks, one can use either attributes in curly braces or a single unbraced word, which will be treated as a class name. The Div ends with another line containing a string of at least three @@ -5023,13 +5030,14 @@ You can add notes to your Markdown document thus: .IP .nf \f[C] -<div\ class="notes"> +:::\ notes + This\ is\ my\ note. \-\ It\ can\ contain\ Markdown \-\ like\ this\ list -</div> +::: \f[] .fi .PP @@ -5037,6 +5045,24 @@ To show the notes window, press \f[C]s\f[] while viewing the presentation. Notes are not yet supported for other slide formats, but the notes will not appear on the slides themselves. +.SS Columns +.PP +To put material in side by side columns, you can use a native div +container with class \f[C]columns\f[], containing two or more div +containers with class \f[C]column\f[] and a \f[C]width\f[] attribute: +.IP +.nf +\f[C] +::::::::::::::\ {.columns} +:::\ {.column\ width="40%"} +contents... +::: +:::\ {.column\ width="60%"} +contents... +::: +:::::::::::::: +\f[] +.fi .SS Frame attributes in beamer .PP Sometimes it is necessary to add the LaTeX \f[C][fragile]\f[] option to diff --git a/pandoc.cabal b/pandoc.cabal index f95851dc6..92dd44b9e 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -1,5 +1,5 @@ name: pandoc -version: 2.0.0.1 +version: 2.0.1 cabal-version: >= 1.10 build-type: Custom license: GPL @@ -596,6 +596,7 @@ test-suite test-pandoc Tests.Writers.RST Tests.Writers.TEI Tests.Writers.Muse + Tests.Writers.FB2 ghc-options: -rtsopts -Wall -fno-warn-unused-do-bind -threaded default-language: Haskell98 diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index 27d5c6a9c..5f491e08b 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -79,6 +79,7 @@ instance Show Direction where data Dimension = Pixel Integer | Centimeter Double + | Millimeter Double | Inch Double | Percent Double | Em Double @@ -86,6 +87,7 @@ data Dimension = Pixel Integer instance Show Dimension where show (Pixel a) = show a ++ "px" show (Centimeter a) = showFl a ++ "cm" + show (Millimeter a) = showFl a ++ "mm" show (Inch a) = showFl a ++ "in" show (Percent a) = show a ++ "%" show (Em a) = showFl a ++ "em" @@ -184,6 +186,7 @@ inInch opts dim = case dim of (Pixel a) -> fromIntegral a / fromIntegral (writerDpi opts) (Centimeter a) -> a * 0.3937007874 + (Millimeter a) -> a * 0.03937007874 (Inch a) -> a (Percent _) -> 0 (Em a) -> a * (11/64) @@ -193,6 +196,7 @@ inPixel opts dim = case dim of (Pixel a) -> a (Centimeter a) -> floor $ dpi * a * 0.3937007874 :: Integer + (Millimeter a) -> floor $ dpi * a * 0.03937007874 :: Integer (Inch a) -> floor $ dpi * a :: Integer (Percent _) -> 0 (Em a) -> floor $ dpi * a * (11/64) :: Integer @@ -225,6 +229,7 @@ scaleDimension factor dim = case dim of Pixel x -> Pixel (round $ factor * fromIntegral x) Centimeter x -> Centimeter (factor * x) + Millimeter x -> Millimeter (factor * x) Inch x -> Inch (factor * x) Percent x -> Percent (factor * x) Em x -> Em (factor * x) @@ -243,7 +248,7 @@ lengthToDim :: String -> Maybe Dimension lengthToDim s = numUnit s >>= uncurry toDim where toDim a "cm" = Just $ Centimeter a - toDim a "mm" = Just $ Centimeter (a / 10) + toDim a "mm" = Just $ Millimeter a toDim a "in" = Just $ Inch a toDim a "inch" = Just $ Inch a toDim a "%" = Just $ Percent a diff --git a/src/Text/Pandoc/Readers/Creole.hs b/src/Text/Pandoc/Readers/Creole.hs index 4da259c0e..b4eb6eaef 100644 --- a/src/Text/Pandoc/Readers/Creole.hs +++ b/src/Text/Pandoc/Readers/Creole.hs @@ -27,7 +27,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA License : GNU GPL, version 2 or above Maintainer : Sascha Wilde <wilde@sha-bang.de> - Stability : WIP + Stability : alpha Portability : portable Conversion of creole text to 'Pandoc' document. @@ -64,7 +64,7 @@ readCreole opts s = do type CRLParser = ParserT [Char] ParserState -- --- Utility funcitons +-- Utility functions -- (<+>) :: (Monad m, Monoid a) => m a -> m a -> m a @@ -111,7 +111,8 @@ block = do return res nowiki :: PandocMonad m => CRLParser m B.Blocks -nowiki = try $ fmap (B.codeBlock . mconcat) (nowikiStart >> manyTill content nowikiEnd) +nowiki = try $ fmap (B.codeBlock . mconcat) (nowikiStart + >> manyTill content nowikiEnd) where content = brackets <|> line brackets = try $ option "" ((:[]) <$> newline) @@ -154,7 +155,8 @@ listItem :: PandocMonad m => Char -> Int -> CRLParser m B.Blocks listItem c n = fmap (B.plain . B.trimInlines .mconcat) (listStart >> many1Till inline itemEnd) where - listStart = try $ optional newline >> skipSpaces >> count n (char c) + listStart = try $ skipSpaces >> optional newline >> skipSpaces + >> count n (char c) >> lookAhead (noneOf [c]) >> skipSpaces itemEnd = endOfParaElement <|> nextItem n <|> if n < 3 then nextItem (n+1) @@ -193,7 +195,7 @@ endOfParaElement = lookAhead $ endOfInput <|> endOfPara startOf :: PandocMonad m => CRLParser m a -> CRLParser m () startOf p = try $ blankline >> p >> return mempty startOfList = startOf $ anyList 1 - startOfTable =startOf table + startOfTable = startOf table startOfHeader = startOf header startOfNowiki = startOf nowiki hr = startOf horizontalRule diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 8d37deb26..915fa852f 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -1172,8 +1172,9 @@ htmlTag f = try $ do case next of TagComment s | "<!--" `isPrefixOf` inp -> do - char '<' - manyTill anyChar endAngle + string "<!--" + count (length s) anyChar + string "-->" stripComments <- getOption readerStripComments if stripComments then return (next, "") diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index a982029af..9bac3d3a7 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1132,7 +1132,7 @@ inlineCommand' = try $ do lookupListDefault raw names inlineCommands tok :: PandocMonad m => LP m Inlines -tok = grouped inline <|> inlineCommand' <|> singleChar' +tok = try $ spaces >> grouped inline <|> inlineCommand' <|> singleChar' where singleChar' = do Tok _ _ t <- singleChar return (str (T.unpack t)) diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 2a88b39ec..98552e65d 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -846,6 +846,7 @@ listLine continuationIndent = try $ do skipMany spaceChar listStart) notFollowedByHtmlCloser + notFollowedByDivCloser optional (() <$ gobbleSpaces continuationIndent) listLineCommon @@ -883,16 +884,24 @@ listContinuation continuationIndent = try $ do x <- try $ do notFollowedBy blankline notFollowedByHtmlCloser + notFollowedByDivCloser gobbleSpaces continuationIndent anyLineNewline xs <- many $ try $ do notFollowedBy blankline notFollowedByHtmlCloser + notFollowedByDivCloser gobbleSpaces continuationIndent <|> notFollowedBy' listStart anyLineNewline blanks <- many blankline return $ concat (x:xs) ++ blanks +notFollowedByDivCloser :: PandocMonad m => MarkdownParser m () +notFollowedByDivCloser = do + guardDisabled Ext_fenced_divs <|> + do divLevel <- stateFencedDivLevel <$> getState + guard (divLevel < 1) <|> notFollowedBy divFenceEnd + notFollowedByHtmlCloser :: PandocMonad m => MarkdownParser m () notFollowedByHtmlCloser = do inHtmlBlock <- stateInHtmlBlock <$> getState @@ -965,6 +974,7 @@ defRawBlock compact = try $ do let dline = try ( do notFollowedBy blankline notFollowedByHtmlCloser + notFollowedByDivCloser if compact -- laziness not compatible with compact then () <$ indentSpaces else (() <$ indentSpaces) @@ -1688,10 +1698,8 @@ endline = try $ do guardEnabled Ext_blank_before_header <|> (notFollowedBy . char =<< atxChar) -- atx header guardDisabled Ext_backtick_code_blocks <|> notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced)) - guardDisabled Ext_fenced_divs <|> - do divLevel <- stateFencedDivLevel <$> getState - guard (divLevel < 1) <|> notFollowedBy divFenceEnd notFollowedByHtmlCloser + notFollowedByDivCloser (eof >> return mempty) <|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak)) <|> (guardEnabled Ext_ignore_line_breaks >> return mempty) diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index cf96393ca..666b67e52 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -64,7 +64,6 @@ data FbRenderState = FbRenderState { footnotes :: [ (Int, String, [Content]) ] -- ^ #, ID, text , imagesToFetch :: [ (String, String) ] -- ^ filename, URL or path , parentListMarker :: String -- ^ list marker of the parent ordered list - , parentBulletLevel :: Int -- ^ nesting level of the unordered list , writerOptions :: WriterOptions } deriving (Show) @@ -73,7 +72,7 @@ type FBM m = StateT FbRenderState m newFB :: FbRenderState newFB = FbRenderState { footnotes = [], imagesToFetch = [] - , parentListMarker = "", parentBulletLevel = 0 + , parentListMarker = "" , writerOptions = def } data ImageMode = NormalImage | InlineImage deriving (Eq) @@ -347,32 +346,21 @@ blockToXml (OrderedList a bss) = do concat <$> zipWithM mkitem markers bss blockToXml (BulletList bss) = do state <- get - let level = parentBulletLevel state let pmrk = parentListMarker state - let prefix = replicate (length pmrk) ' ' - let bullets = ["\x2022", "\x25e6", "*", "\x2043", "\x2023"] - let mrk = prefix ++ bullets !! (level `mod` length bullets) + let mrk = pmrk ++ "•" let mkitem bs = do - modify (\s -> s { parentBulletLevel = level+1 }) + modify (\s -> s { parentListMarker = mrk ++ " "}) item <- cMapM blockToXml $ plainToPara $ indentBlocks (mrk ++ " ") bs - modify (\s -> s { parentBulletLevel = level }) -- restore bullet level + modify (\s -> s { parentListMarker = pmrk }) -- old parent marker return item cMapM mkitem bss blockToXml (DefinitionList defs) = cMapM mkdef defs where mkdef (term, bss) = do - def' <- cMapM (cMapM blockToXml . sep . paraToPlain . map indent) bss + items <- cMapM (cMapM blockToXml . plainToPara . indentBlocks (replicate 4 ' ')) bss t <- wrap "strong" term - return [ el "p" t, el "p" def' ] - sep blocks = - if all needsBreak blocks then - blocks ++ [Plain [LineBreak]] - else - blocks - needsBreak (Para _) = False - needsBreak (Plain ins) = LineBreak `notElem` ins - needsBreak _ = True + return (el "p" t : items) blockToXml h@Header{} = do -- should not occur after hierarchicalize, except inside lists/blockquotes report $ BlockNotRendered h @@ -403,14 +391,6 @@ blockToXml (Table caption aligns _ headers rows) = do align_str AlignDefault = "left" blockToXml Null = return [] --- Replace paragraphs with plain text and line break. --- Necessary to simulate multi-paragraph lists in FB2. -paraToPlain :: [Block] -> [Block] -paraToPlain [] = [] -paraToPlain (Para inlines : rest) = - Plain inlines : Plain [LineBreak] : paraToPlain rest -paraToPlain (p:rest) = p : paraToPlain rest - -- Replace plain text with paragraphs and add line break after paragraphs. -- It is used to convert plain text from tight list items to paragraphs. plainToPara :: [Block] -> [Block] diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 2aac777c6..0ac37efba 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -37,7 +37,6 @@ import Data.Generics (everywhere, mkT) import Data.List (isSuffixOf, partition) import Data.Maybe (fromMaybe) import Data.Text (Text) -import qualified Text.Pandoc.Builder as B import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Definition import Text.Pandoc.Highlighting (languages, languagesByExtension) @@ -56,38 +55,14 @@ import qualified Text.XML.Light as Xml data JATSVersion = JATS1_1 deriving (Eq, Show) -type DB = ReaderT JATSVersion - --- | Convert list of authors to a docbook <author> section -authorToJATS :: PandocMonad m => WriterOptions -> [Inline] -> DB m B.Inlines -authorToJATS opts name' = do - name <- render Nothing <$> inlinesToJATS opts name' - let colwidth = if writerWrapText opts == WrapAuto - then Just $ writerColumns opts - else Nothing - return $ B.rawInline "docbook" $ render colwidth $ - if ',' `elem` name - then -- last name first - let (lastname, rest) = break (==',') name - firstname = triml rest in - inTagsSimple "firstname" (text $ escapeStringForXML firstname) <> - inTagsSimple "surname" (text $ escapeStringForXML lastname) - else -- last name last - let namewords = words name - lengthname = length namewords - (firstname, lastname) = case lengthname of - 0 -> ("","") - 1 -> ("", name) - n -> (unwords (take (n-1) namewords), last namewords) - in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$ - inTagsSimple "surname" (text $ escapeStringForXML lastname) +type JATS = ReaderT JATSVersion writeJATS :: PandocMonad m => WriterOptions -> Pandoc -> m Text writeJATS opts d = runReaderT (docToJATS opts d) JATS1_1 -- | Convert Pandoc document to string in JATS format. -docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> DB m Text +docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> JATS m Text docToJATS opts (Pandoc meta blocks) = do let isBackBlock (Div ("refs",_,_) _) = True isBackBlock _ = False @@ -110,14 +85,12 @@ docToJATS opts (Pandoc meta blocks) = do TopLevelChapter -> 0 TopLevelSection -> 1 TopLevelDefault -> 1 - auths' <- mapM (authorToJATS opts) $ docAuthors meta - let meta' = B.setMeta "author" auths' meta metadata <- metaToJSON opts (fmap (render' . vcat) . mapM (elementToJATS opts' startLvl) . hierarchicalize) (fmap render' . inlinesToJATS opts') - meta' + meta main <- (render' . vcat) <$> mapM (elementToJATS opts' startLvl) elements back <- (render' . vcat) <$> @@ -132,7 +105,7 @@ docToJATS opts (Pandoc meta blocks) = do Just tpl -> renderTemplate' tpl context -- | Convert an Element to JATS. -elementToJATS :: PandocMonad m => WriterOptions -> Int -> Element -> DB m Doc +elementToJATS :: PandocMonad m => WriterOptions -> Int -> Element -> JATS m Doc elementToJATS opts _ (Blk block) = blockToJATS opts block elementToJATS opts lvl (Sec _ _num (id',_,kvs) title elements) = do let idAttr = [("id", writerIdentifierPrefix opts ++ id') | not (null id')] @@ -144,7 +117,7 @@ elementToJATS opts lvl (Sec _ _num (id',_,kvs) title elements) = do inTagsSimple "title" title' $$ vcat contents -- | Convert a list of Pandoc blocks to JATS. -blocksToJATS :: PandocMonad m => WriterOptions -> [Block] -> DB m Doc +blocksToJATS :: PandocMonad m => WriterOptions -> [Block] -> JATS m Doc blocksToJATS opts = fmap vcat . mapM (blockToJATS opts) -- | Auxiliary function to convert Plain block to Para. @@ -155,13 +128,13 @@ plainToPara x = x -- | Convert a list of pairs of terms and definitions into a list of -- JATS varlistentrys. deflistItemsToJATS :: PandocMonad m - => WriterOptions -> [([Inline],[[Block]])] -> DB m Doc + => WriterOptions -> [([Inline],[[Block]])] -> JATS m Doc deflistItemsToJATS opts items = vcat <$> mapM (uncurry (deflistItemToJATS opts)) items -- | Convert a term and a list of blocks into a JATS varlistentry. deflistItemToJATS :: PandocMonad m - => WriterOptions -> [Inline] -> [[Block]] -> DB m Doc + => WriterOptions -> [Inline] -> [[Block]] -> JATS m Doc deflistItemToJATS opts term defs = do term' <- inlinesToJATS opts term def' <- blocksToJATS opts $ concatMap (map plainToPara) defs @@ -171,7 +144,7 @@ deflistItemToJATS opts term defs = do -- | Convert a list of lists of blocks to a list of JATS list items. listItemsToJATS :: PandocMonad m - => WriterOptions -> Maybe [String] -> [[Block]] -> DB m Doc + => WriterOptions -> Maybe [String] -> [[Block]] -> JATS m Doc listItemsToJATS opts markers items = case markers of Nothing -> vcat <$> mapM (listItemToJATS opts Nothing) items @@ -179,7 +152,7 @@ listItemsToJATS opts markers items = -- | Convert a list of blocks into a JATS list item. listItemToJATS :: PandocMonad m - => WriterOptions -> Maybe String -> [Block] -> DB m Doc + => WriterOptions -> Maybe String -> [Block] -> JATS m Doc listItemToJATS opts mbmarker item = do contents <- blocksToJATS opts item return $ inTagsIndented "list-item" $ @@ -187,7 +160,7 @@ listItemToJATS opts mbmarker item = do $$ contents -- | Convert a Pandoc block element to JATS. -blockToJATS :: PandocMonad m => WriterOptions -> Block -> DB m Doc +blockToJATS :: PandocMonad m => WriterOptions -> Block -> JATS m Doc blockToJATS _ Null = return empty -- Bibliography reference: blockToJATS opts (Div ('r':'e':'f':'-':_,_,_) [Para lst]) = @@ -311,7 +284,7 @@ tableRowToJATS :: PandocMonad m => WriterOptions -> Bool -> [[Block]] - -> DB m Doc + -> JATS m Doc tableRowToJATS opts isHeader cols = (inTagsIndented "tr" . vcat) <$> mapM (tableItemToJATS opts isHeader) cols @@ -319,17 +292,17 @@ tableItemToJATS :: PandocMonad m => WriterOptions -> Bool -> [Block] - -> DB m Doc + -> JATS m Doc tableItemToJATS opts isHeader item = (inTags True (if isHeader then "th" else "td") [] . vcat) <$> mapM (blockToJATS opts) item -- | Convert a list of inline elements to JATS. -inlinesToJATS :: PandocMonad m => WriterOptions -> [Inline] -> DB m Doc +inlinesToJATS :: PandocMonad m => WriterOptions -> [Inline] -> JATS m Doc inlinesToJATS opts lst = hcat <$> mapM (inlineToJATS opts) lst -- | Convert an inline element to JATS. -inlineToJATS :: PandocMonad m => WriterOptions -> Inline -> DB m Doc +inlineToJATS :: PandocMonad m => WriterOptions -> Inline -> JATS m Doc inlineToJATS _ (Str str) = return $ text $ escapeStringForXML str inlineToJATS opts (Emph lst) = inTagsSimple "italic" <$> inlinesToJATS opts lst diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index ab1e90b3b..976450dcd 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -371,6 +371,10 @@ toSlides bs = do concat `fmap` mapM (elementToBeamer slideLevel) (hierarchicalize bs') elementToBeamer :: PandocMonad m => Int -> Element -> LW m [Block] +elementToBeamer _slideLevel (Blk (Div attr bs)) = do + -- make sure we support "blocks" inside divs + bs' <- concat `fmap` mapM (elementToBeamer 0) (hierarchicalize bs) + return [Div attr bs'] elementToBeamer _slideLevel (Blk b) = return [b] elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts) | lvl > slideLevel = do diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 5d812b169..a1f30cb0e 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -397,11 +397,19 @@ blockToMarkdown' :: PandocMonad m blockToMarkdown' _ Null = return empty blockToMarkdown' opts (Div attrs ils) = do contents <- blockListToMarkdown opts ils - return $ if isEnabled Ext_raw_html opts && - isEnabled Ext_markdown_in_html_blocks opts - then tagWithAttrs "div" attrs <> blankline <> - contents <> blankline <> "</div>" <> blankline - else contents <> blankline + return $ + case () of + _ | isEnabled Ext_fenced_divs opts && + attrs /= nullAttr -> + nowrap (text ":::" <+> attrsToMarkdown attrs) $$ + chomp contents $$ + text ":::" <> blankline + | isEnabled Ext_native_divs opts || + (isEnabled Ext_raw_html opts && + isEnabled Ext_markdown_in_html_blocks opts) -> + tagWithAttrs "div" attrs <> blankline <> + contents <> blankline <> "</div>" <> blankline + | otherwise -> contents <> blankline blockToMarkdown' opts (Plain inlines) = do contents <- inlineListToMarkdown opts inlines -- escape if para starts with ordered list marker diff --git a/test/Tests/Readers/Creole.hs b/test/Tests/Readers/Creole.hs index 96517c25c..3a21df738 100644 --- a/test/Tests/Readers/Creole.hs +++ b/test/Tests/Readers/Creole.hs @@ -127,6 +127,11 @@ tests = [ =?> bulletList [ plain "foo" <> bulletList [ plain "bar", plain "baz" ] , plain "blubb" ] + , "nested unordered list, one separating space, trailing space" =: + "* foo \n** bar \n** baz \n* blubb " + =?> bulletList [ plain "foo" + <> bulletList [ plain "bar", plain "baz" ] + , plain "blubb" ] , "ordered list, two entries, one separating space" =: "# foo\n# bar" =?> orderedList [ plain "foo", plain "bar" ] @@ -141,6 +146,11 @@ tests = [ =?> orderedList [ plain "foo" <> orderedList [ plain "bar", plain "baz" ] , plain "blubb" ] + , "nested ordered list, one separating space, trailing space" =: + "# foo \n## bar \n## baz \n# blubb " + =?> orderedList [ plain "foo" + <> orderedList [ plain "bar", plain "baz" ] + , plain "blubb" ] , "nested many ordered lists, one separating space" =: ("# foo\n## bar\n### third\n### third two\n## baz\n### third again\n" <> "#### fourth\n##### fith\n# blubb") @@ -193,7 +203,10 @@ tests = [ , "forced line breaks" =: "{{{no break!\\\\here}}} but a break\\\\here!" =?> para (code "no break!\\\\here" <> " but a break" - <> linebreak <> "here!") + <> linebreak <> "here!"), + "quoted block, after trailing white space" =: + "this is a paragraph \n{{{\nfoo bar\n //baz//\n}}}" + =?> para "this is a paragraph" <> codeBlock "foo bar\n //baz//" ] , testGroup "Images and Links" [ "image simple" =: diff --git a/test/Tests/Writers/FB2.hs b/test/Tests/Writers/FB2.hs new file mode 100644 index 000000000..77ab4a82c --- /dev/null +++ b/test/Tests/Writers/FB2.hs @@ -0,0 +1,34 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.FB2 (tests) where + +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +fb2 :: String -> String +fb2 x = "<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n" ++ + "<FictionBook xmlns=\"http://www.gribuser.ru/xml/fictionbook/2.0\" xmlns:l=\"http://www.w3.org/1999/xlink\"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section>" ++ x ++ "</section></body></FictionBook>" + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test (purely (writeFB2 def) . toPandoc) + +tests :: [TestTree] +tests = [ testGroup "block elements" + ["para" =: para "Lorem ipsum cetera." + =?> fb2 "<p>Lorem ipsum cetera.</p>" + ] + , testGroup "inlines" + [ + "Emphasis" =: emph ("emphasized") + =?> fb2 "<emphasis>emphasized</emphasis>" + ] + , "bullet list" =: bulletList [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> fb2 "<p>\x2022 first</p><p>\x2022 second</p><p>\x2022 third</p>" + ] diff --git a/test/command/3596.md b/test/command/3596.md index a064ca632..01a871e1b 100644 --- a/test/command/3596.md +++ b/test/command/3596.md @@ -50,11 +50,9 @@ ^D - foo -- <div id="id"> - +- ::: {#id} bar - - </div> + ::: - baz diff --git a/test/command/4012.md b/test/command/4012.md new file mode 100644 index 000000000..579ee2459 --- /dev/null +++ b/test/command/4012.md @@ -0,0 +1,8 @@ +``` +pandoc -f markdown-implicit_figures +![image] + +[image]: http://example.com/image.jpg {height=35mm} +^D +<p><img src="http://example.com/image.jpg" alt="image" style="height:35mm" /></p> +``` diff --git a/test/command/4016.md b/test/command/4016.md new file mode 100644 index 000000000..69ad1c911 --- /dev/null +++ b/test/command/4016.md @@ -0,0 +1,47 @@ +``` +pandoc -t beamer +# Level 2 blocks + +<div class="columns"> +<div class="column" width="40%"> +## Block one +- Item +</div> +<div class="column" width="60%"> +## Block two +- Item +</div> +</div> +^D +\begin{frame}{% +\protect\hypertarget{level-2-blocks}{% +Level 2 blocks}} + +\begin{columns}[T] +\begin{column}{0.40\textwidth} +\begin{block}{Block one} + +\begin{itemize} +\tightlist +\item + Item +\end{itemize} + +\end{block} +\end{column} + +\begin{column}{0.60\textwidth} +\begin{block}{Block two} + +\begin{itemize} +\tightlist +\item + Item +\end{itemize} + +\end{block} +\end{column} +\end{columns} + +\end{frame} +``` diff --git a/test/command/4019.md b/test/command/4019.md new file mode 100644 index 000000000..ab13f0233 --- /dev/null +++ b/test/command/4019.md @@ -0,0 +1,8 @@ +``` +pandoc --wrap=preserve +This <!-- x > 0 --> works! +This <!-- x > 0 --> fails? +^D +<p>This <!-- x > 0 --> works! +This <!-- x > 0 --> fails?</p> +``` diff --git a/test/command/latex-command-comment.md b/test/command/latex-command-comment.md new file mode 100644 index 000000000..640277f15 --- /dev/null +++ b/test/command/latex-command-comment.md @@ -0,0 +1,7 @@ +``` +pandoc -f latex -t native +\emph% +{hi} +^D +[Para [Emph [Str "hi"]]] +``` diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs index 358354e42..e1ce1bc70 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -23,6 +23,7 @@ import qualified Tests.Writers.AsciiDoc import qualified Tests.Writers.ConTeXt import qualified Tests.Writers.Docbook import qualified Tests.Writers.Docx +import qualified Tests.Writers.FB2 import qualified Tests.Writers.HTML import qualified Tests.Writers.LaTeX import qualified Tests.Writers.Markdown @@ -52,6 +53,7 @@ tests = testGroup "pandoc tests" [ Tests.Command.tests , testGroup "RST" Tests.Writers.RST.tests , testGroup "TEI" Tests.Writers.TEI.tests , testGroup "Muse" Tests.Writers.Muse.tests + , testGroup "FB2" Tests.Writers.FB2.tests ] , testGroup "Readers" [ testGroup "LaTeX" Tests.Readers.LaTeX.tests diff --git a/test/writer.fb2 b/test/writer.fb2 index 8a4986508..9b4645d50 100644 --- a/test/writer.fb2 +++ b/test/writer.fb2 @@ -261,23 +261,23 @@ <p>Nested</p> </title> <p>• Tab</p> -<p>◦ Tab</p> -<p>* Tab</p> +<p>• • Tab</p> +<p>• • • Tab</p> <p>Here’s another:</p> <p>1. First</p> <p>2. Second:</p> -<p> • Fee</p> -<p> • Fie</p> -<p> • Foe</p> +<p>2. • Fee</p> +<p>2. • Fie</p> +<p>2. • Foe</p> <p>3. Third</p> <p>Same thing but with paragraphs:</p> <p>1. First</p> <empty-line /> <p>2. Second:</p> <empty-line /> -<p> • Fee</p> -<p> • Fie</p> -<p> • Foe</p> +<p>2. • Fee</p> +<p>2. • Fie</p> +<p>2. • Foe</p> <p>3. Third</p> <empty-line /> </section> @@ -289,9 +289,9 @@ <empty-line /> <p>• this is a list item indented with spaces</p> <empty-line /> -<p>◦ this is an example list item indented with tabs</p> +<p>• • this is an example list item indented with tabs</p> <empty-line /> -<p>◦ this is an example list item indented with spaces</p> +<p>• • this is an example list item indented with spaces</p> <empty-line /> </section> <section> @@ -332,64 +332,61 @@ <p> <strong>apple</strong> </p> -<p> red fruit<empty-line /> -</p> +<p> red fruit</p> <p> <strong>orange</strong> </p> -<p> orange fruit<empty-line /> -</p> +<p> orange fruit</p> <p> <strong>banana</strong> </p> -<p> yellow fruit<empty-line /> -</p> +<p> yellow fruit</p> <p>Tight using tabs:</p> <p> <strong>apple</strong> </p> -<p> red fruit<empty-line /> -</p> +<p> red fruit</p> <p> <strong>orange</strong> </p> -<p> orange fruit<empty-line /> -</p> +<p> orange fruit</p> <p> <strong>banana</strong> </p> -<p> yellow fruit<empty-line /> -</p> +<p> yellow fruit</p> <p>Loose:</p> <p> <strong>apple</strong> </p> -<p> red fruit<empty-line /> -</p> +<p> red fruit</p> +<empty-line /> <p> <strong>orange</strong> </p> -<p> orange fruit<empty-line /> -</p> +<p> orange fruit</p> +<empty-line /> <p> <strong>banana</strong> </p> -<p> yellow fruit<empty-line /> -</p> +<p> yellow fruit</p> +<empty-line /> <p>Multiple blocks with italics:</p> <p> <strong> <emphasis>apple</emphasis> </strong> </p> -<p> red fruit<empty-line /> contains seeds, crisp, pleasant to taste<empty-line /> -</p> +<p> red fruit</p> +<empty-line /> +<p> contains seeds, crisp, pleasant to taste</p> +<empty-line /> <p> <strong> <emphasis>orange</emphasis> </strong> </p> -<p> orange fruit<empty-line /> +<p> orange fruit</p> +<empty-line /> <empty-line /> <p> <code> { orange code block }</code> @@ -398,42 +395,47 @@ <cite> <p> orange block quote</p> </cite> -</p> <p>Multiple definitions, tight:</p> <p> <strong>apple</strong> </p> -<p> red fruit<empty-line /> computer<empty-line /> -</p> +<p> red fruit</p> +<p> computer</p> <p> <strong>orange</strong> </p> -<p> orange fruit<empty-line /> bank<empty-line /> -</p> +<p> orange fruit</p> +<p> bank</p> <p>Multiple definitions, loose:</p> <p> <strong>apple</strong> </p> -<p> red fruit<empty-line /> computer<empty-line /> -</p> +<p> red fruit</p> +<empty-line /> +<p> computer</p> +<empty-line /> <p> <strong>orange</strong> </p> -<p> orange fruit<empty-line /> bank<empty-line /> -</p> +<p> orange fruit</p> +<empty-line /> +<p> bank</p> +<empty-line /> <p>Blank line after term, indented marker, alternate markers:</p> <p> <strong>apple</strong> </p> -<p> red fruit<empty-line /> computer<empty-line /> -</p> +<p> red fruit</p> +<empty-line /> +<p> computer</p> +<empty-line /> <p> <strong>orange</strong> </p> -<p> orange fruit<empty-line /> +<p> orange fruit</p> +<empty-line /> <p>1. sublist</p> <p>2. sublist</p> -</p> </section> <section> <title> diff --git a/test/writer.jats b/test/writer.jats index 6f808e109..0f52965bc 100644 --- a/test/writer.jats +++ b/test/writer.jats @@ -14,6 +14,18 @@ <title-group> <article-title>Pandoc Test Suite</article-title> </title-group> +<contrib-group> +<contrib contrib-type="author"> +<name> +<string-name>John MacFarlane</string-name> +</name> +</contrib> +<contrib contrib-type="author"> +<name> +<string-name>Anonymous</string-name> +</name> +</contrib> +</contrib-group> <pub-date pub-type="epub"> <string-date>July 17, 2006</string-date> </pub-date> |