diff options
author | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2007-01-15 19:52:42 +0000 |
---|---|---|
committer | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2007-01-15 19:52:42 +0000 |
commit | 60989d0637780787fb337b94af212f1ee9e1ae22 (patch) | |
tree | 95b5caa1e7e304a47739532a9c4d3767ce54435c | |
parent | 4224d913880e4f77a358cda868c9d1ca75820506 (diff) | |
download | pandoc-60989d0637780787fb337b94af212f1ee9e1ae22.tar.gz |
Added support for tables in markdown reader and in LaTeX,
DocBook, and HTML writers. The syntax is documented in
README. Tests have been added to the test suite.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@493 788f1e2b-df1e-0410-8736-df70ead52e1b
-rw-r--r-- | README | 65 | ||||
-rw-r--r-- | debian/changelog | 8 | ||||
-rw-r--r-- | src/Main.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Definition.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 161 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 34 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 32 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 33 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 2 | ||||
-rw-r--r-- | src/Text/ParserCombinators/Pandoc.hs | 14 | ||||
-rw-r--r-- | src/headers/LaTeXHeader | 4 | ||||
-rw-r--r-- | tests/runtests.pl | 19 | ||||
-rw-r--r-- | tests/tables.db | 286 | ||||
-rw-r--r-- | tests/tables.html | 138 | ||||
-rw-r--r-- | tests/tables.native | 11 | ||||
-rw-r--r-- | tests/tables.tex | 139 | ||||
-rw-r--r-- | tests/tables.txt | 57 | ||||
-rw-r--r-- | tests/writer.latex | 4 |
21 files changed, 1033 insertions, 13 deletions
@@ -471,6 +471,71 @@ they cannot contain multiple paragraphs). The syntax is as follows: Inline and regular footnotes may be mixed freely. +Tables +------ + +Two kinds of tables may be used. Both kinds presuppose the use of +a fixed-width font, such as Courier. Currently only the HTML, +Docbook, and LaTeX writers support tables. + +Simple tables look like this: + + Right Left Center Default + ------- ------ ---------- ------- + 12 12 12 12 + 123 123 123 123 + 1 1 1 1 + + Table: Demonstration of simple table syntax. + +The headers and table rows must each fit on one line. Column +alignments are determined by the position of the header text relative +to the dashed line below it:[^2] + + - If the dashed line is flush with the header text on the right side + but extends beyond it on the left, the column is right-aligned. + - If the dashed line is flush with the header text on the left side + but extends beyond it on the right, the column is left-aligned. + - If the dashed line extends beyond the header text on both sides, + the column is centered. + - If the dashed line is flush with the header text on both sides, + the default alignment is used (in most cases, this will be left). + +[^2]: This scheme is due to Michel Fortin, who proposed it on the + Markdown discussion list: <http://six.pairlist.net/pipermail/markdown-discuss/2005-March/001097.html> + +The table must end with a blank line. Optionally, a caption may be +provided (as illustrated in the example above). A caption is a paragraph +beginning with the string `Table:`, which will be stripped off. + +The table parser pays attention to the widths of the columns, and +the writers try to reproduce these relative widths in the output. +So, if you find that one of the columns is too narrow in the output, +try widening it in the markdown source. + +Multiline tables allow headers and table rows to span multiple lines +of text. Here is an example: + + --------------------------------------------------------------- + Centered Left Right + Header Aligned Aligned Default aligned + ---------- --------- ----------- --------------------------- + First row 12.0 Example of a row that spans + multiple lines. + + Second row 5.0 Here's another one. Note + the blank line between rows. + --------------------------------------------------------------- + + Table: Optional caption. This, too, may span multiple + lines. + +These work like simple tables, but with the following differences: + + - They must begin with a row of dashes, before the header text. + - They must end with a row of dashes, then a blank line. + - The rows must be separated by blank lines. + Embedded HTML ------------- diff --git a/debian/changelog b/debian/changelog index 29de84cd2..85f9e2cb2 100644 --- a/debian/changelog +++ b/debian/changelog @@ -1,3 +1,11 @@ +pandoc (0.4) unstable; urgency=low + + [ John MacFarlane ] + + * Added support for simple and multiline tables to markdown reader, + LaTeX writer, DocBook writer, and HTML writer. Added tests and + documentation in README. + pandoc (0.3) unstable; urgency=low [ John MacFarlane ] diff --git a/src/Main.hs b/src/Main.hs index 0ca1e5ca5..f3c70c472 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -48,7 +48,7 @@ import Text.Pandoc.Writers.DefaultHeaders ( defaultHtmlHeader, import Text.Pandoc.Definition import Text.Pandoc.Shared import Text.Regex ( mkRegex, matchRegex ) -import System.Environment ( getArgs, getProgName ) +import System.Environment ( getArgs, getProgName, getEnvironment ) import System.Exit ( exitWith, ExitCode (..) ) import System.Console.GetOpt import System.IO @@ -58,7 +58,7 @@ import Char ( toLower ) import Control.Monad ( (>>=) ) version :: String -version = "0.3" +version = "0.4" copyrightMessage :: String copyrightMessage = "\nCopyright (C) 2006 John MacFarlane\nWeb: http://sophos.berkeley.edu/macfarlane/pandoc\nThis is free software; see the source for copying conditions. There is no\nwarranty, not even for merchantability or fitness for a particular purpose." @@ -426,6 +426,11 @@ main = do then return stdout else openFile outputFile WriteMode + environment <- getEnvironment + let columns = case lookup "COLUMNS" environment of + Just cols -> read cols + Nothing -> stateColumns defaultParserState + let tabFilter = if preserveTabs then id else (tabsToSpaces tabStop) let addBlank str = str ++ "\n\n" let removeCRs str = filter (/= '\r') str -- remove DOS-style line endings @@ -435,6 +440,7 @@ main = do stateTabStop = tabStop, stateStandalone = standalone && (not strict), stateSmart = smart || writerName' == "latex", + stateColumns = columns, stateStrict = strict } let csslink = if (css == "") then "" diff --git a/src/Text/Pandoc/Definition.hs b/src/Text/Pandoc/Definition.hs index 2313b1ef1..d16309b4e 100644 --- a/src/Text/Pandoc/Definition.hs +++ b/src/Text/Pandoc/Definition.hs @@ -39,6 +39,12 @@ data Meta = Meta [Inline] -- title String -- date deriving (Eq, Show, Read) +-- | Alignment of a table column. +data Alignment = AlignLeft + | AlignRight + | AlignCenter + | AlignDefault deriving (Eq, Show, Read) + -- | Block element. data Block = Plain [Inline] -- ^ Plain text, not a paragraph @@ -57,6 +63,11 @@ data Block | HorizontalRule -- ^ Horizontal rule | Note String [Block] -- ^ Footnote or endnote - reference (string), -- text (list of blocks) + | Table [Inline] -- ^ Table caption, + [Alignment] -- column alignments, + [Float] -- column widths (relative to page), + [[Block]] -- column headers, and + [[[Block]]] -- rows deriving (Eq, Read, Show) -- | Target for a link: either a URL or an indirect (labeled) reference. diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 4e6a7b39c..1a77a5958 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -31,7 +31,7 @@ module Text.Pandoc.Readers.Markdown ( readMarkdown ) where -import Data.List ( findIndex, sortBy ) +import Data.List ( findIndex, sortBy, transpose ) import Data.Char ( isAlphaNum ) import Text.ParserCombinators.Pandoc import Text.Pandoc.Definition @@ -88,6 +88,7 @@ setextHChars = ['=','-'] blockQuoteChar = '>' hyphenChar = '-' ellipsesChar = '.' +listColSepChar = '|' -- treat these as potentially non-text when parsing inline: specialChars = [escapeChar, labelStart, labelEnd, emphStart, emphEnd, @@ -106,9 +107,9 @@ indentSpaces = do state <- getState let tabStop = stateTabStop state count tabStop (char ' ') <|> - (do{skipNonindentSpaces; string "\t"}) <?> "indentation" + (do{nonindentSpaces; string "\t"}) <?> "indentation" -skipNonindentSpaces = do +nonindentSpaces = do state <- getState let tabStop = stateTabStop state choice (map (\n -> (try (count n (char ' ')))) (reverse [0..(tabStop - 1)])) @@ -192,7 +193,7 @@ parseMarkdown = do parseBlocks = manyTill block eof -block = choice [ codeBlock, note, referenceKey, header, hrule, list, +block = choice [ header, table, codeBlock, note, referenceKey, hrule, list, blockQuote, htmlBlock, rawLaTeXEnvironment', para, plain, blankBlock, nullBlock ] <?> "block" @@ -322,7 +323,7 @@ emacsBoxQuote = try (do return raw) emailBlockQuoteStart = try (do - skipNonindentSpaces + nonindentSpaces char blockQuoteChar option ' ' (char ' ') return "> ") @@ -356,7 +357,7 @@ list = choice [ bulletList, orderedList ] <?> "list" bulletListStart = try (do option ' ' newline -- if preceded by a Plain block in a list context - skipNonindentSpaces + nonindentSpaces notFollowedBy' hrule -- because hrules start out just like lists oneOf bulletListMarkers spaceChar @@ -364,7 +365,7 @@ bulletListStart = try (do orderedListStart = try (do option ' ' newline -- if preceded by a Plain block in a list context - skipNonindentSpaces + nonindentSpaces many1 digit <|> (do{failIfStrict; count 1 letter}) delim <- oneOf orderedListDelimiters if delim /= '.' then failIfStrict else return () @@ -501,7 +502,7 @@ rawHtmlBlocks = try (do -- referenceKey = try (do - skipNonindentSpaces + nonindentSpaces label <- reference char labelSep skipSpaces @@ -523,6 +524,150 @@ rawLaTeXEnvironment' = do failIfStrict rawLaTeXEnvironment +-- +-- Tables +-- + +-- | Parse a dashed line with optional trailing spaces; return its length +-- and the length including trailing space. +dashedLine ch = do + dashes <- many1 (char ch) + sp <- many spaceChar + return $ (length dashes, length $ dashes ++ sp) + +-- | Parse a table header with dashed lines of '-' preceded by +-- one line of text. +simpleTableHeader = do + rawContent <- anyLine + initSp <- nonindentSpaces + dashes <- many1 (dashedLine '-') + newline + let (lengths, lines) = unzip dashes + let indices = scanl (+) (length initSp) lines + let rawHeads = tail $ splitByIndices (init indices) rawContent + let aligns = zipWith alignType (map (\a -> [a]) rawHeads) lengths + return $ (rawHeads, aligns, indices) + +-- | Parse a table footer - dashed lines followed by blank line. +tableFooter = try $ do + nonindentSpaces + many1 (dashedLine '-') + blanklines + +-- | Parse a table separator - dashed line. +tableSep = try $ do + nonindentSpaces + many1 (dashedLine '-') + string "\n" + +-- | Parse a raw line and split it into chunks by indices. +rawTableLine indices = do + notFollowedBy' (blanklines <|> tableFooter) + line <- many1Till anyChar newline + return $ map removeLeadingTrailingSpace $ tail $ + splitByIndices (init indices) line + +-- | Parse a table line and return a list of lists of blocks (columns). +tableLine indices = try $ do + rawline <- rawTableLine indices + mapM (parseFromStr (many plain)) rawline + +-- | Parse a multiline table row and return a list of blocks (columns). +multilineRow indices = try $ do + colLines <- many1 (rawTableLine indices) + option "" blanklines + let cols = map unlines $ transpose colLines + mapM (parseFromStr (many plain)) cols + +-- | Calculate relative widths of table columns, based on indices +widthsFromIndices :: Int -- ^ Number of columns on terminal + -> [Int] -- ^ Indices + -> [Float] -- ^ Fractional relative sizes of columns +widthsFromIndices _ [] = [] +widthsFromIndices numColumns indices = + let lengths = zipWith (-) indices (0:indices) + totLength = sum lengths + quotient = if totLength > numColumns + then fromIntegral totLength + else fromIntegral numColumns + fracs = map (\l -> (fromIntegral l) / quotient) lengths in + tail fracs + +-- | Parses a table caption: inlines beginning with 'Table:' +-- and followed by blank lines +tableCaption = try $ do + nonindentSpaces + string "Table:" + result <- many1 inline + blanklines + return $ normalizeSpaces result + +-- | Parse a table using 'headerParser', 'lineParser', and 'footerParser' +tableWith headerParser lineParser footerParser = try $ do + (rawHeads, aligns, indices) <- headerParser + lines <- many1Till (lineParser indices) footerParser + caption <- option [] tableCaption + heads <- mapM (parseFromStr (many plain)) rawHeads + state <- getState + let numColumns = stateColumns state + let widths = widthsFromIndices numColumns indices + return $ Table caption aligns widths heads lines + +-- | Parse a simple table with '---' header and one line per row. +simpleTable = tableWith simpleTableHeader tableLine blanklines + +-- | Parse a multiline table: starts with row of '-' on top, then header +-- (which may be multiline), then the rows, +-- which may be multiline, separated by blank lines, and +-- ending with a footer (dashed line followed by blank line). +multilineTable = tableWith multilineTableHeader multilineRow tableFooter + +multilineTableHeader = try $ do + tableSep + rawContent <- many1 (do{notFollowedBy' tableSep; + many1Till anyChar newline}) + initSp <- nonindentSpaces + dashes <- many1 (dashedLine '-') + newline + let (lengths, lines) = unzip dashes + let indices = scanl (+) (length initSp) lines + let rawHeadsList = transpose $ map + (\ln -> tail $ splitByIndices (init indices) ln) + rawContent + let rawHeads = map (joinWithSep " ") rawHeadsList + let aligns = zipWith alignType rawHeadsList lengths + return $ ((map removeLeadingTrailingSpace rawHeads), + aligns, indices) + +-- | Returns the longest of a list of strings. +longest :: [String] -> String +longest [] = "" +longest [x] = x +longest (x:xs) = + if (length x) >= (maximum $ map length xs) + then x + else longest xs + +-- | Returns an alignment type for a table, based on a list of strings +-- (the rows of the column header) and a number (the length of the +-- dashed line under the rows. +alignType :: [String] -> Int -> Alignment +alignType [] len = AlignDefault +alignType strLst len = + let str = longest $ map removeTrailingSpace strLst + leftSpace = if null str then False else ((str !! 0) `elem` " \t") + rightSpace = (length str < len || (str !! (len - 1)) `elem` " \t") in + case (leftSpace, rightSpace) of + (True, False) -> AlignRight + (False, True) -> AlignLeft + (True, True) -> AlignCenter + (False, False) -> AlignDefault + +table = do + failIfStrict + result <- simpleTable <|> multilineTable <?> "table" + return result + -- -- inline -- diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 624f573de..8ee990827 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -30,6 +30,7 @@ Utility functions and definitions used by the various Pandoc modules. module Text.Pandoc.Shared ( -- * List processing splitBy, + splitByIndices, -- * Text processing gsub, joinWithSep, @@ -133,6 +134,8 @@ data ParserState = ParserState stateDate :: String, -- ^ Date of document stateStrict :: Bool, -- ^ Use strict markdown syntax stateSmart :: Bool, -- ^ Use smart typography + stateColumns :: Int, -- ^ Number of columns in + -- terminal (used for tables) stateHeaderTable :: [HeaderType] -- ^ List of header types used, -- in what order (rst only) } @@ -154,6 +157,7 @@ defaultParserState = stateDate = [], stateStrict = False, stateSmart = False, + stateColumns = 80, stateHeaderTable = [] } -- | Indent string as a block. @@ -292,6 +296,13 @@ splitBy sep lst = rest' = dropWhile (== sep) rest in first:(splitBy sep rest') +-- | Split list into chunks divided at specified indices. +splitByIndices :: [Int] -> [a] -> [[a]] +splitByIndices [] lst = [lst] +splitByIndices (x:xs) lst = + let (first, rest) = splitAt x lst in + first:(splitByIndices (map (\y -> y - x) xs) rest) + -- | Normalize a list of inline elements: remove leading and trailing -- @Space@ elements, and collapse double @Space@s into singles. normalizeSpaces :: [Inline] -> [Inline] diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index e67b91fcd..ec3801a9a 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -151,7 +151,39 @@ blockToDocbook opts (RawHtml str) = text str -- raw XML block blockToDocbook opts HorizontalRule = empty -- not semantic blockToDocbook opts (Note _ _) = empty -- shouldn't occur blockToDocbook opts (Key _ _) = empty -- shouldn't occur -blockToDocbook opts _ = inTagsIndented "para" (text "Unknown block type") +blockToDocbook opts (Table caption aligns widths headers rows) = + let alignStrings = map alignmentToString aligns + captionDoc = if null caption + then empty + else inTagsIndented "caption" + (inlinesToDocbook opts caption) + tableType = if isEmpty captionDoc then "informaltable" else "table" in + inTagsIndented tableType $ captionDoc $$ + (colHeadsToDocbook opts alignStrings widths headers) $$ + (vcat $ map (tableRowToDocbook opts alignStrings) rows) + +colHeadsToDocbook opts alignStrings widths headers = + let heads = zipWith3 + (\align width item -> tableItemToDocbook opts "th" align width item) + alignStrings widths headers in + inTagsIndented "tr" $ vcat heads + +alignmentToString alignment = case alignment of + AlignLeft -> "left" + AlignRight -> "right" + AlignCenter -> "center" + AlignDefault -> "left" + +tableRowToDocbook opts aligns cols = + inTagsIndented "tr" $ vcat $ zipWith3 (tableItemToDocbook opts "td") aligns (repeat 0) cols + +tableItemToDocbook opts tag align width item = + let attrib = [("align", align)] ++ + if (width /= 0) + then [("style", "{width: " ++ + show (truncate (100*width)) ++ "%;}")] + else [] in + inTags True tag attrib $ vcat $ map (blockToDocbook opts) item -- | Put string in CDATA section cdata :: String -> Doc diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index e119a5c87..d38a57556 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -186,6 +186,38 @@ blockToHtml opts (Header level lst) = if ((level > 0) && (level <= 6)) then inTagsSimple ("h" ++ show level) contents else inTagsSimple "p" contents +blockToHtml opts (Table caption aligns widths headers rows) = + let alignStrings = map alignmentToString aligns + captionDoc = if null caption + then empty + else inTagsSimple "caption" + (inlineListToHtml opts caption) in + inTagsIndented "table" $ captionDoc $$ + (colHeadsToHtml opts alignStrings widths headers) $$ + (vcat $ map (tableRowToHtml opts alignStrings) rows) + +colHeadsToHtml opts alignStrings widths headers = + let heads = zipWith3 + (\align width item -> tableItemToHtml opts "th" align width item) + alignStrings widths headers in + inTagsIndented "tr" $ vcat heads + +alignmentToString alignment = case alignment of + AlignLeft -> "left" + AlignRight -> "right" + AlignCenter -> "center" + AlignDefault -> "left" + +tableRowToHtml opts aligns cols = + inTagsIndented "tr" $ vcat $ zipWith3 (tableItemToHtml opts "td") aligns (repeat 0) cols + +tableItemToHtml opts tag align width item = + let attrib = [("align", align)] ++ + if (width /= 0) + then [("style", "{width: " ++ + show (truncate (100*width)) ++ "%;}")] + else [] in + inTags False tag attrib $ vcat $ map (blockToHtml opts) item listItemToHtml :: WriterOptions -> [Block] -> Doc listItemToHtml opts list = diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index aca72535d..db7af223d 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -32,6 +32,7 @@ module Text.Pandoc.Writers.LaTeX ( ) where import Text.Pandoc.Definition import Text.Pandoc.Shared +import Text.Printf ( printf ) import List ( (\\) ) -- | Convert Pandoc to LaTeX. @@ -123,6 +124,38 @@ blockToLaTeX notes (Header level lst) = then "\\" ++ (concat (replicate (level - 1) "sub")) ++ "section{" ++ (inlineListToLaTeX notes (deVerb lst)) ++ "}\n\n" else (inlineListToLaTeX notes lst) ++ "\n\n" +blockToLaTeX notes (Table caption aligns widths heads rows) = + let colWidths = map printDecimal widths + colDescriptors = concat $ zipWith + (\width align -> ">{\\PBS" ++ + (case align of + AlignLeft -> "\\raggedright" + AlignRight -> "\\raggedleft" + AlignCenter -> "\\centering" + AlignDefault -> "\\raggedright") ++ + "\\hspace{0pt}}p{" ++ width ++ + "\\textwidth}") + colWidths aligns + headers = tableRowToLaTeX notes heads + captionText = inlineListToLaTeX notes caption + tableBody = "\\begin{tabular}{" ++ colDescriptors ++ "}\n" ++ + headers ++ "\\hline\n" ++ + (concatMap (tableRowToLaTeX notes) rows) ++ + "\\end{tabular}\n" + centered str = "\\begin{center}\n" ++ str ++ "\\end{center}\n" in + if null captionText + then centered tableBody ++ "\n" + else "\\begin{table}[h]\n" ++ centered tableBody ++ "\\caption{" ++ + captionText ++ "}\n" ++ "\\end{table}\n\n" + + +printDecimal :: Float -> String +printDecimal = printf "%.2f" + +tableColumnWidths notes cols = map (length . (concatMap (blockToLaTeX notes))) cols + +tableRowToLaTeX notes cols = joinWithSep " & " (map (concatMap (blockToLaTeX notes)) cols) ++ "\\\\\n" + listItemToLaTeX notes list = "\\item " ++ (concatMap (blockToLaTeX notes) list) diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 343942421..0e7704510 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -132,6 +132,10 @@ blockToMarkdown tabStop (OrderedList lst) = blockToMarkdown tabStop HorizontalRule = text "\n* * * * *\n" blockToMarkdown tabStop (Header level lst) = text ((replicate level '#') ++ " ") <> (inlineListToMarkdown lst) <> (text "\n") +blockToMarkdown tabStop (Table caption _ _ headers rows) = + blockToMarkdown tabStop (Para [Str "pandoc: TABLE unsupported in Markdown writer"]) + + bulletListItemToMarkdown tabStop list = hang (text "- ") tabStop (vcat (map (blockToMarkdown tabStop) list)) diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 7e1581908..b6802ffa2 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -148,6 +148,9 @@ blockToRST tabStop (Header level lst) = let headerChar = if (level > 5) then ' ' else "=-~^'" !! (level - 1) in let border = text $ replicate headerLength headerChar in (headerText <> char '\n' <> border <> char '\n', refs) +blockToRST tabStop (Table caption _ _ headers rows) = + blockToRST tabStop (Para [Str "pandoc: TABLE unsupported in RST writer"]) + -- | Convert bullet list item (list of blocks) to reStructuredText. -- Returns a pair of 'Doc', the first the main text, the second references diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 20f06d21b..b53e39cb2 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -170,6 +170,8 @@ blockToRTF notes indent HorizontalRule = blockToRTF notes indent (Header level lst) = rtfPar indent 0 ("\\b \\fs" ++ (show (40 - (level * 4))) ++ " " ++ (inlineListToRTF notes lst)) +blockToRTF notes indent (Table caption _ _ headers rows) = + blockToRTF notes indent (Para [Str "pandoc: TABLE unsupported in RST writer"]) -- | Ensure that there's the same amount of space after compact -- lists as after regular lists. diff --git a/src/Text/ParserCombinators/Pandoc.hs b/src/Text/ParserCombinators/Pandoc.hs index b55ceb23d..a825ef8ff 100644 --- a/src/Text/ParserCombinators/Pandoc.hs +++ b/src/Text/ParserCombinators/Pandoc.hs @@ -41,7 +41,8 @@ module Text.ParserCombinators.Pandoc ( enclosed, blankBlock, nullBlock, - stringAnyCase + stringAnyCase, + parseFromStr ) where import Text.ParserCombinators.Parsec import Text.Pandoc.Definition @@ -138,3 +139,14 @@ stringAnyCase (x:xs) = try (do firstChar <- choice [ char (toUpper x), char (toLower x) ] rest <- stringAnyCase xs return (firstChar:rest)) + +-- | Parse contents of 'str' using 'parser' and return result. +parseFromStr :: GenParser tok st a -> [tok] -> GenParser tok st a +parseFromStr parser str = try $ do + oldInput <- getInput + setInput str + result <- parser + setInput oldInput + return result + + diff --git a/src/headers/LaTeXHeader b/src/headers/LaTeXHeader index d50bf8ae3..f808ef80f 100644 --- a/src/headers/LaTeXHeader +++ b/src/headers/LaTeXHeader @@ -3,8 +3,12 @@ \usepackage{ucs} \usepackage[utf8x]{inputenc} \usepackage{graphicx} +\usepackage{array} \setlength{\parindent}{0pt} \setlength{\parskip}{6pt plus 2pt minus 1pt} % This is needed for code blocks in footnotes: \usepackage{fancyvrb} \VerbatimFootnotes +% This is needed because raggedright in table elements redefines //: +\newcommand{\PreserveBackslash}[1]{\let\temp=\\#1\let\\=\temp} +\let\PBS=\PreserveBackslash diff --git a/tests/runtests.pl b/tests/runtests.pl index 754b6e75e..44b56f844 100644 --- a/tests/runtests.pl +++ b/tests/runtests.pl @@ -4,7 +4,7 @@ $verbose = 1; my $diffexists = `which diff`; if ($diffexists eq "") { die "diff not found in path.\n"; } -my $script = "./pandoc"; +my $script = "COLUMNS=78 ./pandoc"; use Getopt::Long; GetOptions("script=s" => \$script); @@ -73,12 +73,29 @@ print "Testing -H -B -A -c options..."; `$script -r native -s -w html -H insert -B insert -A insert -c main.css s5.native > tmp.html`; test_results("-B, -A, -H, -c options", "tmp.html", "s5.inserts.html"); +print "Testing tables:\n"; +print " html writer..."; +`$script -r native -w html tables.native > tmp.html`; +test_results("html table writer", "tmp.html", "tables.html"); + +print " latex writer..."; +`$script -r native -w latex tables.native > tmp.tex`; +test_results("latex table writer", "tmp.tex", "tables.tex"); + +print " docbook writer..."; +`$script -r native -w docbook tables.native > tmp.db`; +test_results("docbook table writer", "tmp.db", "tables.db"); + print "\nReader tests:\n"; print "Testing markdown reader..."; `$script -r markdown -w native -s -S testsuite.txt > tmp.native`; test_results("markdown reader", "tmp.native", "testsuite.native"); +print " tables..."; +`$script -r markdown -w native tables.txt > tmp.native`; +test_results("markdown table reader", "tmp.native", "tables.native"); + print "Testing rst reader..."; `$script -r rst -w native -s rst-reader.rst > tmp.native`; test_results("rst reader", "tmp.native", "rst-reader.native"); diff --git a/tests/tables.db b/tests/tables.db new file mode 100644 index 000000000..0bb094307 --- /dev/null +++ b/tests/tables.db @@ -0,0 +1,286 @@ +<para> + Simple table with caption: +</para> +<table> + <caption> + Demonstration of simple table syntax. + </caption> + <tr> + <th align="right" style="{width: 15%;}"> + Right + </th> + <th align="left" style="{width: 8%;}"> + Left + </th> + <th align="center" style="{width: 16%;}"> + Center + </th> + <th align="left" style="{width: 12%;}"> + Default + </th> + </tr> + <tr> + <td align="right"> + 12 + </td> + <td align="left"> + 12 + </td> + <td align="center"> + 12 + </td> + <td align="left"> + 12 + </td> + </tr> + <tr> + <td align="right"> + 123 + </td> + <td align="left"> + 123 + </td> + <td align="center"> + 123 + </td> + <td align="left"> + 123 + </td> + </tr> + <tr> + <td align="right"> + 1 + </td> + <td align="left"> + 1 + </td> + <td align="center"> + 1 + </td> + <td align="left"> + 1 + </td> + </tr> +</table> +<para> + Simple table without caption: +</para> +<informaltable> + <tr> + <th align="right" style="{width: 15%;}"> + Right + </th> + <th align="left" style="{width: 8%;}"> + Left + </th> + <th align="center" style="{width: 16%;}"> + Center + </th> + <th align="left" style="{width: 12%;}"> + Default + </th> + </tr> + <tr> + <td align="right"> + 12 + </td> + <td align="left"> + 12 + </td> + <td align="center"> + 12 + </td> + <td align="left"> + 12 + </td> + </tr> + <tr> + <td align="right"> + 123 + </td> + <td align="left"> + 123 + </td> + <td align="center"> + 123 + </td> + <td align="left"> + 123 + </td> + </tr> + <tr> + <td align="right"> + 1 + </td> + <td align="left"> + 1 + </td> + <td align="center"> + 1 + </td> + <td align="left"> + 1 + </td> + </tr> +</informaltable> +<para> + Simple table indented two spaces: +</para> +<table> + <caption> + Demonstration of simple table syntax. + </caption> + <tr> + <th align="right" style="{width: 15%;}"> + Right + </th> + <th align="left" style="{width: 8%;}"> + Left + </th> + <th align="center" style="{width: 16%;}"> + Center + </th> + <th align="left" style="{width: 12%;}"> + Default + </th> + </tr> + <tr> + <td align="right"> + 12 + </td> + <td align="left"> + 12 + </td> + <td align="center"> + 12 + </td> + <td align="left"> + 12 + </td> + </tr> + <tr> + <td align="right"> + 123 + </td> + <td align="left"> + 123 + </td> + <td align="center"> + 123 + </td> + <td align="left"> + 123 + </td> + </tr> + <tr> + <td align="right"> + 1 + </td> + <td align="left"> + 1 + </td> + <td align="center"> + 1 + </td> + <td align="left"> + 1 + </td> + </tr> +</table> +<para> + Multiline table with caption: +</para> +<table> + <caption> + Here's the caption. It may span multiple lines. + </caption> + <tr> + <th align="center" style="{width: 15%;}"> + Centered Header + </th> + <th align="left" style="{width: 13%;}"> + Left Aligned + </th> + <th align="right" style="{width: 16%;}"> + Right Aligned + </th> + <th align="left" style="{width: 33%;}"> + Default aligned + </th> + </tr> + <tr> + <td align="center"> + First + </td> + <td align="left"> + row + </td> + <td align="right"> + 12.0 + </td> + <td align="left"> + Example of a row that spans multiple lines. + </td> + </tr> + <tr> + <td align="center"> + Second + </td> + <td align="left"> + row + </td> + <td align="right"> + 5.0 + </td> + <td align="left"> + Here's another one. Note the blank line between rows. + </td> + </tr> +</table> +<para> + Multiline table without caption: +</para> +<informaltable> + <tr> + <th align="center" style="{width: 15%;}"> + Centered Header + </th> + <th align="left" style="{width: 13%;}"> + Left Aligned + </th> + <th align="right" style="{width: 16%;}"> + Right Aligned + </th> + <th align="left" style="{width: 33%;}"> + Default aligned + </th> + </tr> + <tr> + <td align="center"> + First + </td> + <td align="left"> + row + </td> + <td align="right"> + 12.0 + </td> + <td align="left"> + Example of a row that spans multiple lines. + </td> + </tr> + <tr> + <td align="center"> + Second + </td> + <td align="left"> + row + </td> + <td align="right"> + 5.0 + </td> + <td align="left"> + Here's another one. Note the blank line between rows. + </td> + </tr> +</informaltable> diff --git a/tests/tables.html b/tests/tables.html new file mode 100644 index 000000000..e145088d2 --- /dev/null +++ b/tests/tables.html @@ -0,0 +1,138 @@ +<p> + Simple table with caption: +</p> +<table> + <caption>Demonstration of simple table syntax.</caption> + <tr> + <th align="right" style="{width: 15%;}">Right</th> + <th align="left" style="{width: 8%;}">Left</th> + <th align="center" style="{width: 16%;}">Center</th> + <th align="left" style="{width: 12%;}">Default</th> + </tr> + <tr> + <td align="right">12</td> + <td align="left">12</td> + <td align="center">12</td> + <td align="left">12</td> + </tr> + <tr> + <td align="right">123</td> + <td align="left">123</td> + <td align="center">123</td> + <td align="left">123</td> + </tr> + <tr> + <td align="right">1</td> + <td align="left">1</td> + <td align="center">1</td> + <td align="left">1</td> + </tr> +</table> +<p> + Simple table without caption: +</p> +<table> + <tr> + <th align="right" style="{width: 15%;}">Right</th> + <th align="left" style="{width: 8%;}">Left</th> + <th align="center" style="{width: 16%;}">Center</th> + <th align="left" style="{width: 12%;}">Default</th> + </tr> + <tr> + <td align="right">12</td> + <td align="left">12</td> + <td align="center">12</td> + <td align="left">12</td> + </tr> + <tr> + <td align="right">123</td> + <td align="left">123</td> + <td align="center">123</td> + <td align="left">123</td> + </tr> + <tr> + <td align="right">1</td> + <td align="left">1</td> + <td align="center">1</td> + <td align="left">1</td> + </tr> +</table> +<p> + Simple table indented two spaces: +</p> +<table> + <caption>Demonstration of simple table syntax.</caption> + <tr> + <th align="right" style="{width: 15%;}">Right</th> + <th align="left" style="{width: 8%;}">Left</th> + <th align="center" style="{width: 16%;}">Center</th> + <th align="left" style="{width: 12%;}">Default</th> + </tr> + <tr> + <td align="right">12</td> + <td align="left">12</td> + <td align="center">12</td> + <td align="left">12</td> + </tr> + <tr> + <td align="right">123</td> + <td align="left">123</td> + <td align="center">123</td> + <td align="left">123</td> + </tr> + <tr> + <td align="right">1</td> + <td align="left">1</td> + <td align="center">1</td> + <td align="left">1</td> + </tr> +</table> +<p> + Multiline table with caption: +</p> +<table> + <caption>Here's the caption. It may span multiple lines.</caption> + <tr> + <th align="center" style="{width: 15%;}">Centered Header</th> + <th align="left" style="{width: 13%;}">Left Aligned</th> + <th align="right" style="{width: 16%;}">Right Aligned</th> + <th align="left" style="{width: 33%;}">Default aligned</th> + </tr> + <tr> + <td align="center">First</td> + <td align="left">row</td> + <td align="right">12.0</td> + <td align="left">Example of a row that spans multiple lines.</td> + </tr> + <tr> + <td align="center">Second</td> + <td align="left">row</td> + <td align="right">5.0</td> + <td align="left">Here's another one. Note the blank line between + rows.</td> + </tr> +</table> +<p> + Multiline table without caption: +</p> +<table> + <tr> + <th align="center" style="{width: 15%;}">Centered Header</th> + <th align="left" style="{width: 13%;}">Left Aligned</th> + <th align="right" style="{width: 16%;}">Right Aligned</th> + <th align="left" style="{width: 33%;}">Default aligned</th> + </tr> + <tr> + <td align="center">First</td> + <td align="left">row</td> + <td align="right">12.0</td> + <td align="left">Example of a row that spans multiple lines.</td> + </tr> + <tr> + <td align="center">Second</td> + <td align="left">row</td> + <td align="right">5.0</td> + <td align="left">Here's another one. Note the blank line between + rows.</td> + </tr> +</table> diff --git a/tests/tables.native b/tests/tables.native new file mode 100644 index 000000000..7572dfdc2 --- /dev/null +++ b/tests/tables.native @@ -0,0 +1,11 @@ +Pandoc (Meta [] [] "") +[ Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"] +, Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax",Str "."] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.15,8.75e-2,0.1625,0.125] [[Plain [Str "Right"]],[Plain [Str "Left"]],[Plain [Str "Center"]],[Plain [Str "Default"]]] [[[Plain [Str "12"]],[Plain [Str "12"]],[Plain [Str "12"]],[Plain [Str "12"]]],[[Plain [Str "123"]],[Plain [Str "123"]],[Plain [Str "123"]],[Plain [Str "123"]]],[[Plain [Str "1"]],[Plain [Str "1"]],[Plain [Str "1"]],[Plain [Str "1"]]]] +, Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption:"] +, Table [] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.15,8.75e-2,0.1625,0.125] [[Plain [Str "Right"]],[Plain [Str "Left"]],[Plain [Str "Center"]],[Plain [Str "Default"]]] [[[Plain [Str "12"]],[Plain [Str "12"]],[Plain [Str "12"]],[Plain [Str "12"]]],[[Plain [Str "123"]],[Plain [Str "123"]],[Plain [Str "123"]],[Plain [Str "123"]]],[[Plain [Str "1"]],[Plain [Str "1"]],[Plain [Str "1"]],[Plain [Str "1"]]]] +, Para [Str "Simple",Space,Str "table",Space,Str "indented",Space,Str "two",Space,Str "spaces:"] +, Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax",Str "."] [AlignRight,AlignLeft,AlignCenter,AlignDefault] [0.15,8.75e-2,0.1625,0.125] [[Plain [Str "Right"]],[Plain [Str "Left"]],[Plain [Str "Center"]],[Plain [Str "Default"]]] [[[Plain [Str "12"]],[Plain [Str "12"]],[Plain [Str "12"]],[Plain [Str "12"]]],[[Plain [Str "123"]],[Plain [Str "123"]],[Plain [Str "123"]],[Plain [Str "123"]]],[[Plain [Str "1"]],[Plain [Str "1"]],[Plain [Str "1"]],[Plain [Str "1"]]]] +, Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] +, Table [Str "Here",Str "'",Str "s",Space,Str "the",Space,Str "caption",Str ".",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines",Str "."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] [[Plain [Str "Centered",Space,Str "Header"]],[Plain [Str "Left",Space,Str "Aligned"]],[Plain [Str "Right",Space,Str "Aligned"]],[Plain [Str "Default",Space,Str "aligned"]]] [[[Plain [Str "First"]],[Plain [Str "row"]],[Plain [Str "12",Str ".",Str "0"]],[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."]]],[[Plain [Str "Second"]],[Plain [Str "row"]],[Plain [Str "5",Str ".",Str "0"]],[Plain [Str "Here",Str "'",Str "s",Space,Str "another",Space,Str "one",Str ".",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows",Str "."]]]] +, Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] +, Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] [[Plain [Str "Centered",Space,Str "Header"]],[Plain [Str "Left",Space,Str "Aligned"]],[Plain [Str "Right",Space,Str "Aligned"]],[Plain [Str "Default",Space,Str "aligned"]]] [[[Plain [Str "First"]],[Plain [Str "row"]],[Plain [Str "12",Str ".",Str "0"]],[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines",Str "."]]],[[Plain [Str "Second"]],[Plain [Str "row"]],[Plain [Str "5",Str ".",Str "0"]],[Plain [Str "Here",Str "'",Str "s",Space,Str "another",Space,Str "one",Str ".",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows",Str "."]]]] ] diff --git a/tests/tables.tex b/tests/tables.tex new file mode 100644 index 000000000..4cbb27385 --- /dev/null +++ b/tests/tables.tex @@ -0,0 +1,139 @@ +Simple table with caption: + +\begin{table}[h] +\begin{center} +\begin{tabular}{>{\PBS\raggedleft\hspace{0pt}}p{0.15\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.09\textwidth}>{\PBS\centering\hspace{0pt}}p{0.16\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.13\textwidth}} +Right + & Left + & Center + & Default +\\ +\hline +12 + & 12 + & 12 + & 12 +\\ +123 + & 123 + & 123 + & 123 +\\ +1 + & 1 + & 1 + & 1 +\\ +\end{tabular} +\end{center} +\caption{Demonstration of simple table syntax.} +\end{table} + +Simple table without caption: + +\begin{center} +\begin{tabular}{>{\PBS\raggedleft\hspace{0pt}}p{0.15\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.09\textwidth}>{\PBS\centering\hspace{0pt}}p{0.16\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.13\textwidth}} +Right + & Left + & Center + & Default +\\ +\hline +12 + & 12 + & 12 + & 12 +\\ +123 + & 123 + & 123 + & 123 +\\ +1 + & 1 + & 1 + & 1 +\\ +\end{tabular} +\end{center} + +Simple table indented two spaces: + +\begin{table}[h] +\begin{center} +\begin{tabular}{>{\PBS\raggedleft\hspace{0pt}}p{0.15\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.09\textwidth}>{\PBS\centering\hspace{0pt}}p{0.16\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.13\textwidth}} +Right + & Left + & Center + & Default +\\ +\hline +12 + & 12 + & 12 + & 12 +\\ +123 + & 123 + & 123 + & 123 +\\ +1 + & 1 + & 1 + & 1 +\\ +\end{tabular} +\end{center} +\caption{Demonstration of simple table syntax.} +\end{table} + +Multiline table with caption: + +\begin{table}[h] +\begin{center} +\begin{tabular}{>{\PBS\centering\hspace{0pt}}p{0.15\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.14\textwidth}>{\PBS\raggedleft\hspace{0pt}}p{0.16\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.34\textwidth}} +Centered Header + & Left Aligned + & Right Aligned + & Default aligned +\\ +\hline +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. +\\ +\end{tabular} +\end{center} +\caption{Here's the caption. It may span multiple lines.} +\end{table} + +Multiline table without caption: + +\begin{center} +\begin{tabular}{>{\PBS\centering\hspace{0pt}}p{0.15\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.14\textwidth}>{\PBS\raggedleft\hspace{0pt}}p{0.16\textwidth}>{\PBS\raggedright\hspace{0pt}}p{0.34\textwidth}} +Centered Header + & Left Aligned + & Right Aligned + & Default aligned +\\ +\hline +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. +\\ +\end{tabular} +\end{center} + diff --git a/tests/tables.txt b/tests/tables.txt new file mode 100644 index 000000000..73b3b9cd7 --- /dev/null +++ b/tests/tables.txt @@ -0,0 +1,57 @@ +Simple table with caption: + + Right Left Center Default +------- ------ ---------- ------- + 12 12 12 12 + 123 123 123 123 + 1 1 1 1 + +Table: Demonstration of simple table syntax. + +Simple table without caption: + + Right Left Center Default +------- ------ ---------- ------- + 12 12 12 12 + 123 123 123 123 + 1 1 1 1 + +Simple table indented two spaces: + + Right Left Center Default + ------- ------ ---------- ------- + 12 12 12 12 + 123 123 123 123 + 1 1 1 1 + + Table: Demonstration of simple table syntax. + +Multiline table with caption: + +--------------------------------------------------------------- + Centered Left Right + Header Aligned Aligned Default aligned +---------- --------- ----------- --------------------------- + First row 12.0 Example of a row that spans + multiple lines. + + Second row 5.0 Here's another one. Note + the blank line between rows. +--------------------------------------------------------------- + +Table: Here's the caption. +It may span multiple lines. + +Multiline table without caption: + +--------------------------------------------------------------- + Centered Left Right + Header Aligned Aligned Default aligned +---------- --------- ----------- --------------------------- + First row 12.0 Example of a row that spans + multiple lines. + + Second row 5.0 Here's another one. Note + the blank line between rows. +--------------------------------------------------------------- + diff --git a/tests/writer.latex b/tests/writer.latex index af9aad6f9..f3ffeed62 100644 --- a/tests/writer.latex +++ b/tests/writer.latex @@ -3,11 +3,15 @@ \usepackage{ucs} \usepackage[utf8x]{inputenc} \usepackage{graphicx} +\usepackage{array} \setlength{\parindent}{0pt} \setlength{\parskip}{6pt plus 2pt minus 1pt} % This is needed for code blocks in footnotes: \usepackage{fancyvrb} \VerbatimFootnotes +% This is needed because raggedright in table elements redefines //: +\newcommand{\PreserveBackslash}[1]{\let\temp=\\#1\let\\=\temp} +\let\PBS=\PreserveBackslash \setcounter{secnumdepth}{0} \title{Pandoc Test Suite} \author{John MacFarlane\\Anonymous} |