preliminary material toward table support
This commit is contained in:
parent
75fa22c300
commit
d917db5e42
2 changed files with 68 additions and 2 deletions
|
@ -47,6 +47,9 @@ data Alignment = AlignLeft
|
|||
| AlignCenter
|
||||
| AlignDefault deriving (Eq, Ord, Show, Read, Typeable, Data)
|
||||
|
||||
-- | Table cells are list of Blocks
|
||||
type TableCell = [Block]
|
||||
|
||||
-- | List attributes.
|
||||
type ListAttributes = (Int, ListNumberStyle, ListNumberDelim)
|
||||
|
||||
|
@ -85,7 +88,7 @@ data Block
|
|||
-- definitions (each a list of blocks)
|
||||
| Header Int [Inline] -- ^ Header - level (integer) and text (inlines)
|
||||
| HorizontalRule -- ^ Horizontal rule
|
||||
| Table [Inline] [Alignment] [Double] [[Block]] [[[Block]]] -- ^ Table,
|
||||
| Table [Inline] [Alignment] [Double] [TableCell] [[TableCell]] -- ^ Table,
|
||||
-- with caption, column alignments,
|
||||
-- relative column widths (0 = default),
|
||||
-- column headers (each a list of blocks), and
|
||||
|
|
|
@ -63,7 +63,7 @@ readTextile state s = (readWith parseTextile) state (s ++ "\n\n")
|
|||
|
||||
-- | Special chars border strings parsing
|
||||
specialChars :: [Char]
|
||||
specialChars = "\\[]*#_@~<>!?-+^&'\";:"
|
||||
specialChars = "\\[]*#_@~<>!?-+^&'\";:|"
|
||||
|
||||
-- | Generate a Pandoc ADT from a textile document
|
||||
parseTextile :: GenParser Char ParserState Pandoc
|
||||
|
@ -82,6 +82,7 @@ blockParsers = [ codeBlock
|
|||
, header
|
||||
, blockQuote
|
||||
, anyList
|
||||
, table
|
||||
, para
|
||||
, nullBlock ]
|
||||
|
||||
|
@ -173,6 +174,68 @@ para = try $ do
|
|||
content <- manyTill inline blockBreak
|
||||
return $ Para $ normalizeSpaces content
|
||||
|
||||
|
||||
-- Tables
|
||||
|
||||
-- TODO : DOC and factorizing cellInlines
|
||||
|
||||
tableCell :: GenParser Char ParserState TableCell
|
||||
tableCell = many1 cellInline >>= return . (:[]) . Plain . normalizeSpaces
|
||||
where cellInline = choice [ str
|
||||
, whitespace
|
||||
, code
|
||||
, simpleInline (string "??") (Cite [])
|
||||
, simpleInline (char '*') Strong
|
||||
, simpleInline (char '_') Emph
|
||||
, simpleInline (string "**") Strong
|
||||
, simpleInline (string "__") Emph
|
||||
, simpleInline (char '-') Strikeout
|
||||
, simpleInline (char '+') Inserted
|
||||
, simpleInline (char '^') Superscript
|
||||
, simpleInline (char '~') Subscript
|
||||
-- , link
|
||||
-- , image
|
||||
-- , math
|
||||
-- , autoLink
|
||||
]
|
||||
|
||||
tableRow :: GenParser Char ParserState [TableCell]
|
||||
tableRow = try $ do
|
||||
char '|'
|
||||
cells <- endBy1 tableCell (char '|')
|
||||
newline
|
||||
return cells
|
||||
|
||||
tableRows :: GenParser Char ParserState [[TableCell]]
|
||||
tableRows = many1 tableRow
|
||||
|
||||
tableHeaders :: GenParser Char ParserState [TableCell]
|
||||
tableHeaders = try $ do
|
||||
let separator = (try $ string "|_.")
|
||||
separator
|
||||
headers <- sepBy1 tableCell separator
|
||||
char '|'
|
||||
newline
|
||||
return headers
|
||||
|
||||
table :: GenParser Char ParserState Block
|
||||
table = try $ do
|
||||
headers <- option [] tableHeaders
|
||||
rows <- tableRows
|
||||
return $ Table []
|
||||
(replicate (length headers) AlignDefault)
|
||||
(replicate (length headers) 0.0)
|
||||
headers
|
||||
rows
|
||||
|
||||
|
||||
----------
|
||||
-- Inlines
|
||||
----------
|
||||
|
||||
|
||||
|
||||
|
||||
-- | Any inline element
|
||||
inline :: GenParser Char ParserState Inline
|
||||
inline = choice inlineParsers <?> "inline"
|
||||
|
|
Loading…
Add table
Reference in a new issue