From 543aa28c3895d4dc7d3d659b652237efb41661b0 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Sun, 12 Dec 2010 20:09:14 -0800 Subject: [PATCH] Added new prettyprinting module. * Added Text.Pandoc.Pretty. This is better suited for pandoc than the 'pretty' package. One advantage is that we now get proper wrapping; Emph [Inline] is no longer treated as a big unwrappable unit. Previously we only got breaks for spaces at the "outer level." We can also more easily avoid doubled blank lines. Performance is significantly better as well. * Removed Text.Pandoc.Blocks. Text.Pandoc.Pretty allows you to define blocks and concatenate them. * Modified markdown, RST, org readers to use Text.Pandoc.Pretty instead of Text.PrettyPrint.HughesPJ. * Text.Pandoc.Shared: Added writerColumns to WriterOptions. * Markdown, RST, Org writers now break text at writerColumns. * Added --columns command-line option, which sets stColumns and writerColumns. * Table parsing: If the size of the header > stColumns, use the header size as 100% for purposes of calculating relative widths of columns. --- README | 7 +- pandoc.cabal | 10 +- src/Text/Pandoc/Blocks.hs | 146 ------- src/Text/Pandoc/Parsing.hs | 5 +- src/Text/Pandoc/Pretty.hs | 395 ++++++++++++++++++ src/Text/Pandoc/Shared.hs | 3 + src/Text/Pandoc/Writers/Markdown.hs | 292 +++++++------ src/Text/Pandoc/Writers/Org.hs | 148 +++---- src/Text/Pandoc/Writers/RST.hs | 170 ++++---- src/pandoc.hs | 58 ++- src/test-pandoc.hs | 15 +- templates/org.template | 2 + tests/biblatex-citations.latex | 10 +- ...markdown-citations.chicago-author-date.txt | 10 +- tests/markdown-citations.ieee.txt | 10 +- tests/markdown-citations.mhra.txt | 39 +- tests/markdown-citations.txt | 14 +- tests/natbib-citations.latex | 20 +- tests/tables.markdown | 17 +- tests/tables.plain | 17 +- tests/writer.markdown | 117 ++---- tests/writer.org | 296 ++++--------- tests/writer.plain | 118 ++---- tests/writer.rst | 209 +++------ 24 files changed, 1052 insertions(+), 1076 deletions(-) delete mode 100644 src/Text/Pandoc/Blocks.hs create mode 100644 src/Text/Pandoc/Pretty.hs diff --git a/README b/README index 2e8502f01..0bc9b3a01 100644 --- a/README +++ b/README @@ -177,7 +177,7 @@ Options `-p`, `--preserve-tabs` : Preserve tabs instead of converting them to spaces (the default). -`--tab-stop=`*TABSTOP* +`--tab-stop=`*NUMBER* : Specify the number of spaces per tab (default is 4). `--strict` @@ -270,6 +270,9 @@ Options : Disable text wrapping in output. By default, text is wrapped appropriately for the output format. +`--columns`=*NUMBER* +: Specify length of lines in characters (for text wrapping). + `--email-obfuscation=`*none|javascript|references* : Specify a method for obfuscating `mailto:` links in HTML documents. *none* leaves `mailto:` links as they are. *javascript* obfuscates @@ -294,7 +297,7 @@ Options one) in the output document. This option has no effect on `man`, `docbook`, `slidy`, or `s5` output. -`--base-header-level=`*LEVEL* +`--base-header-level=`*NUMBER* : Specify the base level for headers (defaults to 1). `--template=`*FILE* diff --git a/pandoc.cabal b/pandoc.cabal index 312111afb..089ba6095 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -87,7 +87,7 @@ Extra-Source-Files: tests/latex-reader.native, tests/markdown-reader-more.txt, tests/markdown-reader-more.native, - tests/textile-reader.textile, + tests/textile-reader.textile, tests/rst-reader.native, tests/rst-reader.rst, tests/s5.basic.html, @@ -175,7 +175,8 @@ Library random, extensible-exceptions, citeproc-hs >= 0.3 && < 0.4, pandoc-types == 1.7.*, - json >= 0.4 && < 0.5 + json >= 0.4 && < 0.5, + dlist >= 0.4 && < 0.6 if impl(ghc >= 6.10) Build-depends: base >= 4 && < 5, syb else @@ -193,7 +194,7 @@ Library -- END DUPLICATED SECTION Exposed-Modules: Text.Pandoc, - Text.Pandoc.Blocks, + Text.Pandoc.Pretty, Text.Pandoc.CharacterReferences, Text.Pandoc.Shared, Text.Pandoc.Parsing, @@ -247,7 +248,8 @@ Executable pandoc random, extensible-exceptions, citeproc-hs >= 0.3 && < 0.4, pandoc-types == 1.7.*, - json >= 0.4 && < 0.5 + json >= 0.4 && < 0.5, + dlist >= 0.4 && < 0.6 if impl(ghc >= 6.10) Build-depends: base >= 4 && < 5, syb else diff --git a/src/Text/Pandoc/Blocks.hs b/src/Text/Pandoc/Blocks.hs deleted file mode 100644 index 122931773..000000000 --- a/src/Text/Pandoc/Blocks.hs +++ /dev/null @@ -1,146 +0,0 @@ -{- -Copyright (C) 2007 John MacFarlane <jgm@berkeley.edu> - -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 -the Free Software Foundation; either version 2 of the License, or -(at your option) any later version. - -This program is distributed in the hope that it will be useful, -but WITHOUT ANY WARRANTY; without even the implied warranty of -MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -GNU General Public License for more details. - -You should have received a copy of the GNU General Public License -along with this program; if not, write to the Free Software -Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA --} - -{- | - Module : Text.Pandoc.Blocks - Copyright : Copyright (C) 2007 John MacFarlane - License : GNU GPL, version 2 or above - - Maintainer : John MacFarlane <jgm@berkeley.edu> - Stability : alpha - Portability : portable - -Functions for the manipulation of fixed-width blocks of text. -These are used in the construction of plain-text tables. --} - -module Text.Pandoc.Blocks - ( - TextBlock (..), - docToBlock, - blockToDoc, - widthOfBlock, - heightOfBlock, - hcatBlocks, - hsepBlocks, - centerAlignBlock, - leftAlignBlock, - rightAlignBlock - ) -where -import Text.PrettyPrint -import Data.List ( intersperse ) - --- | A fixed-width block of text. Parameters are width of block, --- height of block, and list of lines. -data TextBlock = TextBlock Int Int [String] -instance Show TextBlock where - show x = show $ blockToDoc x - --- | Break lines in a list of lines so that none are greater than --- a given width. -breakLines :: Int -- ^ Maximum length of lines. - -> [String] -- ^ List of lines. - -> [String] -breakLines _ [] = [] -breakLines width (l:ls) = - if length l > width - then (take width l):(breakLines width ((drop width l):ls)) - else l:(breakLines width ls) - --- | Convert a @Doc@ element into a @TextBlock@ with a specified width. -docToBlock :: Int -- ^ Width of text block. - -> Doc -- ^ @Doc@ to convert. - -> TextBlock -docToBlock width doc = - let rendered = renderStyle (style {lineLength = width, - ribbonsPerLine = 1}) doc - lns = breakLines width $ lines rendered - in TextBlock width (length lns) lns - --- | Convert a @TextBlock@ to a @Doc@ element. -blockToDoc :: TextBlock -> Doc -blockToDoc (TextBlock _ _ lns) = - if null lns - then empty - else vcat $ map text lns - --- | Returns width of a @TextBlock@ (number of columns). -widthOfBlock :: TextBlock -> Int -widthOfBlock (TextBlock width _ _) = width - --- | Returns height of a @TextBlock@ (number of rows). -heightOfBlock :: TextBlock -> Int -heightOfBlock (TextBlock _ height _) = height - --- | Pads a string out to a given width using spaces. -hPad :: Int -- ^ Desired width. - -> String -- ^ String to pad. - -> String -hPad width line = - let linelen = length line - in if linelen <= width - then line ++ replicate (width - linelen) ' ' - else take width line - --- | Concatenates a list of @TextBlock@s into a new @TextBlock@ in --- which they appear side by side. -hcatBlocks :: [TextBlock] -> TextBlock -hcatBlocks [] = TextBlock 0 0 [] -hcatBlocks [x] = x -- This is not redundant! We don't want last item hPad'd. -hcatBlocks ((TextBlock width1 height1 lns1):xs) = - let (TextBlock width2 height2 lns2) = hcatBlocks xs - height = max height1 height2 - width = width1 + width2 - lns1' = map (hPad width1) $ lns1 ++ replicate (height - height1) "" - lns2' = lns2 ++ replicate (height - height2) "" - lns = zipWith (++) lns1' lns2' - in TextBlock width height lns - --- | Like @hcatBlocks@, but inserts space between the @TextBlock@s. -hsepBlocks :: [TextBlock] -> TextBlock -hsepBlocks = hcatBlocks . (intersperse (TextBlock 1 1 [" "])) - -isWhitespace :: Char -> Bool -isWhitespace x = x `elem` " \t" - --- | Left-aligns the contents of a @TextBlock@ within the block. -leftAlignBlock :: TextBlock -> TextBlock -leftAlignBlock (TextBlock width height lns) = - TextBlock width height $ map (dropWhile isWhitespace) lns - --- | Right-aligns the contents of a @TextBlock@ within the block. -rightAlignBlock :: TextBlock -> TextBlock -rightAlignBlock (TextBlock width height lns) = - let rightAlignLine ln = - let (spaces, rest) = span isWhitespace $ reverse $ hPad width ln - in reverse (rest ++ spaces) - in TextBlock width height $ map rightAlignLine lns - --- | Centers the contents of a @TextBlock@ within the block. -centerAlignBlock :: TextBlock -> TextBlock -centerAlignBlock (TextBlock width height lns) = - let centerAlignLine ln = - let ln' = hPad width ln - (startSpaces, rest) = span isWhitespace ln' - endSpaces = takeWhile isWhitespace (reverse ln') - numSpaces = length (startSpaces ++ endSpaces) - startSpaces' = replicate (quot numSpaces 2) ' ' - in startSpaces' ++ rest - in TextBlock width height $ map centerAlignLine lns - diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 48c6aa70d..a49f464c8 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -453,8 +453,9 @@ widthsFromIndices :: Int -- Number of columns on terminal -> [Int] -- Indices -> [Double] -- Fractional relative sizes of columns widthsFromIndices _ [] = [] -widthsFromIndices numColumns indices = - let lengths' = zipWith (-) indices (0:indices) +widthsFromIndices numColumns' indices = + let numColumns = max numColumns' (if null indices then 0 else last indices) + lengths' = zipWith (-) indices (0:indices) lengths = reverse $ case reverse lengths' of [] -> [] diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs new file mode 100644 index 000000000..e8b27df91 --- /dev/null +++ b/src/Text/Pandoc/Pretty.hs @@ -0,0 +1,395 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{- +Copyright (C) 2010 John MacFarlane <jgm@berkeley.edu> + +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 +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111(-1)307 USA +-} + +{- | + Module : Text.Pandoc.Pretty + Copyright : Copyright (C) 2010 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane <jgm@berkeley.edu> + Stability : alpha + Portability : portable + +A prettyprinting library for the production of text documents, +including wrapped text, indentated blocks, and tables. +-} + +module Text.Pandoc.Pretty ( + Doc + , render + , cr + , blankline + , space + , text + , char + , prefixed + , flush + , nest + , hang + , nowrap + , offset + , height + , lblock + , cblock + , rblock + , (<>) + , (<+>) + , ($$) + , ($+$) + , isEmpty + , empty + , cat + , hcat + , hsep + , vcat + , vsep + ) + +where +import Data.DList (DList, fromList, toList, cons, singleton) +import Data.List (intercalate) +import Data.Monoid +import Data.String +import Control.Monad.State +import Data.Char (isSpace) + +data Monoid a => + RenderState a = RenderState{ + output :: [a] -- ^ In reverse order + , prefix :: String + , usePrefix :: Bool + , lineLength :: Maybe Int -- ^ 'Nothing' means no wrapping + , column :: Int + , newlines :: Int -- ^ Number of preceding newlines + } + +type DocState a = State (RenderState a) () + +data D = Text Int String + | Block Int [String] + | Prefixed String Doc + | Flush Doc + | BreakingSpace + | CarriageReturn + | NewLine + | BlankLine + deriving (Show) + +newtype Doc = Doc { unDoc :: DList D } + deriving (Monoid) + +instance Show Doc where + show = render Nothing + +instance IsString Doc where + fromString = text + +-- | True if the document is empty. +isEmpty :: Doc -> Bool +isEmpty = null . toList . unDoc + +-- | The empty document. +empty :: Doc +empty = mempty + +-- | @a <> b@ is the result of concatenating @a@ with @b@. +(<>) :: Doc -> Doc -> Doc +(<>) = mappend + +-- | Concatenate a list of 'Doc's. +cat :: [Doc] -> Doc +cat = mconcat + +-- | Same as 'cat'. +hcat :: [Doc] -> Doc +hcat = mconcat + +-- | Concatenate a list of 'Doc's, putting breakable spaces +-- between them. +(<+>) :: Doc -> Doc -> Doc +(<+>) x y = if isEmpty x + then y + else if isEmpty y + then x + else x <> space <> y + +-- | Same as 'cat', but putting breakable spaces between the +-- 'Doc's. +hsep :: [Doc] -> Doc +hsep = foldr (<+>) empty + +-- | @a $$ b@ puts @a@ above @b@. +($$) :: Doc -> Doc -> Doc +($$) x y = if isEmpty x + then y + else if isEmpty y + then x + else x <> cr <> y + +-- | @a $$ b@ puts @a@ above @b@, with a blank line between. +($+$) :: Doc -> Doc -> Doc +($+$) x y = if isEmpty x + then y + else if isEmpty y + then x + else x <> blankline <> y + +-- | List version of '$$'. +vcat :: [Doc] -> Doc +vcat = foldr ($$) empty + +-- | List version of '$+$'. +vsep :: [Doc] -> Doc +vsep = foldr ($+$) empty + +outp :: (IsString a, Monoid a) + => Int -> String -> DocState a +outp off s | off <= 0 = do + st' <- get + let rawpref = prefix st' + when (column st' == 0 && usePrefix st' && not (null rawpref)) $ do + let pref = reverse $ dropWhile isSpace $ reverse rawpref + modify $ \st -> st{ output = fromString pref : output st + , column = column st + length pref } + when (off < 0) $ do + modify $ \st -> st { output = fromString s : output st + , column = 0 + , newlines = newlines st + 1 } +outp off s = do + st' <- get + let pref = prefix st' + when (column st' == 0 && usePrefix st' && not (null pref)) $ do + modify $ \st -> st{ output = fromString pref : output st + , column = column st + length pref } + modify $ \st -> st{ output = fromString s : output st + , column = column st + off + , newlines = 0 } + +-- | Renders a 'Doc'. @render (Just n)@ will use +-- a line length of @n@ to reflow text on breakable spaces. +-- @render Nothing@ will not reflow text. +render :: (Monoid a, IsString a) + => Maybe Int -> Doc -> a +render linelen doc = fromString . mconcat . reverse . output $ + execState (renderDoc doc) startingState + where startingState = RenderState{ + output = mempty + , prefix = "" + , usePrefix = True + , lineLength = linelen + , column = 0 + , newlines = 2 } + +renderDoc :: (IsString a, Monoid a) + => Doc -> DocState a +renderDoc = renderList . toList . unDoc + +renderList :: (IsString a, Monoid a) + => [D] -> DocState a +renderList [] = return () +renderList (Text off s : xs) = do + outp off s + renderList xs + +renderList (Prefixed pref d : xs) = do + st <- get + let oldPref = prefix st + put st{ prefix = prefix st ++ pref } + renderDoc d + modify $ \s -> s{ prefix = oldPref } + renderList xs + +renderList (Flush d : xs) = do + st <- get + let oldUsePrefix = usePrefix st + put st{ usePrefix = False } + renderDoc d + modify $ \s -> s{ usePrefix = oldUsePrefix } + renderList xs + +renderList (BlankLine : xs) = do + st <- get + case output st of + _ | newlines st > 1 || null xs -> return () + _ | column st == 0 -> do + outp (-1) "\n" + _ -> do + outp (-1) "\n" + outp (-1) "\n" + renderList xs + +renderList (CarriageReturn : xs) = do + st <- get + if newlines st > 0 || null xs + then renderList xs + else do + outp (-1) "\n" + renderList xs + +renderList (NewLine : xs) = do + outp (-1) "\n" + renderList xs + +renderList (BreakingSpace : xs) = do + let isText (Text _ _) = True + isText (Block _ _) = True + isText _ = False + let isBreakingSpace BreakingSpace = True + isBreakingSpace _ = False + let xs' = dropWhile isBreakingSpace xs + let next = takeWhile isText xs' + st <- get + let off = sum $ map offsetOf next + case lineLength st of + Just l | column st + 1 + off > l -> do + outp (-1) "\n" + renderList xs' + _ -> do + outp 1 " " + renderList xs' + +renderList (b1@Block{} : b2@Block{} : xs) = + renderList (mergeBlocks False b1 b2 : xs) + +renderList (b1@Block{} : BreakingSpace : b2@Block{} : xs) = + renderList (mergeBlocks True b1 b2 : xs) + +renderList (Block width lns : xs) = do + st <- get + let oldPref = prefix st + case column st - length oldPref of + n | n > 0 -> modify $ \s -> s{ prefix = oldPref ++ replicate n ' ' } + _ -> return () + renderDoc $ blockToDoc width lns + modify $ \s -> s{ prefix = oldPref } + renderList xs + +mergeBlocks :: Bool -> D -> D -> D +mergeBlocks addSpace (Block w1 lns1) (Block w2 lns2) = + Block (w1 + w2 + if addSpace then 1 else 0) $ + zipWith (\l1 l2 -> pad w1 l1 ++ l2) (lns1 ++ empties) (map sp lns2 ++ empties) + where empties = replicate (abs $ length lns1 - length lns2) "" + pad n s = s ++ replicate (n - length s) ' ' + sp "" = "" + sp xs = if addSpace then (' ' : xs) else xs +mergeBlocks _ _ _ = error "mergeBlocks tried on non-Block!" + +blockToDoc :: Int -> [String] -> Doc +blockToDoc _ lns = text $ intercalate "\n" lns + +offsetOf :: D -> Int +offsetOf (Text o _) = o +offsetOf (Block w _) = w +offsetOf BreakingSpace = 1 +offsetOf _ = 0 + +-- | A literal string. +text :: String -> Doc +text = Doc . toChunks + where toChunks :: String -> DList D + toChunks [] = mempty + toChunks s = case break (=='\n') s of + ([], _:ys) -> NewLine `cons` toChunks ys + (xs, _:ys) -> Text (length xs) xs `cons` + NewLine `cons` toChunks ys + (xs, []) -> singleton $ Text (length xs) xs + +-- | A character. +char :: Char -> Doc +char c = text [c] + +-- | A breaking (reflowable) space. +space :: Doc +space = Doc $ singleton BreakingSpace + +-- | A carriage return. Does nothing if we're at the beginning of +-- a line; otherwise inserts a newline. +cr :: Doc +cr = Doc $ singleton CarriageReturn + +-- | Inserts a blank line unless one exists already. +-- (@blankline <> blankline@ has the same effect as @blankline@. +-- If you want multiple blank lines, use @text "\\n\\n"@. +blankline :: Doc +blankline = Doc $ singleton BlankLine + +-- | Uses the specified string as a prefix for every line of +-- the enclosed document (except the first, if not at the beginning +-- of the line). +prefixed :: String -> Doc -> Doc +prefixed pref doc = Doc $ singleton $ Prefixed pref doc + +-- | Makes a 'Doc' flush against the left margin. +flush :: Doc -> Doc +flush doc = Doc $ singleton $ Flush doc + +-- | Indents a 'Doc' by the specified number of spaces. +nest :: Int -> Doc -> Doc +nest ind = prefixed (replicate ind ' ') + +-- | A hanging indent. @hang ind start doc@ prints @start@, +-- then @doc@, leaving an indent of @ind@ spaces on every +-- line but the first. +hang :: Int -> Doc -> Doc -> Doc +hang ind start doc = start <> nest ind doc + +-- | Makes a 'Doc' non-reflowable. +nowrap :: Doc -> Doc +nowrap doc = Doc $ fromList $ map replaceSpace $ toList $ unDoc doc + where replaceSpace BreakingSpace = Text 1 " " + replaceSpace x = x + +-- | Returns the width of a 'Doc'. +offset :: Doc -> Int +offset d = case map length . lines . render Nothing $ d of + [] -> 0 + os -> maximum os + +block :: (String -> String) -> Int -> Doc -> Doc +block filler width = Doc . singleton . Block width . + map filler . chop width . render (Just width) + +-- | @lblock n d@ is a block of width @n@ characters, with +-- text derived from @d@ and aligned to the left. +lblock :: Int -> Doc -> Doc +lblock = block id + +-- | Like 'lblock' but aligned to the right. +rblock :: Int -> Doc -> Doc +rblock w = block (\s -> replicate (w - length s) ' ' ++ s) w + +-- | Like 'lblock' but aligned centered. +cblock :: Int -> Doc -> Doc +cblock w = block (\s -> replicate ((w - length s) `div` 2) ' ' ++ s) w + +-- | Returns the height of a block or other 'Doc'. +height :: Doc -> Int +height = length . lines . render Nothing + +chop :: Int -> String -> [String] +chop _ [] = [] +chop n cs = case break (=='\n') cs of + (xs, ys) -> if len <= n + then case ys of + [] -> [xs] + (_:[]) -> [xs, ""] + (_:zs) -> xs : chop n zs + else take n xs : chop n (drop n xs ++ ys) + where len = length xs + diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index f0c6eb378..7de3fabb2 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -398,6 +398,7 @@ stringify = queryWith go go Space = " " go (Str x) = x go (Code x) = x + go (Math _ x) = x go _ = "" -- | Change final list item from @Para@ to @Plain@ if the list contains @@ -560,6 +561,7 @@ data WriterOptions = WriterOptions , writerStrictMarkdown :: Bool -- ^ Use strict markdown syntax , writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , writerWrapText :: Bool -- ^ Wrap text to line length + , writerColumns :: Int -- ^ Characters in a line (for text wrapping) , writerLiterateHaskell :: Bool -- ^ Write as literate haskell , writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails , writerIdentifierPrefix :: String -- ^ Prefix for section & note ids in HTML @@ -588,6 +590,7 @@ defaultWriterOptions = , writerStrictMarkdown = False , writerReferenceLinks = False , writerWrapText = True + , writerColumns = 72 , writerLiterateHaskell = False , writerEmailObfuscation = JavascriptObfuscation , writerIdentifierPrefix = "" diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 012889552..fe03ff113 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu> @@ -33,11 +34,10 @@ module Text.Pandoc.Writers.Markdown (writeMarkdown, writePlain) where import Text.Pandoc.Definition import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Shared -import Text.Pandoc.Parsing -import Text.Pandoc.Blocks +import Text.Pandoc.Parsing hiding (blankline) import Text.ParserCombinators.Parsec ( runParser, GenParser ) import Data.List ( group, isPrefixOf, find, intersperse, transpose ) -import Text.PrettyPrint.HughesPJ hiding ( Str ) +import Text.Pandoc.Pretty import Control.Monad.State type Notes = [[Block]] @@ -64,22 +64,21 @@ writePlain opts document = plainify :: Pandoc -> Pandoc plainify = processWith go - where go :: [Inline] -> [Inline] - go (Emph xs : ys) = go xs ++ go ys - go (Strong xs : ys) = go xs ++ go ys - go (Strikeout xs : ys) = go xs ++ go ys - go (Superscript xs : ys) = go xs ++ go ys - go (Subscript xs : ys) = go xs ++ go ys - go (SmallCaps xs : ys) = go xs ++ go ys - go (Code s : ys) = Str s : go ys - go (Math _ s : ys) = Str s : go ys - go (TeX _ : ys) = Str "" : go ys - go (HtmlInline _ : ys) = Str "" : go ys - go (Link xs _ : ys) = go xs ++ go ys - go (Image _ _ : ys) = go ys - go (Cite _ cits : ys) = go cits ++ go ys - go (x : ys) = x : go ys - go [] = [] + where go :: Inline -> Inline + go (Emph xs) = SmallCaps xs + go (Strong xs) = SmallCaps xs + go (Strikeout xs) = SmallCaps xs + go (Superscript xs) = SmallCaps xs + go (Subscript xs) = SmallCaps xs + go (SmallCaps xs) = SmallCaps xs + go (Code s) = Str s + go (Math _ s) = Str s + go (TeX _) = Str "" + go (HtmlInline _) = Str "" + go (Link xs _) = SmallCaps xs + go (Image xs _) = SmallCaps $ [Str "["] ++ xs ++ [Str "]"] + go (Cite _ cits) = SmallCaps cits + go x = x -- | Return markdown representation of document. pandocToMarkdown :: WriterOptions -> Pandoc -> State WriterState String @@ -97,15 +96,19 @@ pandocToMarkdown opts (Pandoc (Meta title authors date) blocks) = do notes' <- notesToMarkdown opts (reverse $ stNotes st) st' <- get -- note that the notes may contain refs refs' <- refsToMarkdown opts (reverse $ stRefs st') - let main = render $ foldl ($+$) empty $ [body, notes', refs'] + let colwidth = if writerWrapText opts + then Just $ writerColumns opts + else Nothing + let main = render colwidth $ body <> + blankline <> notes' <> blankline <> refs' let context = writerVariables opts ++ - [ ("toc", render toc) + [ ("toc", render colwidth toc) , ("body", main) - , ("title", render title') - , ("date", render date') + , ("title", render colwidth title') + , ("date", render colwidth date') ] ++ [ ("titleblock", "yes") | titleblock ] ++ - [ ("author", render a) | a <- authors' ] + [ ("author", render colwidth a) | a <- authors' ] if writerStandalone opts then return $ renderTemplate context $ writerTemplate opts else return main @@ -113,29 +116,36 @@ pandocToMarkdown opts (Pandoc (Meta title authors date) blocks) = do -- | Return markdown representation of reference key table. refsToMarkdown :: WriterOptions -> Refs -> State WriterState Doc refsToMarkdown opts refs = mapM (keyToMarkdown opts) refs >>= return . vcat - + -- | Return markdown representation of a reference key. keyToMarkdown :: WriterOptions -> ([Inline], (String, String)) -> State WriterState Doc keyToMarkdown opts (label, (src, tit)) = do label' <- inlineListToMarkdown opts label - let tit' = if null tit then empty else text $ " \"" ++ tit ++ "\"" - return $ text " " <> char '[' <> label' <> char ']' <> text ": " <> - text src <> tit' + let tit' = if null tit + then empty + else space <> "\"" <> text tit <> "\"" + return $ nest 2 $ hang 2 + ("[" <> label' <> "]:" <> space) (text src <> tit') -- | Return markdown representation of notes. notesToMarkdown :: WriterOptions -> [[Block]] -> State WriterState Doc notesToMarkdown opts notes = - mapM (\(num, note) -> noteToMarkdown opts num note) (zip [1..] notes) >>= - return . vcat + mapM (\(num, note) -> noteToMarkdown opts num note) (zip [1..] notes) >>= + return . vsep -- | Return markdown representation of a note. noteToMarkdown :: WriterOptions -> Int -> [Block] -> State WriterState Doc noteToMarkdown opts num blocks = do contents <- blockListToMarkdown opts blocks - let marker = text "[^" <> text (show num) <> text "]:" - return $ hang' marker (writerTabStop opts) contents + let num' = text $ show num + let marker = text "[^" <> num' <> text "]:" + let markerSize = 4 + offset num' + let spacer = case writerTabStop opts - markerSize of + n | n > 0 -> text $ replicate n ' ' + _ -> text " " + return $ hang (writerTabStop opts) (marker <> spacer) contents -- | Escape special characters for Markdown. escapeString :: String -> String @@ -170,134 +180,131 @@ olMarker = do (start, style', delim) <- anyOrderedListMarker -- | True if string begins with an ordered list marker beginsWithOrderedListMarker :: String -> Bool -beginsWithOrderedListMarker str = - case runParser olMarker defaultParserState "para start" str of - Left _ -> False +beginsWithOrderedListMarker str = + case runParser olMarker defaultParserState "para start" (take 10 str) of + Left _ -> False Right _ -> True -wrappedMarkdown :: WriterOptions -> [Inline] -> State WriterState Doc -wrappedMarkdown opts inlines = do - let chunks = splitBy LineBreak inlines - let chunks' = if null chunks - then [] - else (map (++ [Str " "]) $ init chunks) ++ [last chunks] - lns <- mapM (wrapIfNeeded opts (inlineListToMarkdown opts)) chunks' - return $ vcat lns - -- | Convert Pandoc block element to markdown. blockToMarkdown :: WriterOptions -- ^ Options -> Block -- ^ Block element -> State WriterState Doc blockToMarkdown _ Null = return empty -blockToMarkdown opts (Plain inlines) = - wrappedMarkdown opts inlines +blockToMarkdown opts (Plain inlines) = do + contents <- inlineListToMarkdown opts inlines + return $ contents <> cr blockToMarkdown opts (Para inlines) = do - contents <- wrappedMarkdown opts inlines + contents <- inlineListToMarkdown opts inlines -- escape if para starts with ordered list marker - let esc = if (not (writerStrictMarkdown opts)) && - beginsWithOrderedListMarker (render contents) - then char '\\' - else empty - return $ esc <> contents <> text "\n" + st <- get + let esc = if (not (writerStrictMarkdown opts)) && + not (stPlain st) && + beginsWithOrderedListMarker (render Nothing contents) + then text "\\" + else empty + return $ esc <> contents <> blankline blockToMarkdown _ (RawHtml str) = do st <- get if stPlain st then return empty - else return $ text str -blockToMarkdown _ HorizontalRule = return $ text "\n* * * * *\n" + else return $ text str <> text "\n" +blockToMarkdown _ HorizontalRule = + return $ blankline <> text "* * * * *" <> blankline blockToMarkdown opts (Header level inlines) = do contents <- inlineListToMarkdown opts inlines st <- get -- use setext style headers if in literate haskell mode. -- ghc interprets '#' characters in column 1 as line number specifiers. if writerLiterateHaskell opts || stPlain st - then let len = length $ render contents - in return $ contents <> text "\n" <> - case level of - 1 -> text $ replicate len '=' ++ "\n" - 2 -> text $ replicate len '-' ++ "\n" - _ -> empty - else return $ text ((replicate level '#') ++ " ") <> contents <> text "\n" -blockToMarkdown opts (CodeBlock (_,classes,_) str) | "haskell" `elem` classes && - "literate" `elem` classes && - writerLiterateHaskell opts = - return $ (vcat $ map (text "> " <>) $ map text (lines str)) <> text "\n" + then let len = offset contents + in return $ contents <> cr <> + (case level of + 1 -> text $ replicate len '=' + 2 -> text $ replicate len '-' + _ -> empty) <> blankline + else return $ + text ((replicate level '#') ++ " ") <> contents <> blankline +blockToMarkdown opts (CodeBlock (_,classes,_) str) + | "haskell" `elem` classes && "literate" `elem` classes && + writerLiterateHaskell opts = + return $ prefixed "> " (text str) <> blankline blockToMarkdown opts (CodeBlock _ str) = return $ - (nest (writerTabStop opts) $ vcat $ map text (lines str)) <> text "\n" + nest (writerTabStop opts) (text str) <> blankline blockToMarkdown opts (BlockQuote blocks) = do st <- get -- if we're writing literate haskell, put a space before the bird tracks -- so they won't be interpreted as lhs... let leader = if writerLiterateHaskell opts - then text . (" > " ++) + then " > " else if stPlain st - then text . (" " ++) - else text . ("> " ++) + then " " + else "> " contents <- blockListToMarkdown opts blocks - return $ (vcat $ map leader $ lines $ render contents) <> - text "\n" + return $ (prefixed leader contents) <> blankline blockToMarkdown opts (Table caption aligns widths headers rows) = do caption' <- inlineListToMarkdown opts caption let caption'' = if null caption then empty - else text "" $+$ (text ": " <> caption') + else blankline <> ": " <> caption' <> blankline headers' <- mapM (blockListToMarkdown opts) headers let alignHeader alignment = case alignment of - AlignLeft -> leftAlignBlock - AlignCenter -> centerAlignBlock - AlignRight -> rightAlignBlock - AlignDefault -> leftAlignBlock + AlignLeft -> lblock + AlignCenter -> cblock + AlignRight -> rblock + AlignDefault -> lblock rawRows <- mapM (mapM (blockListToMarkdown opts)) rows let isSimple = all (==0) widths - let numChars = maximum . map (length . render) + let numChars = maximum . map offset let widthsInChars = if isSimple then map ((+2) . numChars) $ transpose (headers' : rawRows) - else map (floor . (78 *)) widths - let makeRow = hsepBlocks . (zipWith alignHeader aligns) . - (zipWith docToBlock widthsInChars) + else map (floor . (fromIntegral (writerColumns opts) *)) widths + let makeRow = hcat . intersperse (lblock 1 (text " ")) . + (zipWith3 alignHeader aligns widthsInChars) let rows' = map makeRow rawRows let head' = makeRow headers' - let maxRowHeight = maximum $ map heightOfBlock (head':rows') - let underline = hsep $ - map (\width -> text $ replicate width '-') widthsInChars + let maxRowHeight = maximum $ map height (head':rows') + let underline = cat $ intersperse (text " ") $ + map (\width -> text (replicate width '-')) widthsInChars let border = if maxRowHeight > 1 - then text $ replicate (sum widthsInChars + (length widthsInChars - 1)) '-' + then text (replicate (sum widthsInChars + + length widthsInChars - 1) '-') else if all null headers then underline else empty let head'' = if all null headers then empty - else border $+$ blockToDoc head' - let spacer = if maxRowHeight > 1 - then text "" - else empty - let body = vcat $ intersperse spacer $ map blockToDoc rows' + else border <> cr <> head' + let body = if maxRowHeight > 1 + then vsep rows' + else vcat rows' let bottom = if all null headers then underline else border - return $ (nest 2 $ head'' $+$ underline $+$ body $+$ - bottom $+$ caption'') <> text "\n" + return $ nest 2 $ head'' $$ underline $$ body $$ + bottom $$ blankline $$ caption'' $$ blankline blockToMarkdown opts (BulletList items) = do contents <- mapM (bulletListItemToMarkdown opts) items - return $ (vcat contents) <> text "\n" + return $ cat contents <> blankline blockToMarkdown opts (OrderedList attribs items) = do let markers = orderedListMarkers attribs let markers' = map (\m -> if length m < 3 then m ++ replicate (3 - length m) ' ' - else m) markers + else m) markers contents <- mapM (\(item, num) -> orderedListItemToMarkdown opts item num) $ - zip markers' items - return $ (vcat contents) <> text "\n" + zip markers' items + return $ cat contents <> blankline blockToMarkdown opts (DefinitionList items) = do contents <- mapM (definitionListItemToMarkdown opts) items - return $ (vcat contents) <> text "\n" + return $ cat contents <> blankline -- | Convert bullet list item (list of blocks) to markdown. bulletListItemToMarkdown :: WriterOptions -> [Block] -> State WriterState Doc bulletListItemToMarkdown opts items = do contents <- blockListToMarkdown opts items - return $ hang' (text "- ") (writerTabStop opts) contents + let sps = replicate (writerTabStop opts - 2) ' ' + let start = text ('-' : ' ' : sps) + return $ hang (writerTabStop opts) start $ contents <> cr -- | Convert ordered list item (a list of blocks) to markdown. orderedListItemToMarkdown :: WriterOptions -- ^ options @@ -306,8 +313,11 @@ orderedListItemToMarkdown :: WriterOptions -- ^ options -> State WriterState Doc orderedListItemToMarkdown opts marker items = do contents <- blockListToMarkdown opts items - return $ hsep [nest (min (3 - length marker) 0) (text marker), - nest (writerTabStop opts) contents] + let sps = case length marker - writerTabStop opts of + n | n > 0 -> text $ replicate n ' ' + _ -> text " " + let start = text marker <> sps + return $ hang (writerTabStop opts) start $ contents <> cr -- | Convert definition list item (label, list of blocks) to markdown. definitionListItemToMarkdown :: WriterOptions @@ -317,17 +327,20 @@ definitionListItemToMarkdown opts (label, defs) = do labelText <- inlineListToMarkdown opts label let tabStop = writerTabStop opts st <- get - let leader = if stPlain st then empty else text " ~" - contents <- liftM vcat $ - mapM (liftM ((leader $$) . nest tabStop . vcat) . mapM (blockToMarkdown opts)) defs - return $ labelText $+$ contents + let leader = if stPlain st then " " else " ~" + let sps = case writerTabStop opts - 3 of + n | n > 0 -> text $ replicate n ' ' + _ -> text " " + defs' <- mapM (mapM (blockToMarkdown opts)) defs + let contents = vcat $ map (\d -> hang tabStop (leader <> sps) $ vcat d <> cr) defs' + return $ labelText <> cr <> contents <> cr -- | Convert list of Pandoc block elements to markdown. blockListToMarkdown :: WriterOptions -- ^ Options -> [Block] -- ^ List of block elements -> State WriterState Doc blockListToMarkdown opts blocks = - mapM (blockToMarkdown opts) blocks >>= return . vcat + mapM (blockToMarkdown opts) blocks >>= return . cat -- | Get reference for target; if none exists, create unique one and return. -- Prefer label if possible; otherwise, generate a unique key. @@ -350,38 +363,43 @@ getReference label (src, tit) = do -- | Convert list of Pandoc inline elements to markdown. inlineListToMarkdown :: WriterOptions -> [Inline] -> State WriterState Doc inlineListToMarkdown opts lst = - mapM (inlineToMarkdown opts) lst >>= return . hcat + mapM (inlineToMarkdown opts) lst >>= return . cat + +escapeSpaces :: Inline -> Inline +escapeSpaces (Str s) = Str $ substitute " " "\\ " s +escapeSpaces Space = Str "\\ " +escapeSpaces x = x -- | Convert Pandoc inline element to markdown. inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc inlineToMarkdown opts (Emph lst) = do contents <- inlineListToMarkdown opts lst - return $ char '*' <> contents <> char '*' + return $ "*" <> contents <> "*" inlineToMarkdown opts (Strong lst) = do contents <- inlineListToMarkdown opts lst - return $ text "**" <> contents <> text "**" + return $ "**" <> contents <> "**" inlineToMarkdown opts (Strikeout lst) = do contents <- inlineListToMarkdown opts lst - return $ text "~~" <> contents <> text "~~" + return $ "~~" <> contents <> "~~" inlineToMarkdown opts (Superscript lst) = do - contents <- inlineListToMarkdown opts lst - let contents' = text $ substitute " " "\\ " $ render contents - return $ char '^' <> contents' <> char '^' + let lst' = processWith escapeSpaces lst + contents <- inlineListToMarkdown opts lst' + return $ "^" <> contents <> "^" inlineToMarkdown opts (Subscript lst) = do - contents <- inlineListToMarkdown opts lst - let contents' = text $ substitute " " "\\ " $ render contents - return $ char '~' <> contents' <> char '~' + let lst' = processWith escapeSpaces lst + contents <- inlineListToMarkdown opts lst' + return $ "~" <> contents <> "~" inlineToMarkdown opts (SmallCaps lst) = inlineListToMarkdown opts lst inlineToMarkdown opts (Quoted SingleQuote lst) = do contents <- inlineListToMarkdown opts lst - return $ char '‘' <> contents <> char '’' + return $ "‘" <> contents <> "’" inlineToMarkdown opts (Quoted DoubleQuote lst) = do contents <- inlineListToMarkdown opts lst - return $ char '“' <> contents <> char '”' -inlineToMarkdown _ EmDash = return $ char '\8212' -inlineToMarkdown _ EnDash = return $ char '\8211' -inlineToMarkdown _ Apostrophe = return $ char '\8217' -inlineToMarkdown _ Ellipses = return $ char '\8230' + return $ "“" <> contents <> "”" +inlineToMarkdown _ EmDash = return "\8212" +inlineToMarkdown _ EnDash = return "\8211" +inlineToMarkdown _ Apostrophe = return "\8217" +inlineToMarkdown _ Ellipses = return "\8230" inlineToMarkdown _ (Code str) = let tickGroups = filter (\s -> '`' `elem` s) $ group str longest = if null tickGroups @@ -395,25 +413,27 @@ inlineToMarkdown _ (Str str) = do if stPlain st then return $ text str else return $ text $ escapeString str -inlineToMarkdown _ (Math InlineMath str) = return $ char '$' <> text str <> char '$' -inlineToMarkdown _ (Math DisplayMath str) = return $ text "$$" <> text str <> text "$$" +inlineToMarkdown _ (Math InlineMath str) = + return $ "$" <> text str <> "$" +inlineToMarkdown _ (Math DisplayMath str) = + return $ "$$" <> text str <> "$$" inlineToMarkdown _ (TeX str) = return $ text str inlineToMarkdown _ (HtmlInline str) = return $ text str -inlineToMarkdown _ (LineBreak) = return $ text " \n" -inlineToMarkdown _ Space = return $ char ' ' +inlineToMarkdown _ (LineBreak) = return $ " " <> cr +inlineToMarkdown _ Space = return space inlineToMarkdown opts (Cite (c:cs) lst) | writerCiteMethod opts == Citeproc = inlineListToMarkdown opts lst | citationMode c == AuthorInText = do suffs <- inlineListToMarkdown opts $ citationSuffix c rest <- mapM convertOne cs let inbr = suffs <+> joincits rest - br = if isEmpty inbr then empty else brackets inbr + br = if isEmpty inbr then empty else char '[' <> inbr <> char ']' return $ text ("@" ++ citationId c) <+> br | otherwise = do cits <- mapM convertOne (c:cs) return $ text "[" <> joincits cits <> text "]" where - joincits = hcat . punctuate (text "; ") . filter (not . isEmpty) + joincits = hcat . intersperse (text "; ") . filter (not . isEmpty) convertOne Citation { citationId = k , citationPrefix = pinlines , citationSuffix = sinlines @@ -431,7 +451,9 @@ inlineToMarkdown opts (Cite (c:cs) lst) inlineToMarkdown _ (Cite _ _) = return $ text "" inlineToMarkdown opts (Link txt (src', tit)) = do linktext <- inlineListToMarkdown opts txt - let linktitle = if null tit then empty else text $ " \"" ++ tit ++ "\"" + let linktitle = if null tit + then empty + else text $ " \"" ++ tit ++ "\"" let src = unescapeURI src' let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src let useRefLinks = writerReferenceLinks opts @@ -439,24 +461,24 @@ inlineToMarkdown opts (Link txt (src', tit)) = do ref <- if useRefLinks then getReference txt (src, tit) else return [] reftext <- inlineListToMarkdown opts ref return $ if useAuto - then char '<' <> text srcSuffix <> char '>' + then "<" <> text srcSuffix <> ">" else if useRefLinks - then let first = char '[' <> linktext <> char ']' + then let first = "[" <> linktext <> "]" second = if txt == ref - then text "[]" - else char '[' <> reftext <> char ']' + then "[]" + else "[" <> reftext <> "]" in first <> second - else char '[' <> linktext <> char ']' <> - char '(' <> text src <> linktitle <> char ')' + else "[" <> linktext <> "](" <> + text src <> linktitle <> ")" inlineToMarkdown opts (Image alternate (source, tit)) = do let txt = if (null alternate) || (alternate == [Str ""]) || (alternate == [Str source]) -- to prevent autolinks then [Str "image"] else alternate linkPart <- inlineToMarkdown opts (Link txt (unescapeURI source, tit)) - return $ char '!' <> linkPart + return $ "!" <> linkPart inlineToMarkdown _ (Note contents) = do modify (\st -> st{ stNotes = contents : stNotes st }) st <- get let ref = show $ (length $ stNotes st) - return $ text "[^" <> text ref <> char ']' + return $ "[^" <> text ref <> "]" diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 862628f9d..59f7e14f5 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2006-2010 Puneeth Chaganti <punchagan@gmail.com> @@ -32,10 +33,9 @@ Org-Mode: <http://orgmode.org> module Text.Pandoc.Writers.Org ( writeOrg) where import Text.Pandoc.Definition import Text.Pandoc.Shared -import Text.Pandoc.Blocks +import Text.Pandoc.Pretty import Text.Pandoc.Templates (renderTemplate) import Data.List ( intersect, intersperse, transpose ) -import Text.PrettyPrint.HughesPJ hiding ( Str ) import Control.Monad.State import Control.Applicative ( (<$>) ) @@ -66,13 +66,16 @@ pandocToOrg (Pandoc (Meta tit auth dat) blocks) = do notes <- liftM (reverse . stNotes) get >>= notesToOrg -- note that the notes may contain refs, so we do them first hasMath <- liftM stHasMath get - let main = render $ foldl ($+$) empty $ [body, notes] + let colwidth = if writerWrapText opts + then Just $ writerColumns opts + else Nothing + let main = render colwidth $ foldl ($+$) empty $ [body, notes] let context = writerVariables opts ++ [ ("body", main) - , ("title", render title) - , ("date", render date) ] ++ + , ("title", render Nothing title) + , ("date", render Nothing date) ] ++ [ ("math", "yes") | hasMath ] ++ - [ ("author", render a) | a <- authors ] + [ ("author", render Nothing a) | a <- authors ] if writerStandalone opts then return $ renderTemplate context $ writerTemplate opts else return main @@ -81,22 +84,14 @@ pandocToOrg (Pandoc (Meta tit auth dat) blocks) = do notesToOrg :: [[Block]] -> State WriterState Doc notesToOrg notes = mapM (\(num, note) -> noteToOrg num note) (zip [1..] notes) >>= - return . vcat + return . vsep -- | Return Org representation of a note. noteToOrg :: Int -> [Block] -> State WriterState Doc noteToOrg num note = do contents <- blockListToOrg note - let marker = text "[" <> text (show num) <> text "] " - return $ marker <> contents - --- | Take list of inline elements and return wrapped doc. -wrappedOrg :: WriterOptions -> [Inline] -> State WriterState Doc -wrappedOrg opts inlines = do - lineBreakDoc <- inlineToOrg LineBreak - chunks <- mapM (wrapIfNeeded opts inlineListToOrg) - (splitBy LineBreak inlines) - return $ vcat $ intersperse lineBreakDoc chunks + let marker = "[" ++ show num ++ "] " + return $ hang (length marker) (text marker) contents -- | Escape special characters for Org. escapeString :: String -> String @@ -106,32 +101,28 @@ titleToOrg :: [Inline] -> State WriterState Doc titleToOrg [] = return empty titleToOrg lst = do contents <- inlineListToOrg lst - let titleName = text "#+TITLE: " - return $ titleName <> contents + return $ "#+TITLE: " <> contents -- | Convert Pandoc block element to Org. blockToOrg :: Block -- ^ Block element -> State WriterState Doc blockToOrg Null = return empty -blockToOrg (Plain inlines) = do - opts <- get >>= (return . stOptions) - wrappedOrg opts inlines +blockToOrg (Plain inlines) = inlineListToOrg inlines blockToOrg (Para [Image txt (src,tit)]) = do capt <- inlineListToOrg txt img <- inlineToOrg (Image txt (src,tit)) - return $ text "#+CAPTION: " <> capt <> text "\n" $$ img + return $ "#+CAPTION: " <> capt <> blankline <> img blockToOrg (Para inlines) = do - opts <- get >>= (return . stOptions) - contents <- wrappedOrg opts inlines - return $ contents <> text "\n" + contents <- inlineListToOrg inlines + return $ contents <> blankline blockToOrg (RawHtml str) = - return $ (text "\n#+BEGIN_HTML\n") $$ (nest 2 $ vcat $ map text (lines str)) - $$ (text "\n#+END_HTML\n") -blockToOrg HorizontalRule = return $ text "--------------\n" + return $ blankline $$ "#+BEGIN_HTML" $$ + nest 2 (text str) $$ "#+END_HTML" $$ blankline +blockToOrg HorizontalRule = return $ blankline $$ "--------------" $$ blankline blockToOrg (Header level inlines) = do contents <- inlineListToOrg inlines let headerStr = text $ if level > 999 then " " else replicate level '*' - return $ headerStr <> text " " <> contents <> text "\n" + return $ headerStr <> " " <> contents <> blankline blockToOrg (CodeBlock (_,classes,_) str) = do opts <- stOptions <$> get let tabstop = writerTabStop opts @@ -143,31 +134,30 @@ blockToOrg (CodeBlock (_,classes,_) str) = do let (beg, end) = if null at then ("#+BEGIN_EXAMPLE", "#+END_EXAMPLE") else ("#+BEGIN_SRC" ++ head at, "#+END_SRC") - return $ text beg $+$ (nest tabstop $ vcat $ map text (lines str)) - $+$ text end + return $ text beg $$ nest tabstop (text str) $$ text end $$ blankline blockToOrg (BlockQuote blocks) = do contents <- blockListToOrg blocks - return $ (text "\n#+BEGIN_QUOTE\n") $$ (nest 2 contents) - $$ (text "\n#+END_QUOTE\n") + return $ blankline $$ "#+BEGIN_QUOTE" $$ + nest 2 contents $$ "#+END_QUOTE" $$ blankline blockToOrg (Table caption' _ _ headers rows) = do caption'' <- inlineListToOrg caption' let caption = if null caption' then empty - else (text "#+CAPTION: " <> caption'') + else ("#+CAPTION: " <> caption'') headers' <- mapM blockListToOrg headers rawRows <- mapM (mapM blockListToOrg) rows - let numChars = maximum . map (length . render) + let numChars = maximum . map offset -- FIXME: width is not being used. let widthsInChars = map ((+2) . numChars) $ transpose (headers' : rawRows) -- FIXME: Org doesn't allow blocks with height more than 1. - let hpipeBlocks blocks = hcatBlocks [beg, middle, end] - where height = maximum (map heightOfBlock blocks) - sep' = TextBlock 3 height (replicate height " | ") - beg = TextBlock 2 height (replicate height "| ") - end = TextBlock 2 height (replicate height " |") - middle = hcatBlocks $ intersperse sep' blocks - let makeRow = hpipeBlocks . zipWith docToBlock widthsInChars + let hpipeBlocks blocks = hcat [beg, middle, end] + where h = maximum (map height blocks) + sep' = lblock 3 $ vcat (map text $ replicate h " | ") + beg = lblock 2 $ vcat (map text $ replicate h "| ") + end = lblock 2 $ vcat (map text $ replicate h " |") + middle = hcat $ intersperse sep' blocks + let makeRow = hpipeBlocks . zipWith lblock widthsInChars let head' = makeRow headers' rows' <- mapM (\row -> do cols <- mapM blockListToOrg row return $ makeRow cols) rows @@ -175,34 +165,37 @@ blockToOrg (Table caption' _ _ headers rows) = do (hcat $ intersperse (char ch <> char '+' <> char ch) $ map (\l -> text $ replicate l ch) widthsInChars) <> char ch <> char '|' - let body = vcat $ map blockToDoc rows' + let body = vcat rows' let head'' = if all null headers then empty - else blockToDoc head' $+$ border '-' - return $ head'' $+$ body $$ caption $$ text "" + else head' $$ border '-' + return $ head'' $$ body $$ caption $$ blankline blockToOrg (BulletList items) = do contents <- mapM bulletListItemToOrg items -- ensure that sublists have preceding blank line - return $ text "" $+$ vcat contents <> text "\n" -blockToOrg (OrderedList (start, style', delim) items) = do + return $ blankline $+$ vcat contents $$ blankline +blockToOrg (OrderedList (start, _, delim) items) = do + let delim' = case delim of + TwoParens -> OneParen + x -> x let markers = take (length items) $ orderedListMarkers - (start, style', delim) + (start, Decimal, delim') let maxMarkerLength = maximum $ map length markers let markers' = map (\m -> let s = maxMarkerLength - length m in m ++ replicate s ' ') markers contents <- mapM (\(item, num) -> orderedListItemToOrg item num) $ - zip markers' items + zip markers' items -- ensure that sublists have preceding blank line - return $ text "" $+$ vcat contents <> text "\n" + return $ blankline $$ vcat contents $$ blankline blockToOrg (DefinitionList items) = do contents <- mapM definitionListItemToOrg items - return $ (vcat contents) <> text "\n" + return $ vcat contents $$ blankline -- | Convert bullet list item (list of blocks) to Org. bulletListItemToOrg :: [Block] -> State WriterState Doc bulletListItemToOrg items = do contents <- blockListToOrg items - return $ (text "- ") <> contents + return $ hang 3 "- " (contents <> cr) -- | Convert ordered list item (a list of blocks) to Org. orderedListItemToOrg :: String -- ^ marker for list item @@ -210,14 +203,14 @@ orderedListItemToOrg :: String -- ^ marker for list item -> State WriterState Doc orderedListItemToOrg marker items = do contents <- blockListToOrg items - return $ (text marker <> char ' ') <> contents + return $ hang (length marker + 1) (text marker <> space) (contents <> cr) -- | Convert defintion list item (label, list of blocks) to Org. definitionListItemToOrg :: ([Inline], [[Block]]) -> State WriterState Doc definitionListItemToOrg (label, defs) = do label' <- inlineListToOrg label contents <- liftM vcat $ mapM blockListToOrg defs - return $ (text "- ") <> label' <> (text " :: ") <> contents + return $ hang 3 "- " $ label' <> " :: " <> (contents <> cr) -- | Convert list of Pandoc block elements to Org. blockListToOrg :: [Block] -- ^ List of block elements @@ -232,60 +225,57 @@ inlineListToOrg lst = mapM inlineToOrg lst >>= return . hcat inlineToOrg :: Inline -> State WriterState Doc inlineToOrg (Emph lst) = do contents <- inlineListToOrg lst - return $ char '/' <> contents <> char '/' + return $ "/" <> contents <> "/" inlineToOrg (Strong lst) = do contents <- inlineListToOrg lst - return $ text "*" <> contents <> text "*" + return $ "*" <> contents <> "*" inlineToOrg (Strikeout lst) = do contents <- inlineListToOrg lst - return $ text "+" <> contents <> char '+' + return $ "+" <> contents <> "+" inlineToOrg (Superscript lst) = do contents <- inlineListToOrg lst - return $ text "^{" <> contents <> text "}" + return $ "^{" <> contents <> "}" inlineToOrg (Subscript lst) = do contents <- inlineListToOrg lst - return $ text "_{" <> contents <> text "}" + return $ "_{" <> contents <> "}" inlineToOrg (SmallCaps lst) = inlineListToOrg lst inlineToOrg (Quoted SingleQuote lst) = do contents <- inlineListToOrg lst - return $ char '\'' <> contents <> char '\'' + return $ "'" <> contents <> "'" inlineToOrg (Quoted DoubleQuote lst) = do contents <- inlineListToOrg lst - return $ char '\"' <> contents <> char '\"' -inlineToOrg (Cite _ lst) = - inlineListToOrg lst -inlineToOrg EmDash = return $ text "---" -inlineToOrg EnDash = return $ text "--" -inlineToOrg Apostrophe = return $ char '\'' -inlineToOrg Ellipses = return $ text "..." -inlineToOrg (Code str) = return $ text $ "=" ++ str ++ "=" + return $ "\"" <> contents <> "\"" +inlineToOrg (Cite _ lst) = inlineListToOrg lst +inlineToOrg EmDash = return "---" +inlineToOrg EnDash = return "--" +inlineToOrg Apostrophe = return "'" +inlineToOrg Ellipses = return "..." +inlineToOrg (Code str) = return $ "=" <> text str <> "=" inlineToOrg (Str str) = return $ text $ escapeString str inlineToOrg (Math t str) = do modify $ \st -> st{ stHasMath = True } return $ if t == InlineMath - then text $ "$" ++ str ++ "$" - else text $ "$$" ++ str ++ "$$" + then "$" <> text str <> "$" + else "$$" <> text str <> "$$" inlineToOrg (TeX str) = return $ text str inlineToOrg (HtmlInline _) = return empty -inlineToOrg (LineBreak) = do - return $ empty -- there's no line break in Org -inlineToOrg Space = return $ char ' ' +inlineToOrg (LineBreak) = return cr -- there's no line break in Org +inlineToOrg Space = return space inlineToOrg (Link txt (src, _)) = do case txt of [Code x] | x == src -> -- autolink do modify $ \s -> s{ stLinks = True } - return $ text $ "[[" ++ x ++ "]]" + return $ "[[" <> text x <> "]]" _ -> do contents <- inlineListToOrg txt modify $ \s -> s{ stLinks = True } - return $ text ("[[" ++ src ++ "][") <> contents <> - (text "]]") + return $ "[[" <> text src <> "][" <> contents <> "]]" inlineToOrg (Image _ (source', _)) = do let source = unescapeURI source' modify $ \s -> s{ stImages = True } - return $ text $ "[[" ++ source ++ "]]" + return $ "[[" <> text source <> "]]" inlineToOrg (Note contents) = do -- add to notes in state notes <- get >>= (return . stNotes) modify $ \st -> st { stNotes = contents:notes } let ref = show $ (length notes) + 1 - return $ text " [" <> text ref <> text "]" + return $ " [" <> text ref <> "]" diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index e79f97b33..908549041 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE OverloadedStrings #-} {- Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu> @@ -32,10 +33,9 @@ reStructuredText: <http://docutils.sourceforge.net/rst.html> module Text.Pandoc.Writers.RST ( writeRST) where import Text.Pandoc.Definition import Text.Pandoc.Shared -import Text.Pandoc.Blocks import Text.Pandoc.Templates (renderTemplate) -import Data.List ( isPrefixOf, isSuffixOf, intersperse, transpose ) -import Text.PrettyPrint.HughesPJ hiding ( Str ) +import Data.List ( isPrefixOf, intersperse, transpose ) +import Text.Pandoc.Pretty import Control.Monad.State import Control.Applicative ( (<$>) ) @@ -70,13 +70,16 @@ pandocToRST (Pandoc (Meta tit auth dat) blocks) = do refs <- liftM (reverse . stLinks) get >>= refsToRST pics <- liftM (reverse . stImages) get >>= pictRefsToRST hasMath <- liftM stHasMath get - let main = render $ foldl ($+$) empty $ [body, notes, refs, pics] + let colwidth = if writerWrapText opts + then Just $ writerColumns opts + else Nothing + let main = render colwidth $ foldl ($+$) empty $ [body, notes, refs, pics] let context = writerVariables opts ++ [ ("body", main) - , ("title", render title) - , ("date", render date) ] ++ + , ("title", render Nothing title) + , ("date", render colwidth date) ] ++ [ ("math", "yes") | hasMath ] ++ - [ ("author", render a) | a <- authors ] + [ ("author", render colwidth a) | a <- authors ] if writerStandalone opts then return $ renderTemplate context $ writerTemplate opts else return main @@ -84,49 +87,40 @@ pandocToRST (Pandoc (Meta tit auth dat) blocks) = do -- | Return RST representation of reference key table. refsToRST :: Refs -> State WriterState Doc refsToRST refs = mapM keyToRST refs >>= return . vcat - + -- | Return RST representation of a reference key. keyToRST :: ([Inline], (String, String)) -> State WriterState Doc keyToRST (label, (src, _)) = do label' <- inlineListToRST label - let label'' = if ':' `elem` (render label') + let label'' = if ':' `elem` (render Nothing label') then char '`' <> label' <> char '`' else label' - return $ text ".. _" <> label'' <> text ": " <> text src + return $ ".. _" <> label'' <> ": " <> text src -- | Return RST representation of notes. notesToRST :: [[Block]] -> State WriterState Doc notesToRST notes = - mapM (\(num, note) -> noteToRST num note) (zip [1..] notes) >>= - return . vcat + mapM (\(num, note) -> noteToRST num note) (zip [1..] notes) >>= + return . vsep -- | Return RST representation of a note. noteToRST :: Int -> [Block] -> State WriterState Doc noteToRST num note = do contents <- blockListToRST note - let marker = text ".. [" <> text (show num) <> text "]" + let marker = ".. [" <> text (show num) <> "]" return $ marker $$ nest 3 contents -- | Return RST representation of picture reference table. pictRefsToRST :: Refs -> State WriterState Doc pictRefsToRST refs = mapM pictToRST refs >>= return . vcat - + -- | Return RST representation of a picture substitution reference. pictToRST :: ([Inline], (String, String)) -> State WriterState Doc pictToRST (label, (src, _)) = do label' <- inlineListToRST label - return $ text ".. " <> char '|' <> label' <> char '|' <> text " image:: " <> - text src - --- | Take list of inline elements and return wrapped doc. -wrappedRST :: WriterOptions -> [Inline] -> State WriterState Doc -wrappedRST opts inlines = do - lineBreakDoc <- inlineToRST LineBreak - chunks <- mapM (wrapIfNeeded opts inlineListToRST) - (splitBy LineBreak inlines) - return $ vcat $ intersperse lineBreakDoc chunks + return $ ".. |" <> label' <> "| image:: " <> text src -- | Escape special characters for RST. escapeString :: String -> String @@ -136,69 +130,66 @@ titleToRST :: [Inline] -> State WriterState Doc titleToRST [] = return empty titleToRST lst = do contents <- inlineListToRST lst - let titleLength = length $ render contents + let titleLength = length $ (render Nothing contents :: String) let border = text (replicate titleLength '=') - return $ border $+$ contents $+$ border + return $ border $$ contents $$ border -- | Convert Pandoc block element to RST. blockToRST :: Block -- ^ Block element -> State WriterState Doc blockToRST Null = return empty -blockToRST (Plain inlines) = do - opts <- get >>= (return . stOptions) - wrappedRST opts inlines +blockToRST (Plain inlines) = inlineListToRST inlines blockToRST (Para [Image txt (src,tit)]) = do capt <- inlineListToRST txt - let fig = text "figure:: " <> text src - let align = text ":align: center" - let alt = text ":alt: " <> if null tit then capt else text tit - return $ (text ".. " <> (fig $$ align $$ alt $$ text "" $$ capt)) $$ text "" + let fig = "figure:: " <> text src + let align = ":align: center" + let alt = ":alt: " <> if null tit then capt else text tit + return $ hang 3 ".. " $ fig $$ align $$ alt $+$ capt $$ blankline blockToRST (Para inlines) = do - opts <- get >>= (return . stOptions) - contents <- wrappedRST opts inlines - return $ contents <> text "\n" -blockToRST (RawHtml str) = - let str' = if "\n" `isSuffixOf` str then str ++ "\n" else str ++ "\n\n" in - return $ (text "\n.. raw:: html\n") $$ (nest 3 $ vcat $ map text (lines str')) -blockToRST HorizontalRule = return $ text "--------------\n" + contents <- inlineListToRST inlines + return $ contents <> blankline +blockToRST (RawHtml str) = + return $ blankline <> ".. raw:: html" $+$ + (nest 3 $ text str) <> blankline +blockToRST HorizontalRule = + return $ blankline $$ "--------------" $$ blankline blockToRST (Header level inlines) = do contents <- inlineListToRST inlines - let headerLength = length $ render contents let headerChar = if level > 5 then ' ' else "=-~^'" !! (level - 1) - let border = text $ replicate headerLength headerChar - return $ contents $+$ border <> text "\n" + let border = text $ replicate (offset contents) headerChar + return $ contents $$ border $$ blankline blockToRST (CodeBlock (_,classes,_) str) = do opts <- stOptions <$> get let tabstop = writerTabStop opts if "haskell" `elem` classes && "literate" `elem` classes && writerLiterateHaskell opts - then return $ (vcat $ map (text "> " <>) $ map text (lines str)) <> text "\n" - else return $ (text "::\n") $+$ - (nest tabstop $ vcat $ map text (lines str)) <> text "\n" + then return $ prefixed "> " $ text str $$ blankline + else return $ "::" $+$ nest tabstop (text str) $$ blankline blockToRST (BlockQuote blocks) = do tabstop <- get >>= (return . writerTabStop . stOptions) contents <- blockListToRST blocks - return $ (nest tabstop contents) <> text "\n" + return $ nest tabstop contents <> blankline blockToRST (Table caption _ widths headers rows) = do caption' <- inlineListToRST caption let caption'' = if null caption then empty - else text "" $+$ (text "Table: " <> caption') + else blankline <> text "Table: " <> caption' headers' <- mapM blockListToRST headers rawRows <- mapM (mapM blockListToRST) rows let isSimple = all (==0) widths && all (all (\bs -> length bs == 1)) rows - let numChars = maximum . map (length . render) + let numChars = maximum . map offset + opts <- get >>= return . stOptions let widthsInChars = if isSimple then map ((+2) . numChars) $ transpose (headers' : rawRows) - else map (floor . (78 *)) widths - let hpipeBlocks blocks = hcatBlocks [beg, middle, end] - where height = maximum (map heightOfBlock blocks) - sep' = TextBlock 3 height (replicate height " | ") - beg = TextBlock 2 height (replicate height "| ") - end = TextBlock 2 height (replicate height " |") - middle = hcatBlocks $ intersperse sep' blocks - let makeRow = hpipeBlocks . zipWith docToBlock widthsInChars + else map (floor . (fromIntegral (writerColumns opts) *)) widths + let hpipeBlocks blocks = hcat [beg, middle, end] + where h = maximum (map height blocks) + sep' = lblock 3 $ vcat (map text $ replicate h " | ") + beg = lblock 2 $ vcat (map text $ replicate h "| ") + end = lblock 2 $ vcat (map text $ replicate h " |") + middle = hcat $ intersperse sep' blocks + let makeRow = hpipeBlocks . zipWith lblock widthsInChars let head' = makeRow headers' rows' <- mapM (\row -> do cols <- mapM blockListToRST row return $ makeRow cols) rows @@ -206,15 +197,15 @@ blockToRST (Table caption _ widths headers rows) = do (hcat $ intersperse (char ch <> char '+' <> char ch) $ map (\l -> text $ replicate l ch) widthsInChars) <> char ch <> char '+' - let body = vcat $ intersperse (border '-') $ map blockToDoc rows' + let body = vcat $ intersperse (border '-') rows' let head'' = if all null headers then empty - else blockToDoc head' $+$ border '=' - return $ border '-' $+$ head'' $+$ body $+$ border '-' $$ caption'' $$ text "" + else head' $$ border '=' + return $ border '-' $$ head'' $$ body $$ border '-' $$ caption'' $$ blankline blockToRST (BulletList items) = do contents <- mapM bulletListItemToRST items -- ensure that sublists have preceding blank line - return $ text "" $+$ vcat contents <> text "\n" + return $ blankline $$ vcat contents $$ blankline blockToRST (OrderedList (start, style', delim) items) = do let markers = if start == 1 && style' == DefaultStyle && delim == DefaultDelim then take (length items) $ repeat "#." @@ -224,18 +215,19 @@ blockToRST (OrderedList (start, style', delim) items) = do let markers' = map (\m -> let s = maxMarkerLength - length m in m ++ replicate s ' ') markers contents <- mapM (\(item, num) -> orderedListItemToRST item num) $ - zip markers' items + zip markers' items -- ensure that sublists have preceding blank line - return $ text "" $+$ vcat contents <> text "\n" + return $ blankline $$ vcat contents $$ blankline blockToRST (DefinitionList items) = do contents <- mapM definitionListItemToRST items - return $ (vcat contents) <> text "\n" + -- ensure that sublists have preceding blank line + return $ blankline $$ vcat contents $$ blankline -- | Convert bullet list item (list of blocks) to RST. bulletListItemToRST :: [Block] -> State WriterState Doc bulletListItemToRST items = do contents <- blockListToRST items - return $ (text "- ") <> contents + return $ hang 3 "- " $ contents <> cr -- | Convert ordered list item (a list of blocks) to RST. orderedListItemToRST :: String -- ^ marker for list item @@ -243,7 +235,8 @@ orderedListItemToRST :: String -- ^ marker for list item -> State WriterState Doc orderedListItemToRST marker items = do contents <- blockListToRST items - return $ (text marker <> char ' ') <> contents + let marker' = marker ++ " " + return $ hang (length marker') (text marker') $ contents <> cr -- | Convert defintion list item (label, list of blocks) to RST. definitionListItemToRST :: ([Inline], [[Block]]) -> State WriterState Doc @@ -251,7 +244,7 @@ definitionListItemToRST (label, defs) = do label' <- inlineListToRST label contents <- liftM vcat $ mapM blockListToRST defs tabstop <- get >>= (return . writerTabStop . stOptions) - return $ label' $+$ nest tabstop contents + return $ label' $$ nest tabstop (contents <> cr) -- | Convert list of Pandoc block elements to RST. blockListToRST :: [Block] -- ^ List of block elements @@ -266,65 +259,64 @@ inlineListToRST lst = mapM inlineToRST lst >>= return . hcat inlineToRST :: Inline -> State WriterState Doc inlineToRST (Emph lst) = do contents <- inlineListToRST lst - return $ char '*' <> contents <> char '*' + return $ "*" <> contents <> "*" inlineToRST (Strong lst) = do contents <- inlineListToRST lst - return $ text "**" <> contents <> text "**" + return $ "**" <> contents <> "**" inlineToRST (Strikeout lst) = do contents <- inlineListToRST lst - return $ text "[STRIKEOUT:" <> contents <> char ']' + return $ "[STRIKEOUT:" <> contents <> "]" inlineToRST (Superscript lst) = do contents <- inlineListToRST lst - return $ text "\\ :sup:`" <> contents <> text "`\\ " + return $ "\\ :sup:`" <> contents <> "`\\ " inlineToRST (Subscript lst) = do contents <- inlineListToRST lst - return $ text "\\ :sub:`" <> contents <> text "`\\ " + return $ "\\ :sub:`" <> contents <> "`\\ " inlineToRST (SmallCaps lst) = inlineListToRST lst inlineToRST (Quoted SingleQuote lst) = do contents <- inlineListToRST lst - return $ char '‘' <> contents <> char '’' + return $ "‘" <> contents <> "’" inlineToRST (Quoted DoubleQuote lst) = do contents <- inlineListToRST lst - return $ char '“' <> contents <> char '”' + return $ "“" <> contents <> "”" inlineToRST (Cite _ lst) = inlineListToRST lst inlineToRST EmDash = return $ char '\8212' inlineToRST EnDash = return $ char '\8211' inlineToRST Apostrophe = return $ char '\8217' inlineToRST Ellipses = return $ char '\8230' -inlineToRST (Code str) = return $ text $ "``" ++ str ++ "``" +inlineToRST (Code str) = return $ "``" <> text str <> "``" inlineToRST (Str str) = return $ text $ escapeString str inlineToRST (Math t str) = do modify $ \st -> st{ stHasMath = True } return $ if t == InlineMath - then text $ ":math:`$" ++ str ++ "$`" - else text $ ":math:`$$" ++ str ++ "$$`" + then ":math:`$" <> text str <> "$`" + else ":math:`$$" <> text str <> "$$`" inlineToRST (TeX _) = return empty inlineToRST (HtmlInline _) = return empty -inlineToRST (LineBreak) = do - return $ empty -- there's no line break in RST -inlineToRST Space = return $ char ' ' +inlineToRST (LineBreak) = return cr -- there's no line break in RST +inlineToRST Space = return space inlineToRST (Link [Code str] (src, _)) | src == str || src == "mailto:" ++ str = do let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src return $ text $ unescapeURI srcSuffix inlineToRST (Link txt (src', tit)) = do let src = unescapeURI src' - useReferenceLinks <- get >>= (return . writerReferenceLinks . stOptions) + useReferenceLinks <- get >>= return . writerReferenceLinks . stOptions linktext <- inlineListToRST $ normalizeSpaces txt if useReferenceLinks - then do refs <- get >>= (return . stLinks) + then do refs <- get >>= return . stLinks let refs' = if (txt, (src, tit)) `elem` refs then refs else (txt, (src, tit)):refs modify $ \st -> st { stLinks = refs' } - return $ char '`' <> linktext <> text "`_" - else return $ char '`' <> linktext <> text " <" <> text src <> text ">`_" + return $ "`" <> linktext <> "`_" + else return $ "`" <> linktext <> " <" <> text src <> ">`_" inlineToRST (Image alternate (source', tit)) = do let source = unescapeURI source' - pics <- get >>= (return . stImages) + pics <- get >>= return . stImages let labelsUsed = map fst pics - let txt = if null alternate || alternate == [Str ""] || + let txt = if null alternate || alternate == [Str ""] || alternate `elem` labelsUsed then [Str $ "image" ++ show (length pics)] else alternate @@ -333,10 +325,10 @@ inlineToRST (Image alternate (source', tit)) = do else (txt, (source, tit)):pics modify $ \st -> st { stImages = pics' } label <- inlineListToRST txt - return $ char '|' <> label <> char '|' + return $ "|" <> label <> "|" inlineToRST (Note contents) = do -- add to notes in state - notes <- get >>= (return . stNotes) + notes <- get >>= return . stNotes modify $ \st -> st { stNotes = contents:notes } let ref = show $ (length notes) + 1 - return $ text " [" <> text ref <> text "]_" + return $ " [" <> text ref <> "]_" diff --git a/src/pandoc.hs b/src/pandoc.hs index df83cdd0b..373919e05 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -36,11 +36,11 @@ import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile, #ifdef _HIGHLIGHTING import Text.Pandoc.Highlighting ( languages ) #endif -import System.Environment ( getArgs, getProgName, getEnvironment ) +import System.Environment ( getArgs, getProgName ) import System.Exit ( exitWith, ExitCode (..) ) import System.FilePath import System.Console.GetOpt -import Data.Char ( toLower, isDigit ) +import Data.Char ( toLower ) import Data.List ( intercalate, isSuffixOf ) import System.Directory ( getAppUserDataDirectory, doesFileExist ) import System.IO ( stdout, stderr ) @@ -111,6 +111,7 @@ data Opt = Opt , optStrict :: Bool -- ^ Use strict markdown syntax , optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , optWrapText :: Bool -- ^ Wrap text + , optColumns :: Int -- ^ Line length in characters , optPlugins :: [Pandoc -> IO Pandoc] -- ^ Plugins to apply , optEmailObfuscation :: ObfuscationMethod , optIdentifierPrefix :: String @@ -150,6 +151,7 @@ defaultOpts = Opt , optStrict = False , optReferenceLinks = False , optWrapText = True + , optColumns = 72 , optPlugins = [] , optEmailObfuscation = JavascriptObfuscation , optIdentifierPrefix = "" @@ -194,8 +196,14 @@ options = , Option "" ["tab-stop"] (ReqArg - (\arg opt -> return opt { optTabStop = (read arg) } ) - "TABSTOP") + (\arg opt -> + case reads arg of + [(t,"")] | t > 0 -> return opt { optTabStop = t } + _ -> do + UTF8.hPutStrLn stderr $ + "tab-stop must be a number greater than 0" + exitWith $ ExitFailure 31) + "NUMBER") "" -- "Tab stop (default 4)" , Option "" ["strict"] @@ -300,6 +308,18 @@ options = (\opt -> return opt { optWrapText = False })) "" -- "Do not wrap text in output" + , Option "" ["columns"] + (ReqArg + (\arg opt -> + case reads arg of + [(t,"")] | t > 0 -> return opt { optColumns = t } + _ -> do + UTF8.hPutStrLn stderr $ + "columns must be a number greater than 0" + exitWith $ ExitFailure 33) + "NUMBER") + "" -- "Length of line in characters" + , Option "" ["email-obfuscation"] (ReqArg (\arg opt -> do @@ -333,17 +353,18 @@ options = , Option "" ["base-header-level"] (ReqArg - (\arg opt -> do - if all isDigit arg && (read arg :: Int) >= 1 - then do - let oldTransforms = optTransforms opt - let shift = read arg - 1 - return opt{ optTransforms = - headerShift shift : oldTransforms } - else do - UTF8.hPutStrLn stderr $ "base-header-level must be a number >= 1" - exitWith $ ExitFailure 19) - "LEVEL") + (\arg opt -> + case reads arg of + [(t,"")] | t > 0 -> do + let oldTransforms = optTransforms opt + let shift = t - 1 + return opt{ optTransforms = + headerShift shift : oldTransforms } + _ -> do + UTF8.hPutStrLn stderr $ + "base-header-level must be a number > 0" + exitWith $ ExitFailure 19) + "NUMBER") "" -- "Headers base level" , Option "" ["template"] @@ -617,6 +638,7 @@ main = do , optStrict = strict , optReferenceLinks = referenceLinks , optWrapText = wrap + , optColumns = columns , optEmailObfuscation = obfuscationMethod , optIdentifierPrefix = idPrefix , optIndentedCodeClasses = codeBlockClasses @@ -668,11 +690,6 @@ main = do Right t -> t Left e -> error (show e) - environment <- getEnvironment - let columns = case lookup "COLUMNS" environment of - Just cols -> read cols - Nothing -> stateColumns defaultParserState - let standalone' = standalone || isNonTextOutput writerName' variables' <- case (writerName', standalone', offline) of @@ -746,6 +763,7 @@ main = do writerStrictMarkdown = strict, writerReferenceLinks = referenceLinks, writerWrapText = wrap, + writerColumns = columns, writerLiterateHaskell = "+lhs" `isSuffixOf` writerName' || lhsExtension [outputFile], writerEmailObfuscation = if strict diff --git a/src/test-pandoc.hs b/src/test-pandoc.hs index b475711d2..173816fb1 100644 --- a/src/test-pandoc.hs +++ b/src/test-pandoc.hs @@ -113,7 +113,7 @@ main = do "testsuite.native" "testsuite.native" r14s <- mapM (\style -> runTest ("markdown reader (citations) (" ++ style ++ ")") ["-r", "markdown", "-w", "markdown", "--bibliography", "biblio.bib", "--csl", style ++ ".csl", "--no-wrap"] "markdown-citations.txt" ("markdown-citations." ++ style ++ ".txt")) ["chicago-author-date","ieee","mhra"] let citopts = ["--bibliography", "biblio.bib", "--csl", "chicago-author-date.csl", "--no-citeproc"] - r15 <- runTest "markdown writer (citations)" (["-r", "markdown", "-w", "markdown"] ++ citopts) + r15 <- runTest "markdown writer (citations)" (["-r", "markdown", "-w", "markdown", "--no-wrap"] ++ citopts) "markdown-citations.txt" "markdown-citations.txt" r16s <- runLatexCitationTests citopts "biblatex" r17s <- runLatexCitationTests citopts "natbib" @@ -159,9 +159,9 @@ runLhsReaderTest format = runLatexCitationTests :: [String] -> String -> IO [Bool] runLatexCitationTests o n - = sequence [ rt ("latex reader (" ++ n ++ " citations)") (["-r", "latex", "-w", "markdown", "-s"] ++ o') + = sequence [ rt ("latex reader (" ++ n ++ " citations)") (["-r", "latex", "-w", "markdown", "-s", "--no-wrap"] ++ o') f "markdown-citations.txt" - , rt ("latex writer (" ++ n ++ " citations)") (["-r", "markdown", "-w", "latex", "-s"] ++ o') + , rt ("latex writer (" ++ n ++ " citations)") (["-r", "markdown", "-w", "latex", "-s", "--no-wrap"] ++ o') "markdown-citations.txt" f ] where @@ -172,8 +172,8 @@ runLatexCitationTests o n runWriterTest :: String -> IO Bool runWriterTest format = do - r1 <- runTest (format ++ " writer") ["-r", "native", "-s", "-w", format] "testsuite.native" ("writer" <.> format) - r2 <- runTest (format ++ " writer (tables)") ["-r", "native", "-w", format] "tables.native" ("tables" <.> format) + r1 <- runTest (format ++ " writer") ["-r", "native", "-s", "-w", format, "--columns=78"] "testsuite.native" ("writer" <.> format) + r2 <- runTest (format ++ " writer (tables)") ["-r", "native", "-w", format, "--columns=78"] "tables.native" ("tables" <.> format) return (r1 && r2) runS5WriterTest :: String -> [String] -> String -> IO Bool @@ -202,9 +202,8 @@ runTestWithNormalize normalize testname opts inp norm = do let inpPath = inp let normPath = norm hFlush stdout - -- Note: COLUMNS must be set for markdown table reader - ph <- runProcess pandocPath (opts ++ [inpPath] ++ ["--data-dir", ".."]) Nothing - (Just [("LANG","en_US.UTF-8"),("COLUMNS", "80"),("HOME", "./")]) Nothing (Just hOut) (Just stderr) + ph <- runProcess pandocPath (["--columns=80"] ++ [inpPath] ++ ["--data-dir", ".."] ++ opts) Nothing + (Just [("LANG","en_US.UTF-8"),("HOME", "./")]) Nothing (Just hOut) (Just stderr) ec <- waitForProcess ph result <- if ec == ExitSuccess then do diff --git a/templates/org.template b/templates/org.template index 303e1aad0..eaaa17533 100644 --- a/templates/org.template +++ b/templates/org.template @@ -2,7 +2,9 @@ $if(title)$ $title$ $endif$ +$if(author)$ #+AUTHOR: $for(author)$$author$$sep$; $endfor$ +$endif$ $if(date)$ #+DATE: $date$ diff --git a/tests/biblatex-citations.latex b/tests/biblatex-citations.latex index 7ac680fa4..c975d5bcb 100644 --- a/tests/biblatex-citations.latex +++ b/tests/biblatex-citations.latex @@ -34,8 +34,7 @@ \textcites{item1}[p.~30]{item2}[see also][]{item3} says blah. \item - In a note.% - \footnote{A citation without locators \autocite{item3}.} + In a note.\footnote{A citation without locators \autocite{item3}.} \item A citation group @@ -45,8 +44,7 @@ Another one \autocite[see][p.~34--35]{item1}. \item - And another one in a note.% - \footnote{Some citations \autocites[see][chap. 3]{item2}{item3}{item1}.} + And another one in a note.\footnote{Some citations \autocites[see][chap. 3]{item2}{item3}{item1}.} \item Citation with a suffix and locator @@ -56,9 +54,7 @@ Citation with suffix only \autocite[and nowhere else]{item1}. \item - Now some modifiers.% - \footnote{Like a citation without author: \autocite*{item1}, and now Doe with -a locator \autocite*[p.~44]{item2}.} + Now some modifiers.\footnote{Like a citation without author: \autocite*{item1}, and now Doe with a locator \autocite*[p.~44]{item2}.} \item With some markup \autocite[\emph{see}][p. \textbf{32}]{item1}. diff --git a/tests/markdown-citations.chicago-author-date.txt b/tests/markdown-citations.chicago-author-date.txt index dd89b786f..93cf6ce7c 100644 --- a/tests/markdown-citations.chicago-author-date.txt +++ b/tests/markdown-citations.chicago-author-date.txt @@ -28,7 +28,6 @@ - With some markup (*see* Doe 2005, 32). - # References Doe, John. 2005. *First Book*. Cambridge: Cambridge University Press. @@ -37,11 +36,8 @@ Doe, John. 2005. *First Book*. Cambridge: Cambridge University Press. Doe, John, and Jenny Roe. 2007. Why Water Is Wet. In *Third Book*, ed. Sam Smith. Oxford: Oxford University Press. -[^1]: - A citation without locators (Doe and Roe 2007). +[^1]: A citation without locators (Doe and Roe 2007). -[^2]: - Some citations (see Doe 2006, chap. 3; Doe and Roe 2007; Doe 2005). +[^2]: Some citations (see Doe 2006, chap. 3; Doe and Roe 2007; Doe 2005). -[^3]: - Like a citation without author: (2005), and now Doe with a locator (2006, 44). +[^3]: Like a citation without author: (2005), and now Doe with a locator (2006, 44). \ No newline at end of file diff --git a/tests/markdown-citations.ieee.txt b/tests/markdown-citations.ieee.txt index 53f0995a4..0fd9335ad 100644 --- a/tests/markdown-citations.ieee.txt +++ b/tests/markdown-citations.ieee.txt @@ -28,7 +28,6 @@ - With some markup [1]. - # References [1] J. Doe, *First Book*, Cambridge: Cambridge University Press, 2005. @@ -37,11 +36,8 @@ [3] J. Doe and J. Roe, “Why Water Is Wet,” *Third Book*, Smith, S., Ed., Oxford: Oxford University Press, 2007. -[^1]: - A citation without locators [3]. +[^1]: A citation without locators [3]. -[^2]: - Some citations [1]-[3]. +[^2]: Some citations [1]-[3]. -[^3]: - Like a citation without author: [1], and now Doe with a locator [2]. +[^3]: Like a citation without author: [1], and now Doe with a locator [2]. diff --git a/tests/markdown-citations.mhra.txt b/tests/markdown-citations.mhra.txt index a05db2a54..3add1cfdd 100644 --- a/tests/markdown-citations.mhra.txt +++ b/tests/markdown-citations.mhra.txt @@ -28,7 +28,6 @@ - With some markup.[^12] - # References Doe, John, ‘Article’, *Journal of Generic Studies*, 6 (2006), 33-34. @@ -37,38 +36,28 @@ Doe, John, ‘Article’, *Journal of Generic Studies*, 6 (2006), 33-34. Doe, John, and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed by Sam Smith (Oxford: Oxford University Press, 2007). -[^1]: - *First Book* (Cambridge: Cambridge University Press, 2005). +[^1]: *First Book* (Cambridge: Cambridge University Press, 2005). -[^2]: - First Book, p. 30. +[^2]: First Book, p. 30. -[^3]: - First Book, p. 30, with suffix. +[^3]: First Book, p. 30, with suffix. -[^4]: - First Book; ‘Article’, *Journal of Generic Studies*, 6 (2006), 33-34 (p. 30); see also John Doe and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed by Sam Smith (Oxford: Oxford University Press, 2007). +[^4]: First Book; ‘Article’, *Journal of Generic Studies*, 6 (2006), 33-34 (p. 30); see also John Doe and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed by Sam Smith (Oxford: Oxford University Press, 2007). -[^5]: - A citation without locators Doe and Roe. +[^5]: A citation without locators Doe and Roe. -[^6]: - See Doe, First Book, pp. 34-35; also Doe and Roe, chap. 3. +[^6]: See Doe, First Book, pp. 34-35; also Doe and Roe, chap. 3. -[^7]: - See Doe, First Book, pp. 34-35. +[^7]: See Doe, First Book, pp. 34-35. -[^8]: - Some citations see Doe, Article, 33-34 (chap. 3); Doe and Roe; Doe, First Book. +[^8]: Some citations see Doe, Article, 33-34 (chap. 3); Doe and Roe; Doe, First Book. -[^9]: - Doe, First Book, pp. 33, 35-37, and nowhere else. +[^9]: Doe, First Book, pp. 33, 35-37, and nowhere else. -[^10]: - Doe, First Book, and nowhere else. +[^10]: Doe, First Book, and nowhere else. -[^11]: - Like a citation without author: First Book, and now Doe with a locator Article, 33-34 (p. 44). +[^11]: Like a citation without author: First Book, and now Doe with a locator Article, 33-34 (p. 44). -[^12]: - *See* Doe, First Book, p. 32. +[^11]: Like a citation without author: First Book, and now Doe with a locator Article, 33-34 (p. 44). + +[^12]: *See* Doe, First Book, p. 32. diff --git a/tests/markdown-citations.txt b/tests/markdown-citations.txt index 0944b1101..0e75e0b90 100644 --- a/tests/markdown-citations.txt +++ b/tests/markdown-citations.txt @@ -20,8 +20,7 @@ - And another one in a note.[^2] -- Citation with a suffix and locator - [@item1 pp. 33, 35-37, and nowhere else]. +- Citation with a suffix and locator [@item1 pp. 33, 35-37, and nowhere else]. - Citation with suffix only [@item1 and nowhere else]. @@ -32,12 +31,9 @@ # References -[^1]: - A citation without locators [@item3]. +[^1]: A citation without locators [@item3]. -[^2]: - Some citations [see @item2 chap. 3; @item3; @item1]. +[^2]: Some citations [see @item2 chap. 3; @item3; @item1]. + +[^3]: Like a citation without author: [-@item1], and now Doe with a locator [-@item2 p. 44]. -[^3]: - Like a citation without author: [-@item1], and now Doe with a - locator [-@item2 p. 44]. diff --git a/tests/natbib-citations.latex b/tests/natbib-citations.latex index 373ccc2e6..2e21f38b1 100644 --- a/tests/natbib-citations.latex +++ b/tests/natbib-citations.latex @@ -31,36 +31,28 @@ \citet[p.~30, with suffix]{item1} says blah. \item - \citeauthor{item1} \citetext{\citeyear{item1}; \citeyear[p.~30]{item2}; \citealp[see also][]{item3}} - says blah. + \citeauthor{item1} \citetext{\citeyear{item1}; \citeyear[p.~30]{item2}; \citealp[see also][]{item3}} says blah. \item - In a note.% - \footnote{A citation without locators \citep{item3}.} + In a note.\footnote{A citation without locators \citep{item3}.} \item - A citation group - \citetext{\citealp[see][p.~34--35]{item1}; \citealp[also][chap. 3]{item3}}. + A citation group \citetext{\citealp[see][p.~34--35]{item1}; \citealp[also][chap. 3]{item3}}. \item Another one \citep[see][p.~34--35]{item1}. \item - And another one in a note.% - \footnote{Some citations -\citetext{\citealp[see][chap. 3]{item2}; \citealp{item3}; \citealp{item1}}.} + And another one in a note.\footnote{Some citations \citetext{\citealp[see][chap. 3]{item2}; \citealp{item3}; \citealp{item1}}.} \item - Citation with a suffix and locator - \citep[pp.~33, 35--37, and nowhere else]{item1}. + Citation with a suffix and locator \citep[pp.~33, 35--37, and nowhere else]{item1}. \item Citation with suffix only \citep[and nowhere else]{item1}. \item - Now some modifiers.% - \footnote{Like a citation without author: \citeyearpar{item1}, and now Doe -with a locator \citeyearpar[p.~44]{item2}.} + Now some modifiers.\footnote{Like a citation without author: \citeyearpar{item1}, and now Doe with a locator \citeyearpar[p.~44]{item2}.} \item With some markup \citep[\emph{see}][p. \textbf{32}]{item1}. diff --git a/tests/tables.markdown b/tests/tables.markdown index 95bcc667e..d1bbf168f 100644 --- a/tests/tables.markdown +++ b/tests/tables.markdown @@ -5,7 +5,7 @@ Simple table with caption: 12 12 12 12 123 123 123 123 1 1 1 1 - + : Demonstration of simple table syntax. Simple table without caption: @@ -23,34 +23,34 @@ Simple table indented two spaces: 12 12 12 12 123 123 123 123 1 1 1 1 - + : Demonstration of simple table syntax. Multiline table with caption: -------------------------------------------------------------- Centered Left Right Default aligned - Header Aligned Aligned + Header Aligned 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. -------------------------------------------------------------- - + : Here's the caption. It may span multiple lines. Multiline table without caption: -------------------------------------------------------------- Centered Left Right Default aligned - Header Aligned Aligned + Header Aligned 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. @@ -69,8 +69,9 @@ 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/tables.plain b/tests/tables.plain index 95bcc667e..d1bbf168f 100644 --- a/tests/tables.plain +++ b/tests/tables.plain @@ -5,7 +5,7 @@ Simple table with caption: 12 12 12 12 123 123 123 123 1 1 1 1 - + : Demonstration of simple table syntax. Simple table without caption: @@ -23,34 +23,34 @@ Simple table indented two spaces: 12 12 12 12 123 123 123 123 1 1 1 1 - + : Demonstration of simple table syntax. Multiline table with caption: -------------------------------------------------------------- Centered Left Right Default aligned - Header Aligned Aligned + Header Aligned 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. -------------------------------------------------------------- - + : Here's the caption. It may span multiple lines. Multiline table without caption: -------------------------------------------------------------- Centered Left Right Default aligned - Header Aligned Aligned + Header Aligned 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. @@ -69,8 +69,9 @@ 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.markdown b/tests/writer.markdown index b417a8fee..992bcd020 100644 --- a/tests/writer.markdown +++ b/tests/writer.markdown @@ -2,9 +2,8 @@ % 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. - +This is a set of tests for pandoc. Most of them are adapted from John Gruber’s +markdown test suite. * * * * * @@ -30,23 +29,21 @@ with no blank line 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. +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 @@ -56,27 +53,26 @@ E-mail style: > This is a block quote. It is pretty short. > Code in a block quote: -> +> > sub status { > print "working"; > } -> +> > A list: -> +> > 1. item one > 2. item two -> +> > Nested block quotes: -> +> > > nested -> +> > > nested This should not be a block quote: 2 \> 1. And a following paragraph. - * * * * * # Code Blocks @@ -84,19 +80,18 @@ And a following paragraph. 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: \$ \\ \> \[ \{ + These should not be escaped: \$ \\ \> \[ \{ * * * * * @@ -118,7 +113,6 @@ Asterisks loose: - asterisk 3 - Pluses tight: - Plus 1 @@ -133,7 +127,6 @@ Pluses loose: - Plus 3 - Minuses tight: - Minus 1 @@ -148,7 +141,6 @@ Minuses loose: - Minus 3 - ## Ordered Tight: @@ -171,7 +163,6 @@ Loose using tabs: 3. Third - and using spaces: 1. One @@ -180,27 +171,22 @@ and using spaces: 3. Three - Multiple paragraphs: 1. 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. 2. Item 2. 3. Item 3. - ## Nested - Tab - Tab - Tab - - Here’s another: 1. First @@ -223,7 +209,6 @@ Same thing but with paragraphs: 3. Third - ## Tabs and spaces - this is a list item indented with tabs @@ -234,8 +219,6 @@ Same thing but with paragraphs: - this is an example list item indented with spaces - - ## Fancy list markers (2) begins with 2 @@ -248,8 +231,6 @@ Same thing but with paragraphs: (A) a subsublist (B) a subsublist - - Nesting: A. Upper Alpha @@ -257,23 +238,18 @@ A. Upper Alpha (6) Decimal start with 6 c) Lower alpha with paren - - - Autonumbering: 1. Autonumber. 2. More. 1. Nested. - Should not be a list item: M.A. 2007 B. Williams - * * * * * # Definition Lists @@ -307,7 +283,6 @@ orange banana ~ yellow fruit - Multiple blocks with italics: *apple* @@ -322,7 +297,6 @@ Multiple blocks with italics: > orange block quote - Multiple definitions, tight: apple @@ -344,7 +318,6 @@ orange ~ bank - Blank line after term, indented marker, alternate markers: apple @@ -358,7 +331,6 @@ orange 1. sublist 2. sublist - # HTML Blocks Simple block on one line: @@ -470,7 +442,6 @@ Hr’s: <hr class="foo" id="bar"> - * * * * * # Inline Markup @@ -497,9 +468,8 @@ Superscripts: a^bc^d a^*hello*^ a^hello there^. Subscripts: H~2~O, H~23~O, H~many of them~O. -These should not be superscripts or subscripts, because of the -unescaped spaces: a\^b c\^d, a\~b c\~d. - +These should not be superscripts or subscripts, because of the unescaped +spaces: a\^b c\^d, a\~b c\~d. * * * * * @@ -513,8 +483,8 @@ unescaped spaces: a\^b c\^d, a\~b c\~d. ‘He said, “I want to go.”’ Were you alive in the 70’s? -Here is some quoted ‘`code`’ and a -“[quoted link](http://example.com/?foo=1&bar=2)”. +Here is some quoted ‘`code`’ and a “[quoted +link](http://example.com/?foo=1&bar=2)”. Some dashes: one—two — three—four — five. @@ -522,7 +492,6 @@ Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. - * * * * * # LaTeX @@ -535,14 +504,13 @@ Ellipses…and…and…. - $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: - $\alpha + \omega \times x^2$. +- Here’s one that has a line break in it: $\alpha + \omega \times x^2$. 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.) +- $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$. @@ -554,7 +522,6 @@ Dog & 2 \\ Cat & 1 \\ \hline \end{tabular} - * * * * * # Special Characters @@ -609,7 +576,6 @@ Plus: + Minus: - - * * * * * # Links @@ -662,8 +628,7 @@ Foo [biz](/url/ "Title with "quote" inside"). ## With ampersands -Here’s a -[link with an ampersand in the URL](http://example.com/?foo=1&bar=2). +Here’s a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). Here’s a link with an amersand in the link text: [AT&T](http://att.com/ "AT&T"). @@ -688,7 +653,6 @@ Auto-links should not occur here: `<http://example.com/>` or here: <http://example.com/> - * * * * * # Images @@ -699,44 +663,37 @@ From “Voyage dans la Lune” by Georges Melies (1902): Here is a movie  icon. - * * * * * # Footnotes -Here is a footnote reference,[^1] and another.[^2] This should -*not* be a footnote reference, because it contains a space.[\^my -note] Here is an inline note.[^3] +Here is a footnote reference,[^1] and another.[^2] This should *not* be a +footnote reference, because it contains a space.[\^my note] Here is an inline +note.[^3] > Notes can go in quotes.[^4] 1. And in list items.[^5] -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. -[^1]: - Here is the footnote. It can go anywhere after the footnote - reference. It need not be placed at the end of the document. +[^1]: Here is the footnote. It can go anywhere after the footnote reference. + It need not be placed at the end of the document. -[^2]: - Here’s the long note. This one contains multiple blocks. +[^2]: 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). { <code> } - If you want, you can indent every line, but you can also be lazy - and just indent the first line of each block. + If you want, you can indent every line, but you can also be lazy and just + indent the first line of each block. -[^3]: - This is *easier* to type. Inline notes may contain +[^3]: This is *easier* to type. Inline notes may contain [links](http://google.com) and `]` verbatim characters, as well as [bracketed text]. -[^4]: - In quote. +[^4]: In quote. -[^5]: - In list. +[^5]: In list. diff --git a/tests/writer.org b/tests/writer.org index 59f27acfc..642b2a3ef 100644 --- a/tests/writer.org +++ b/tests/writer.org @@ -3,8 +3,8 @@ #+AUTHOR: John MacFarlane; Anonymous #+DATE: July 17, 2006 -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. -------------- @@ -36,9 +36,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. @@ -51,17 +51,11 @@ here. E-mail style: - #+BEGIN_QUOTE - This is a block quote. It is pretty short. - - #+END_QUOTE - #+BEGIN_QUOTE - Code in a block quote: #+BEGIN_EXAMPLE @@ -69,31 +63,21 @@ E-mail style: print "working"; } #+END_EXAMPLE + A list: - 1. item one 2. item two Nested block quotes: - -#+BEGIN_QUOTE - + #+BEGIN_QUOTE nested + #+END_QUOTE - -#+END_QUOTE - - -#+BEGIN_QUOTE - + #+BEGIN_QUOTE nested - - -#+END_QUOTE - - + #+END_QUOTE #+END_QUOTE This should not be a block quote: 2 > 1. @@ -108,20 +92,22 @@ Code: #+BEGIN_EXAMPLE ---- (should be four hyphens) - + sub status { print "working"; } - + this code block is indented by one tab #+END_EXAMPLE + And: #+BEGIN_EXAMPLE this code block is indented by two tabs - + These should not be escaped: \$ \\ \> \[ \{ #+END_EXAMPLE + -------------- * Lists @@ -130,121 +116,99 @@ And: 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: - 1. First 2. Second 3. Third and: - 1. One 2. Two 3. Three Loose using tabs: - 1. First 2. Second 3. Third - and using spaces: - 1. One 2. Two 3. Three - Multiple paragraphs: - 1. 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. 2. Item 2. 3. Item 3. - ** Nested - - Tab - + - Tab - + - Tab - - Here's another: - 1. First 2. Second: - + - Fee - Fie - Foe @@ -253,72 +217,55 @@ Here's another: Same thing but with paragraphs: - 1. First 2. Second: - - Fee - Fie - Foe 3. 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 +2) begins with 2 +3) and now 3 -(2) begins with 2 -(3) and now 3 - - with a continuation - - - iv. sublist with roman numerals, starting with 4 - v. more items - - (A) a subsublist - (B) a subsublist + with a continuation + 4. sublist with roman numerals, starting with 4 + 5. more items + 1) a subsublist + 2) a subsublist Nesting: +1. Upper Alpha -A. Upper Alpha - - I. Upper Roman. - - (6) Decimal start with 6 - - c) Lower alpha with paren - + 1. Upper Roman. + 6) Decimal start with 6 + 3) Lower alpha with paren Autonumbering: - 1. Autonumber. 2. More. - - 1. Nested. + 1. Nested. Should not be a list item: @@ -350,155 +297,123 @@ Loose: - banana :: yellow fruit - Multiple blocks with italics: - /apple/ :: red fruit - contains seeds, crisp, pleasant to taste + contains seeds, crisp, pleasant to taste - /orange/ :: orange fruit - #+BEGIN_EXAMPLE - { orange code block } - #+END_EXAMPLE - -#+BEGIN_QUOTE - - orange block quote - - -#+END_QUOTE + #+BEGIN_EXAMPLE + { orange code block } + #+END_EXAMPLE + #+BEGIN_QUOTE + orange block quote + #+END_QUOTE Multiple definitions, tight: - apple :: red fruit - computer + computer - orange :: orange fruit - bank + bank Multiple definitions, loose: - apple :: red fruit - computer + computer - orange :: orange fruit - bank - + bank Blank line after term, indented marker, alternate markers: - apple :: red fruit - computer + computer - orange :: orange fruit - - 1. sublist - 2. sublist - + 1. sublist + 2. sublist * HTML Blocks Simple block on one line: - #+BEGIN_HTML - <div> - #+END_HTML foo #+BEGIN_HTML - </div> - #+END_HTML And nested without indentation: - #+BEGIN_HTML - <div> <div> <div> - #+END_HTML foo #+BEGIN_HTML - </div> </div> <div> - #+END_HTML bar #+BEGIN_HTML - </div> </div> - #+END_HTML Interpreted markdown in a table: - #+BEGIN_HTML - <table> <tr> <td> - #+END_HTML This is /emphasized/ #+BEGIN_HTML - </td> <td> - #+END_HTML And this is *strong* #+BEGIN_HTML - </td> </tr> </table> - - <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> + <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> #+END_HTML Here's a simple block: - #+BEGIN_HTML - <div> - #+END_HTML foo #+BEGIN_HTML - </div> - #+END_HTML This should be a code block, though: @@ -508,56 +423,47 @@ This should be a code block, though: foo </div> #+END_EXAMPLE + As should this: #+BEGIN_EXAMPLE <div>foo</div> #+END_EXAMPLE + Now, nested: - #+BEGIN_HTML - <div> <div> <div> - #+END_HTML foo #+BEGIN_HTML - </div> </div> </div> - #+END_HTML This should just be an HTML comment: - #+BEGIN_HTML - <!-- Comment --> - #+END_HTML Multiline: - #+BEGIN_HTML - <!-- Blah Blah --> - + <!-- This is another comment. --> - #+END_HTML Code block: @@ -565,13 +471,11 @@ Code block: #+BEGIN_EXAMPLE <!-- Comment --> #+END_EXAMPLE + Just plain comment, with trailing spaces on the line: - #+BEGIN_HTML - <!-- foo --> - #+END_HTML Code: @@ -579,29 +483,27 @@ Code: #+BEGIN_EXAMPLE <hr /> #+END_EXAMPLE + Hr's: - #+BEGIN_HTML - <hr> - - <hr /> - - <hr /> - - <hr> - - <hr /> - - <hr /> - - <hr class="foo" id="bar" /> - - <hr class="foo" id="bar" /> - - <hr class="foo" id="bar"> + <hr /> + + <hr /> + + <hr> + + <hr /> + + <hr /> + + <hr class="foo" id="bar" /> + + <hr class="foo" id="bar" /> + + <hr class="foo" id="bar"> #+END_HTML -------------- @@ -630,8 +532,8 @@ Superscripts: a^{bc}d a^{/hello/} a^{hello there}. Subscripts: H_{2}O, H_{23}O, H_{many of them}O. -These should not be superscripts or subscripts, because of the -unescaped spaces: a\^b c\^d, a~b c~d. +These should not be superscripts or subscripts, because of the unescaped +spaces: a\^b c\^d, a~b c~d. -------------- @@ -645,8 +547,8 @@ unescaped spaces: a\^b c\^d, a~b c~d. 'He said, "I want to go."' Were you alive in the 70's? -Here is some quoted '=code=' and a -"[[http://example.com/?foo=1&bar=2][quoted link]]". +Here is some quoted '=code=' and a "[[http://example.com/?foo=1&bar=2][quoted +link]]". Some dashes: one---two --- three---four --- five. @@ -658,7 +560,6 @@ Ellipses...and...and.... * LaTeX - - \cite[22-23]{smith.1899} - $2+2=4$ - $x \in y$ @@ -667,15 +568,13 @@ Ellipses...and...and.... - $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: - $\alpha + \omega \times x^2$. +- Here's one that has a line break in it: $\alpha + \omega \times x^2$. 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.) +- $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$. @@ -693,7 +592,6 @@ Cat & 1 \\ \hline Here is some unicode: - - I hat: Î - o umlaut: ö - section: § @@ -789,17 +687,17 @@ This should [not][] be a link. #+BEGIN_EXAMPLE [not]: /url #+END_EXAMPLE + Foo [[/url/][bar]]. Foo [[/url/][biz]]. ** With ampersands -Here's a -[[http://example.com/?foo=1&bar=2][link with an ampersand in the URL]]. +Here's a [[http://example.com/?foo=1&bar=2][link with an ampersand in the +URL]]. -Here's a link with an amersand in the link text: -[[http://att.com/][AT&T]]. +Here's a link with an amersand in the link text: [[http://att.com/][AT&T]]. Here's an [[/script?foo=1&bar=2][inline link]]. @@ -809,20 +707,14 @@ Here's an [[/script?foo=1&bar=2][inline link in pointy braces]]. With an ampersand: [[http://example.com/?foo=1&bar=2]] - - In a list? - [[http://example.com/]] - It should. -An e-mail address: -[[mailto:nobody@nowhere.net][=nobody@nowhere.net=]] - +An e-mail address: [[mailto:nobody@nowhere.net][=nobody@nowhere.net=]] #+BEGIN_QUOTE - Blockquoted: [[http://example.com/]] - - #+END_QUOTE Auto-links should not occur here: =<http://example.com/>= @@ -830,6 +722,7 @@ Auto-links should not occur here: =<http://example.com/>= #+BEGIN_EXAMPLE or here: <http://example.com/> #+END_EXAMPLE + -------------- * Images @@ -845,41 +738,36 @@ Here is a movie [[movie.jpg]] icon. * Footnotes -Here is a footnote reference, [1] and another. [2] This should -/not/ be a footnote reference, because it contains a space.[\^my -note] Here is an inline note. [3] - +Here is a footnote reference, [1] and another. [2] This should /not/ be a +footnote reference, because it contains a space.[\^my note] Here is an inline +note. [3] #+BEGIN_QUOTE - Notes can go in quotes. [4] - - #+END_QUOTE - 1. And in list items. [5] -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. -[1] Here is the footnote. It can go anywhere after the footnote - reference. It need not be placed at the end of the document. +[1] Here is the footnote. It can go anywhere after the footnote reference. It + need not be placed at the end of the document. [2] 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). #+BEGIN_EXAMPLE { <code> } #+END_EXAMPLE - If you want, you can indent every line, but you can also be lazy - and just indent the first line of each block. + + If you want, you can indent every line, but you can also be lazy and just + indent the first line of each block. [3] This is /easier/ to type. Inline notes may contain - [[http://google.com][links]] and =]= verbatim characters, as well - as [bracketed text]. + [[http://google.com][links]] and =]= verbatim characters, as well as + [bracketed text]. [4] In quote. diff --git a/tests/writer.plain b/tests/writer.plain index bc6d25467..cc61916d2 100644 --- a/tests/writer.plain +++ b/tests/writer.plain @@ -2,9 +2,8 @@ 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. - +This is a set of tests for pandoc. Most of them are adapted from John Gruber’s +markdown test suite. * * * * * @@ -35,7 +34,6 @@ Level 2 with no blank line - * * * * * Paragraphs @@ -43,16 +41,15 @@ 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. +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 @@ -63,27 +60,26 @@ E-mail style: This is a block quote. It is pretty short. Code in a block quote: - + sub status { print "working"; } - + A list: - + 1. item one 2. item two - + Nested block quotes: - + nested - + nested This should not be a block quote: 2 > 1. And a following paragraph. - * * * * * Code Blocks @@ -92,19 +88,18 @@ 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: \$ \\ \> \[ \{ + These should not be escaped: \$ \\ \> \[ \{ * * * * * @@ -128,7 +123,6 @@ Asterisks loose: - asterisk 3 - Pluses tight: - Plus 1 @@ -143,7 +137,6 @@ Pluses loose: - Plus 3 - Minuses tight: - Minus 1 @@ -158,7 +151,6 @@ Minuses loose: - Minus 3 - Ordered ------- @@ -182,7 +174,6 @@ Loose using tabs: 3. Third - and using spaces: 1. One @@ -191,19 +182,16 @@ and using spaces: 3. Three - Multiple paragraphs: 1. 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. 2. Item 2. 3. Item 3. - Nested ------ @@ -211,8 +199,6 @@ Nested - Tab - Tab - - Here’s another: 1. First @@ -235,7 +221,6 @@ Same thing but with paragraphs: 3. Third - Tabs and spaces --------------- @@ -247,8 +232,6 @@ Tabs and spaces - this is an example list item indented with spaces - - Fancy list markers ------------------ @@ -262,8 +245,6 @@ Fancy list markers (A) a subsublist (B) a subsublist - - Nesting: A. Upper Alpha @@ -271,23 +252,18 @@ A. Upper Alpha (6) Decimal start with 6 c) Lower alpha with paren - - - Autonumbering: 1. Autonumber. 2. More. 1. Nested. - Should not be a list item: M.A. 2007 B. Williams - * * * * * Definition Lists @@ -322,7 +298,6 @@ orange banana yellow fruit - Multiple blocks with italics: apple @@ -337,7 +312,6 @@ orange orange block quote - Multiple definitions, tight: apple @@ -359,7 +333,6 @@ orange bank - Blank line after term, indented marker, alternate markers: apple @@ -373,7 +346,6 @@ orange 1. sublist 2. sublist - HTML Blocks =========== @@ -420,7 +392,6 @@ Code: Hr’s: - * * * * * Inline Markup @@ -448,9 +419,8 @@ 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. - +These should not be superscripts or subscripts, because of the unescaped +spaces: a^b c^d, a~b c~d. * * * * * @@ -473,7 +443,6 @@ Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. - * * * * * LaTeX @@ -487,22 +456,18 @@ LaTeX - 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: - \alpha + \omega \times x^2. +- Here’s one that has a line break in it: \alpha + \omega \times x^2. 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.) +- $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 @@ -558,7 +523,6 @@ Plus: + Minus: - - * * * * * Links @@ -640,7 +604,6 @@ Auto-links should not occur here: <http://example.com/> or here: <http://example.com/> - * * * * * Images @@ -648,48 +611,41 @@ Images From “Voyage dans la Lune” by Georges Melies (1902): +[lalune] - -Here is a movie icon. - +Here is a movie [movie] icon. * * * * * Footnotes ========= -Here is a footnote reference,[^1] and another.[^2] This should not -be a footnote reference, because it contains a space.[^my note] -Here is an inline note.[^3] +Here is a footnote reference,[^1] and another.[^2] This should not be a +footnote reference, because it contains a space.[^my note] Here is an inline +note.[^3] Notes can go in quotes.[^4] 1. And in list items.[^5] -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. -[^1]: - Here is the footnote. It can go anywhere after the footnote - reference. It need not be placed at the end of the document. +[^1]: Here is the footnote. It can go anywhere after the footnote reference. + It need not be placed at the end of the document. -[^2]: - Here’s the long note. This one contains multiple blocks. +[^2]: 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). { <code> } - If you want, you can indent every line, but you can also be lazy - and just indent the first line of each block. + If you want, you can indent every line, but you can also be lazy and just + indent the first line of each block. -[^3]: - This is easier to type. Inline notes may contain links and ] - verbatim characters, as well as [bracketed text]. +[^3]: This is easier to type. Inline notes may contain links and ] verbatim + characters, as well as [bracketed text]. -[^4]: - In quote. +[^4]: In quote. -[^5]: - In list. +[^5]: In list. diff --git a/tests/writer.rst b/tests/writer.rst index dff04bc81..79d989915 100644 --- a/tests/writer.rst +++ b/tests/writer.rst @@ -9,8 +9,8 @@ Pandoc Test Suite .. role:: math(raw) :format: html latex -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. -------------- @@ -52,9 +52,9 @@ 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. +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. @@ -70,7 +70,6 @@ E-mail style: This is a block quote. It is pretty short. - Code in a block quote: :: @@ -81,7 +80,6 @@ E-mail style: A list: - 1. item one 2. item two @@ -89,11 +87,8 @@ E-mail style: nested - nested - - This should not be a block quote: 2 > 1. And a following paragraph. @@ -108,11 +103,11 @@ Code: :: ---- (should be four hyphens) - + sub status { print "working"; } - + this code block is indented by one tab And: @@ -120,7 +115,7 @@ And: :: this code block is indented by two tabs - + These should not be escaped: \$ \\ \> \[ \{ -------------- @@ -133,123 +128,101 @@ 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: - 1. First 2. Second 3. Third and: - 1. One 2. Two 3. Three Loose using tabs: - 1. First 2. Second 3. Third - and using spaces: - 1. One 2. Two 3. Three - Multiple paragraphs: - 1. 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. 2. Item 2. 3. Item 3. - Nested ------ - - Tab - + - Tab - + - Tab - - Here’s another: - 1. First 2. Second: - + - Fee - Fie - Foe @@ -258,74 +231,57 @@ Here’s another: Same thing but with paragraphs: - 1. First 2. Second: - - Fee - Fie - Foe 3. 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 ------------------ - (2) begins with 2 (3) and now 3 with a continuation - iv. sublist with roman numerals, starting with 4 v. more items - + (A) a subsublist (B) a subsublist - - Nesting: - A. Upper Alpha - + I. Upper Roman. - + (6) Decimal start with 6 - + c) Lower alpha with paren - - - Autonumbering: - #. Autonumber. #. More. - - #. Nested. + #. Nested. Should not be a list item: @@ -367,7 +323,6 @@ orange banana yellow fruit - Multiple blocks with italics: *apple* @@ -384,8 +339,6 @@ Multiple blocks with italics: orange block quote - - Multiple definitions, tight: apple @@ -407,7 +360,6 @@ orange bank - Blank line after term, indented marker, alternate markers: apple @@ -418,36 +370,32 @@ apple orange orange fruit - 1. sublist 2. sublist - HTML Blocks =========== Simple block on one line: - .. raw:: html <div> - + foo .. raw:: html </div> - + And nested without indentation: - .. raw:: html <div> <div> <div> - + foo .. raw:: html @@ -455,30 +403,29 @@ foo </div> </div> <div> - + bar .. raw:: html </div> </div> - -Interpreted markdown in a table: +Interpreted markdown in a table: .. raw:: html <table> <tr> <td> - + This is *emphasized* .. raw:: html </td> <td> - + And this is **strong** .. raw:: html @@ -486,23 +433,22 @@ And this is **strong** </td> </tr> </table> - - <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> - -Here’s a simple block: + <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> + +Here’s a simple block: .. raw:: html <div> - + foo .. raw:: html </div> - + This should be a code block, though: :: @@ -519,14 +465,13 @@ As should this: Now, nested: - .. raw:: html <div> <div> <div> - + foo .. raw:: html @@ -534,16 +479,14 @@ foo </div> </div> </div> - -This should just be an HTML comment: +This should just be an HTML comment: .. raw:: html <!-- Comment --> - -Multiline: +Multiline: .. raw:: html @@ -551,11 +494,11 @@ Multiline: Blah Blah --> - + <!-- This is another comment. --> - + Code block: :: @@ -564,11 +507,10 @@ Code block: Just plain comment, with trailing spaces on the line: - .. raw:: html <!-- foo --> - + Code: :: @@ -577,27 +519,26 @@ Code: Hr’s: - .. raw:: html <hr> - + <hr /> - + <hr /> - + <hr> - + <hr /> - + <hr /> - + <hr class="foo" id="bar" /> - + <hr class="foo" id="bar" /> - + <hr class="foo" id="bar"> - + -------------- Inline Markup @@ -621,14 +562,12 @@ This is code: ``>``, ``$``, ``\``, ``\$``, ``<html>``. [STRIKEOUT:This is *strikeout*.] -Superscripts: a\ :sup:`bc`\ d a\ :sup:`*hello*`\ -a\ :sup:`hello there`\ . +Superscripts: a\ :sup:`bc`\ d a\ :sup:`*hello*`\ a\ :sup:`hello there`\ . -Subscripts: H\ :sub:`2`\ O, H\ :sub:`23`\ O, -H\ :sub:`many of them`\ O. +Subscripts: H\ :sub:`2`\ O, H\ :sub:`23`\ O, H\ :sub:`many of them`\ O. -These should not be superscripts or subscripts, because of the -unescaped spaces: a^b c^d, a~b c~d. +These should not be superscripts or subscripts, because of the unescaped +spaces: a^b c^d, a~b c~d. -------------- @@ -643,8 +582,8 @@ Smart quotes, ellipses, dashes ‘He said, “I want to go.”’ Were you alive in the 70’s? -Here is some quoted ‘``code``’ and a -“`quoted link <http://example.com/?foo=1&bar=2>`_”. +Here is some quoted ‘``code``’ and a “`quoted +link <http://example.com/?foo=1&bar=2>`_”. Some dashes: one—two — three—four — five. @@ -657,7 +596,6 @@ Ellipses…and…and…. LaTeX ===== - - - :math:`$2+2=4$` - :math:`$x \in y$` @@ -671,17 +609,14 @@ LaTeX 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.) +- $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 @@ -689,7 +624,6 @@ Special Characters Here is some unicode: - - I hat: Î - o umlaut: ö - section: § @@ -796,11 +730,10 @@ Foo `biz </url/>`_. With ampersands --------------- -Here’s a -`link with an ampersand in the URL <http://example.com/?foo=1&bar=2>`_. +Here’s a `link with an ampersand in the +URL <http://example.com/?foo=1&bar=2>`_. -Here’s a link with an amersand in the link text: -`AT&T <http://att.com/>`_. +Here’s a link with an amersand in the link text: `AT&T <http://att.com/>`_. Here’s an `inline link </script?foo=1&bar=2>`_. @@ -811,7 +744,6 @@ Autolinks With an ampersand: http://example.com/?foo=1&bar=2 - - In a list? - http://example.com/ - It should. @@ -820,7 +752,6 @@ An e-mail address: nobody@nowhere.net Blockquoted: http://example.com/ - Auto-links should not occur here: ``<http://example.com/>`` :: @@ -837,9 +768,8 @@ From “Voyage dans la Lune” by Georges Melies (1902): .. figure:: lalune.jpg :align: center :alt: Voyage dans la Lune - - lalune + lalune Here is a movie |movie| icon. -------------- @@ -847,40 +777,37 @@ Here is a movie |movie| icon. Footnotes ========= -Here is a footnote reference, [1]_ and another. [2]_ This should -*not* be a footnote reference, because it contains a space.[^my -note] Here is an inline note. [3]_ +Here is a footnote reference, [1]_ and another. [2]_ This should *not* be a +footnote reference, because it contains a space.[^my note] Here is an inline +note. [3]_ Notes can go in quotes. [4]_ - - 1. And in list items. [5]_ -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. .. [1] - Here is the footnote. It can go anywhere after the footnote - reference. It need not be placed at the end of the document. + Here is the footnote. It can go anywhere after the footnote reference. It + need not be placed at the end of the document. .. [2] 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). :: { <code> } - If you want, you can indent every line, but you can also be lazy - and just indent the first line of each block. + If you want, you can indent every line, but you can also be lazy and just + indent the first line of each block. .. [3] This is *easier* to type. Inline notes may contain - `links <http://google.com>`_ and ``]`` verbatim characters, as well - as [bracketed text]. + `links <http://google.com>`_ and ``]`` verbatim characters, as well as + [bracketed text]. .. [4] In quote.