RST reader: Use Text.Pandoc.Builder.
This will give us more flexibility in the future. It also gives built-in normalization. Performance slightly better.
This commit is contained in:
parent
5c06322ab2
commit
ab17faf497
3 changed files with 305 additions and 299 deletions
|
@ -35,11 +35,14 @@ import Text.Pandoc.Shared
|
|||
import Text.Pandoc.Parsing
|
||||
import Text.Pandoc.Options
|
||||
import Control.Monad ( when, liftM, guard, mzero )
|
||||
import Data.List ( findIndex, intercalate, transpose, sort, deleteFirstsBy )
|
||||
import Data.List ( findIndex, intersperse, intercalate, transpose, sort, deleteFirstsBy )
|
||||
import qualified Data.Map as M
|
||||
import Text.Printf ( printf )
|
||||
import Data.Maybe ( catMaybes )
|
||||
import Control.Applicative ((<$>))
|
||||
import Control.Applicative ((<$>), (<$), (<*), (*>))
|
||||
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines, (<>))
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Data.Monoid (mconcat, mempty)
|
||||
|
||||
-- | Parse reStructuredText string and return Pandoc document.
|
||||
readRST :: ReaderOptions -- ^ Reader options
|
||||
|
@ -104,26 +107,25 @@ parseRST = do
|
|||
let reversedNotes = stateNotes st'
|
||||
updateState $ \s -> s { stateNotes = reverse reversedNotes }
|
||||
-- now parse it for real...
|
||||
blocks <- parseBlocks
|
||||
let blocks' = filter (/= Null) blocks
|
||||
blocks <- B.toList <$> parseBlocks
|
||||
standalone <- getOption readerStandalone
|
||||
let (blocks'', title) = if standalone
|
||||
then titleTransform blocks'
|
||||
else (blocks', [])
|
||||
let (blocks', title) = if standalone
|
||||
then titleTransform blocks
|
||||
else (blocks, [])
|
||||
state <- getState
|
||||
let authors = stateAuthors state
|
||||
let date = stateDate state
|
||||
let title' = if (null title) then (stateTitle state) else title
|
||||
return $ Pandoc (Meta title' authors date) blocks''
|
||||
let title' = if null title then stateTitle state else title
|
||||
return $ Pandoc (Meta title' authors date) blocks'
|
||||
|
||||
--
|
||||
-- parsing blocks
|
||||
--
|
||||
|
||||
parseBlocks :: Parser [Char] ParserState [Block]
|
||||
parseBlocks = manyTill block eof
|
||||
parseBlocks :: Parser [Char] ParserState Blocks
|
||||
parseBlocks = mconcat <$> manyTill block eof
|
||||
|
||||
block :: Parser [Char] ParserState Block
|
||||
block :: Parser [Char] ParserState Blocks
|
||||
block = choice [ codeBlock
|
||||
, rawBlock
|
||||
, blockQuote
|
||||
|
@ -142,7 +144,7 @@ block = choice [ codeBlock
|
|||
, lhsCodeBlock
|
||||
, para
|
||||
, plain
|
||||
, nullBlock ] <?> "block"
|
||||
] <?> "block"
|
||||
|
||||
--
|
||||
-- field list
|
||||
|
@ -161,13 +163,13 @@ rawFieldListItem indent = try $ do
|
|||
return (name, raw)
|
||||
|
||||
fieldListItem :: String
|
||||
-> Parser [Char] ParserState (Maybe ([Inline], [[Block]]))
|
||||
-> Parser [Char] ParserState (Maybe (Inlines, [Blocks]))
|
||||
fieldListItem indent = try $ do
|
||||
(name, raw) <- rawFieldListItem indent
|
||||
let term = [Str name]
|
||||
contents <- parseFromString (many block) raw
|
||||
let term = B.str name
|
||||
contents <- parseFromString parseBlocks raw
|
||||
optional blanklines
|
||||
case (name, contents) of
|
||||
case (name, B.toList contents) of
|
||||
("Author", x) -> do
|
||||
updateState $ \st ->
|
||||
st{ stateAuthors = stateAuthors st ++ [extractContents x] }
|
||||
|
@ -188,19 +190,19 @@ extractContents [Plain auth] = auth
|
|||
extractContents [Para auth] = auth
|
||||
extractContents _ = []
|
||||
|
||||
fieldList :: Parser [Char] ParserState Block
|
||||
fieldList :: Parser [Char] ParserState Blocks
|
||||
fieldList = try $ do
|
||||
indent <- lookAhead $ many spaceChar
|
||||
items <- many1 $ fieldListItem indent
|
||||
if null items
|
||||
then return Null
|
||||
else return $ DefinitionList $ catMaybes items
|
||||
then return mempty
|
||||
else return $ B.definitionList $ catMaybes items
|
||||
|
||||
--
|
||||
-- line block
|
||||
--
|
||||
|
||||
lineBlockLine :: Parser [Char] ParserState [Inline]
|
||||
lineBlockLine :: Parser [Char] ParserState Inlines
|
||||
lineBlockLine = try $ do
|
||||
char '|'
|
||||
char ' ' <|> lookAhead (char '\n')
|
||||
|
@ -208,87 +210,74 @@ lineBlockLine = try $ do
|
|||
line <- many $ (notFollowedBy newline >> inline) <|> (try $ endline >>~ char ' ')
|
||||
optional endline
|
||||
return $ if null white
|
||||
then normalizeSpaces line
|
||||
else Str white : normalizeSpaces line
|
||||
then mconcat line
|
||||
else B.str white <> mconcat line
|
||||
|
||||
lineBlock :: Parser [Char] ParserState Block
|
||||
lineBlock :: Parser [Char] ParserState Blocks
|
||||
lineBlock = try $ do
|
||||
lines' <- many1 lineBlockLine
|
||||
blanklines
|
||||
return $ Para (intercalate [LineBreak] lines')
|
||||
return $ B.para (mconcat $ intersperse B.linebreak lines')
|
||||
|
||||
--
|
||||
-- paragraph block
|
||||
--
|
||||
|
||||
para :: Parser [Char] ParserState Block
|
||||
para = paraBeforeCodeBlock <|> paraNormal <?> "paragraph"
|
||||
|
||||
codeBlockStart :: Parser [Char] st Char
|
||||
codeBlockStart = string "::" >> blankline >> blankline
|
||||
|
||||
-- paragraph that ends in a :: starting a code block
|
||||
paraBeforeCodeBlock :: Parser [Char] ParserState Block
|
||||
paraBeforeCodeBlock = try $ do
|
||||
result <- many1 (notFollowedBy' codeBlockStart >> inline)
|
||||
lookAhead (string "::")
|
||||
return $ Para $ if last result == Space
|
||||
then normalizeSpaces result
|
||||
else (normalizeSpaces result) ++ [Str ":"]
|
||||
-- note: paragraph can end in a :: starting a code block
|
||||
para :: Parser [Char] ParserState Blocks
|
||||
para = try $ do
|
||||
result <- trimInlines . mconcat <$>
|
||||
many1 (notFollowedBy' codeBlockStart >> inline)
|
||||
(lookAhead codeBlockStart >> return (B.para $ result <> B.str ":"))
|
||||
<|> (newline >> blanklines >> return (B.para result))
|
||||
|
||||
-- regular paragraph
|
||||
paraNormal :: Parser [Char] ParserState Block
|
||||
paraNormal = try $ do
|
||||
result <- many1 inline
|
||||
newline
|
||||
blanklines
|
||||
return $ Para $ normalizeSpaces result
|
||||
|
||||
plain :: Parser [Char] ParserState Block
|
||||
plain = many1 inline >>= return . Plain . normalizeSpaces
|
||||
plain :: Parser [Char] ParserState Blocks
|
||||
plain = B.plain . trimInlines . mconcat <$> many1 inline
|
||||
|
||||
--
|
||||
-- image block
|
||||
--
|
||||
|
||||
imageBlock :: Parser [Char] ParserState Block
|
||||
imageBlock :: Parser [Char] ParserState Blocks
|
||||
imageBlock = try $ do
|
||||
string ".. "
|
||||
res <- imageDef [Str "image"]
|
||||
return $ Para [res]
|
||||
res <- imageDef (B.str "image")
|
||||
return $ B.para res
|
||||
|
||||
imageDef :: [Inline] -> Parser [Char] ParserState Inline
|
||||
imageDef :: Inlines -> Parser [Char] ParserState Inlines
|
||||
imageDef defaultAlt = try $ do
|
||||
string "image:: "
|
||||
src <- escapeURI . removeLeadingTrailingSpace <$> manyTill anyChar newline
|
||||
fields <- try $ do indent <- lookAhead $ many (oneOf " /t")
|
||||
many $ rawFieldListItem indent
|
||||
optional blanklines
|
||||
let alt = maybe defaultAlt (\x -> [Str $ removeTrailingSpace x])
|
||||
let alt = maybe defaultAlt (\x -> B.str $ removeTrailingSpace x)
|
||||
$ lookup "alt" fields
|
||||
let img = Image alt (src,"")
|
||||
let img = B.image src "" alt
|
||||
return $ case lookup "target" fields of
|
||||
Just t -> Link [img]
|
||||
(escapeURI $ removeLeadingTrailingSpace t,"")
|
||||
Just t -> B.link (escapeURI $ removeLeadingTrailingSpace t)
|
||||
"" img
|
||||
Nothing -> img
|
||||
|
||||
|
||||
--
|
||||
-- header blocks
|
||||
--
|
||||
|
||||
header :: Parser [Char] ParserState Block
|
||||
header :: Parser [Char] ParserState Blocks
|
||||
header = doubleHeader <|> singleHeader <?> "header"
|
||||
|
||||
-- a header with lines on top and bottom
|
||||
doubleHeader :: Parser [Char] ParserState Block
|
||||
doubleHeader :: Parser [Char] ParserState Blocks
|
||||
doubleHeader = try $ do
|
||||
c <- oneOf underlineChars
|
||||
rest <- many (char c) -- the top line
|
||||
let lenTop = length (c:rest)
|
||||
skipSpaces
|
||||
newline
|
||||
txt <- many1 (notFollowedBy blankline >> inline)
|
||||
txt <- trimInlines . mconcat <$> many1 (notFollowedBy blankline >> inline)
|
||||
pos <- getPosition
|
||||
let len = (sourceColumn pos) - 1
|
||||
if (len > lenTop) then fail "title longer than border" else return ()
|
||||
|
@ -303,13 +292,13 @@ doubleHeader = try $ do
|
|||
Just ind -> (headerTable, ind + 1)
|
||||
Nothing -> (headerTable ++ [DoubleHeader c], (length headerTable) + 1)
|
||||
setState (state { stateHeaderTable = headerTable' })
|
||||
return $ Header level (normalizeSpaces txt)
|
||||
return $ B.header level txt
|
||||
|
||||
-- a header with line on the bottom only
|
||||
singleHeader :: Parser [Char] ParserState Block
|
||||
singleHeader :: Parser [Char] ParserState Blocks
|
||||
singleHeader = try $ do
|
||||
notFollowedBy' whitespace
|
||||
txt <- many1 (do {notFollowedBy blankline; inline})
|
||||
txt <- trimInlines . mconcat <$> many1 (do {notFollowedBy blankline; inline})
|
||||
pos <- getPosition
|
||||
let len = (sourceColumn pos) - 1
|
||||
blankline
|
||||
|
@ -323,20 +312,20 @@ singleHeader = try $ do
|
|||
Just ind -> (headerTable, ind + 1)
|
||||
Nothing -> (headerTable ++ [SingleHeader c], (length headerTable) + 1)
|
||||
setState (state { stateHeaderTable = headerTable' })
|
||||
return $ Header level (normalizeSpaces txt)
|
||||
return $ B.header level txt
|
||||
|
||||
--
|
||||
-- hrule block
|
||||
--
|
||||
|
||||
hrule :: Parser [Char] st Block
|
||||
hrule :: Parser [Char] st Blocks
|
||||
hrule = try $ do
|
||||
chr <- oneOf underlineChars
|
||||
count 3 (char chr)
|
||||
skipMany (char chr)
|
||||
blankline
|
||||
blanklines
|
||||
return HorizontalRule
|
||||
return B.horizontalRule
|
||||
|
||||
--
|
||||
-- code blocks
|
||||
|
@ -359,49 +348,49 @@ indentedBlock = try $ do
|
|||
optional blanklines
|
||||
return $ unlines lns
|
||||
|
||||
codeBlock :: Parser [Char] st Block
|
||||
codeBlock :: Parser [Char] st Blocks
|
||||
codeBlock = try $ do
|
||||
codeBlockStart
|
||||
result <- indentedBlock
|
||||
return $ CodeBlock ("",[],[]) $ stripTrailingNewlines result
|
||||
return $ B.codeBlock $ stripTrailingNewlines result
|
||||
|
||||
-- | The 'code-block' directive (from Sphinx) that allows a language to be
|
||||
-- specified.
|
||||
customCodeBlock :: Parser [Char] st Block
|
||||
customCodeBlock :: Parser [Char] st Blocks
|
||||
customCodeBlock = try $ do
|
||||
string ".. code-block:: "
|
||||
language <- manyTill anyChar newline
|
||||
blanklines
|
||||
result <- indentedBlock
|
||||
return $ CodeBlock ("", ["sourceCode", language], []) $ stripTrailingNewlines result
|
||||
return $ B.codeBlockWith ("", ["sourceCode", language], [])
|
||||
$ stripTrailingNewlines result
|
||||
|
||||
|
||||
figureBlock :: Parser [Char] ParserState Block
|
||||
figureBlock :: Parser [Char] ParserState Blocks
|
||||
figureBlock = try $ do
|
||||
string ".. figure::"
|
||||
src <- removeLeadingTrailingSpace `fmap` manyTill anyChar newline
|
||||
src <- escapeURI . removeLeadingTrailingSpace <$> manyTill anyChar newline
|
||||
body <- indentedBlock
|
||||
caption <- parseFromString extractCaption body
|
||||
return $ Para [Image caption (src,"")]
|
||||
return $ B.para $ B.image src "" caption
|
||||
|
||||
extractCaption :: Parser [Char] ParserState [Inline]
|
||||
extractCaption :: Parser [Char] ParserState Inlines
|
||||
extractCaption = try $ do
|
||||
manyTill anyLine blanklines
|
||||
many inline
|
||||
trimInlines . mconcat <$> many inline
|
||||
|
||||
-- | The 'math' directive (from Sphinx) for display math.
|
||||
mathBlock :: Parser [Char] st Block
|
||||
mathBlock :: Parser [Char] st Blocks
|
||||
mathBlock = try $ do
|
||||
string ".. math::"
|
||||
mathBlockMultiline <|> mathBlockOneLine
|
||||
|
||||
mathBlockOneLine :: Parser [Char] st Block
|
||||
mathBlockOneLine :: Parser [Char] st Blocks
|
||||
mathBlockOneLine = try $ do
|
||||
result <- manyTill anyChar newline
|
||||
blanklines
|
||||
return $ Para [Math DisplayMath $ removeLeadingTrailingSpace result]
|
||||
return $ B.para $ B.displayMath $ removeLeadingTrailingSpace result
|
||||
|
||||
mathBlockMultiline :: Parser [Char] st Block
|
||||
mathBlockMultiline :: Parser [Char] st Blocks
|
||||
mathBlockMultiline = try $ do
|
||||
blanklines
|
||||
result <- indentedBlock
|
||||
|
@ -414,9 +403,9 @@ mathBlockMultiline = try $ do
|
|||
let lns' = dropWhile startsWithColon lns
|
||||
let eqs = map (removeLeadingTrailingSpace . unlines)
|
||||
$ filter (not . null) $ splitBy null lns'
|
||||
return $ Para $ map (Math DisplayMath) eqs
|
||||
return $ B.para $ mconcat $ map B.displayMath eqs
|
||||
|
||||
lhsCodeBlock :: Parser [Char] ParserState Block
|
||||
lhsCodeBlock :: Parser [Char] ParserState Blocks
|
||||
lhsCodeBlock = try $ do
|
||||
guardEnabled Ext_literate_haskell
|
||||
optional codeBlockStart
|
||||
|
@ -428,55 +417,54 @@ lhsCodeBlock = try $ do
|
|||
then map (drop 1) lns
|
||||
else lns
|
||||
blanklines
|
||||
return $ CodeBlock ("", ["sourceCode", "literate", "haskell"], []) $ intercalate "\n" lns'
|
||||
return $ B.codeBlockWith ("", ["sourceCode", "literate", "haskell"], [])
|
||||
$ intercalate "\n" lns'
|
||||
|
||||
birdTrackLine :: Parser [Char] st [Char]
|
||||
birdTrackLine = do
|
||||
char '>'
|
||||
manyTill anyChar newline
|
||||
birdTrackLine = char '>' >> manyTill anyChar newline
|
||||
|
||||
--
|
||||
-- raw html/latex/etc
|
||||
--
|
||||
|
||||
rawBlock :: Parser [Char] st Block
|
||||
rawBlock :: Parser [Char] st Blocks
|
||||
rawBlock = try $ do
|
||||
string ".. raw:: "
|
||||
lang <- many1 (letter <|> digit)
|
||||
blanklines
|
||||
result <- indentedBlock
|
||||
return $ RawBlock lang result
|
||||
return $ B.rawBlock lang result
|
||||
|
||||
--
|
||||
-- block quotes
|
||||
--
|
||||
|
||||
blockQuote :: Parser [Char] ParserState Block
|
||||
blockQuote :: Parser [Char] ParserState Blocks
|
||||
blockQuote = do
|
||||
raw <- indentedBlock
|
||||
-- parse the extracted block, which may contain various block elements:
|
||||
contents <- parseFromString parseBlocks $ raw ++ "\n\n"
|
||||
return $ BlockQuote contents
|
||||
return $ B.blockQuote contents
|
||||
|
||||
--
|
||||
-- list blocks
|
||||
--
|
||||
|
||||
list :: Parser [Char] ParserState Block
|
||||
list :: Parser [Char] ParserState Blocks
|
||||
list = choice [ bulletList, orderedList, definitionList ] <?> "list"
|
||||
|
||||
definitionListItem :: Parser [Char] ParserState ([Inline], [[Block]])
|
||||
definitionListItem :: Parser [Char] ParserState (Inlines, [Blocks])
|
||||
definitionListItem = try $ do
|
||||
-- avoid capturing a directive or comment
|
||||
notFollowedBy (try $ char '.' >> char '.')
|
||||
term <- many1Till inline endline
|
||||
term <- trimInlines . mconcat <$> many1Till inline endline
|
||||
raw <- indentedBlock
|
||||
-- parse the extracted block, which may contain various block elements:
|
||||
contents <- parseFromString parseBlocks $ raw ++ "\n"
|
||||
return (normalizeSpaces term, [contents])
|
||||
return (term, [contents])
|
||||
|
||||
definitionList :: Parser [Char] ParserState Block
|
||||
definitionList = many1 definitionListItem >>= return . DefinitionList
|
||||
definitionList :: Parser [Char] ParserState Blocks
|
||||
definitionList = B.definitionList <$> many1 definitionListItem
|
||||
|
||||
-- parses bullet list start and returns its length (inc. following whitespace)
|
||||
bulletListStart :: Parser [Char] st Int
|
||||
|
@ -531,7 +519,7 @@ listContinuation markerLength = try $ do
|
|||
return $ blanks ++ concat result
|
||||
|
||||
listItem :: Parser [Char] ParserState Int
|
||||
-> Parser [Char] ParserState [Block]
|
||||
-> Parser [Char] ParserState Blocks
|
||||
listItem start = try $ do
|
||||
(markerLength, first) <- rawListItem start
|
||||
rest <- many (listContinuation markerLength)
|
||||
|
@ -548,22 +536,21 @@ listItem start = try $ do
|
|||
updateState (\st -> st {stateParserContext = oldContext})
|
||||
return parsed
|
||||
|
||||
orderedList :: Parser [Char] ParserState Block
|
||||
orderedList :: Parser [Char] ParserState Blocks
|
||||
orderedList = try $ do
|
||||
(start, style, delim) <- lookAhead (anyOrderedListMarker >>~ spaceChar)
|
||||
items <- many1 (listItem (orderedListStart style delim))
|
||||
let items' = compactify items
|
||||
return $ OrderedList (start, style, delim) items'
|
||||
let items' = compactify' items
|
||||
return $ B.orderedListWith (start, style, delim) items'
|
||||
|
||||
bulletList :: Parser [Char] ParserState Block
|
||||
bulletList = many1 (listItem bulletListStart) >>=
|
||||
return . BulletList . compactify
|
||||
bulletList :: Parser [Char] ParserState Blocks
|
||||
bulletList = B.bulletList . compactify' <$> many1 (listItem bulletListStart)
|
||||
|
||||
--
|
||||
-- default-role block
|
||||
--
|
||||
|
||||
defaultRoleBlock :: Parser [Char] ParserState Block
|
||||
defaultRoleBlock :: Parser [Char] ParserState Blocks
|
||||
defaultRoleBlock = try $ do
|
||||
string ".. default-role::"
|
||||
-- doesn't enforce any restrictions on the role name; embedded spaces shouldn't be allowed, for one
|
||||
|
@ -574,20 +561,20 @@ defaultRoleBlock = try $ do
|
|||
else role
|
||||
}
|
||||
-- skip body of the directive if it exists
|
||||
many $ blanklines <|> (spaceChar >> manyTill anyChar newline)
|
||||
return Null
|
||||
skipMany $ blanklines <|> (spaceChar >> manyTill anyChar newline)
|
||||
return mempty
|
||||
|
||||
--
|
||||
-- unknown directive (e.g. comment)
|
||||
--
|
||||
|
||||
unknownDirective :: Parser [Char] st Block
|
||||
unknownDirective :: Parser [Char] st Blocks
|
||||
unknownDirective = try $ do
|
||||
string ".."
|
||||
notFollowedBy (noneOf " \t\n")
|
||||
manyTill anyChar newline
|
||||
many $ blanklines <|> (spaceChar >> manyTill anyChar newline)
|
||||
return Null
|
||||
return mempty
|
||||
|
||||
---
|
||||
--- note block
|
||||
|
@ -625,15 +612,15 @@ noteMarker = do
|
|||
-- reference key
|
||||
--
|
||||
|
||||
quotedReferenceName :: Parser [Char] ParserState [Inline]
|
||||
quotedReferenceName :: Parser [Char] ParserState Inlines
|
||||
quotedReferenceName = try $ do
|
||||
char '`' >> notFollowedBy (char '`') -- `` means inline code!
|
||||
label' <- many1Till inline (char '`')
|
||||
label' <- trimInlines . mconcat <$> many1Till inline (char '`')
|
||||
return label'
|
||||
|
||||
unquotedReferenceName :: Parser [Char] ParserState [Inline]
|
||||
unquotedReferenceName :: Parser [Char] ParserState Inlines
|
||||
unquotedReferenceName = try $ do
|
||||
label' <- many1Till inline (lookAhead $ char ':')
|
||||
label' <- trimInlines . mconcat <$> many1Till inline (lookAhead $ char ':')
|
||||
return label'
|
||||
|
||||
-- Simple reference names are single words consisting of alphanumerics
|
||||
|
@ -647,12 +634,12 @@ simpleReferenceName' = do
|
|||
<|> (try $ oneOf "-_:+." >> lookAhead alphaNum)
|
||||
return (x:xs)
|
||||
|
||||
simpleReferenceName :: Parser [Char] st [Inline]
|
||||
simpleReferenceName :: Parser [Char] st Inlines
|
||||
simpleReferenceName = do
|
||||
raw <- simpleReferenceName'
|
||||
return [Str raw]
|
||||
return $ B.str raw
|
||||
|
||||
referenceName :: Parser [Char] ParserState [Inline]
|
||||
referenceName :: Parser [Char] ParserState Inlines
|
||||
referenceName = quotedReferenceName <|>
|
||||
(try $ simpleReferenceName >>~ lookAhead (char ':')) <|>
|
||||
unquotedReferenceName
|
||||
|
@ -678,7 +665,7 @@ targetURI = do
|
|||
imageKey :: Parser [Char] ParserState ()
|
||||
imageKey = try $ do
|
||||
string ".. |"
|
||||
(alt,ref) <- withRaw (manyTill inline (char '|'))
|
||||
(alt,ref) <- withRaw (trimInlines . mconcat <$> manyTill inline (char '|'))
|
||||
skipSpaces
|
||||
img <- imageDef alt
|
||||
let key = toKey $ init ref
|
||||
|
@ -753,7 +740,7 @@ simpleTableRow indices = do
|
|||
firstLine <- simpleTableRawLine indices
|
||||
colLines <- return [] -- TODO
|
||||
let cols = map unlines . transpose $ firstLine : colLines
|
||||
mapM (parseFromString (many plain)) cols
|
||||
mapM (parseFromString (B.toList . mconcat <$> many plain)) cols
|
||||
|
||||
simpleTableSplitLine :: [Int] -> String -> [String]
|
||||
simpleTableSplitLine indices line =
|
||||
|
@ -775,34 +762,34 @@ simpleTableHeader headless = try $ do
|
|||
let rawHeads = if headless
|
||||
then replicate (length dashes) ""
|
||||
else simpleTableSplitLine indices rawContent
|
||||
heads <- mapM (parseFromString (many plain)) $
|
||||
heads <- mapM (parseFromString (B.toList . mconcat <$> many plain)) $
|
||||
map removeLeadingTrailingSpace rawHeads
|
||||
return (heads, aligns, indices)
|
||||
|
||||
-- Parse a simple table.
|
||||
simpleTable :: Bool -- ^ Headerless table
|
||||
-> Parser [Char] ParserState Block
|
||||
-> Parser [Char] ParserState Blocks
|
||||
simpleTable headless = do
|
||||
Table c a _w h l <- tableWith (simpleTableHeader headless) simpleTableRow sep simpleTableFooter
|
||||
-- Simple tables get 0s for relative column widths (i.e., use default)
|
||||
return $ Table c a (replicate (length a) 0) h l
|
||||
return $ B.singleton $ Table c a (replicate (length a) 0) h l
|
||||
where
|
||||
sep = return () -- optional (simpleTableSep '-')
|
||||
|
||||
gridTable :: Bool -- ^ Headerless table
|
||||
-> Parser [Char] ParserState Block
|
||||
gridTable = gridTableWith parseBlocks
|
||||
-> Parser [Char] ParserState Blocks
|
||||
gridTable headerless = B.singleton
|
||||
<$> gridTableWith (B.toList <$> parseBlocks) headerless
|
||||
|
||||
table :: Parser [Char] ParserState Block
|
||||
table :: Parser [Char] ParserState Blocks
|
||||
table = gridTable False <|> simpleTable False <|>
|
||||
gridTable True <|> simpleTable True <?> "table"
|
||||
|
||||
--
|
||||
-- inline
|
||||
--
|
||||
|
||||
--
|
||||
-- inline
|
||||
--
|
||||
|
||||
inline :: Parser [Char] ParserState Inline
|
||||
inline :: Parser [Char] ParserState Inlines
|
||||
inline = choice [ whitespace
|
||||
, link
|
||||
, str
|
||||
|
@ -815,36 +802,36 @@ inline = choice [ whitespace
|
|||
, subscript
|
||||
, math
|
||||
, note
|
||||
, smartPunctuation inline
|
||||
, smart
|
||||
, hyphens
|
||||
, escapedChar
|
||||
, symbol ] <?> "inline"
|
||||
|
||||
hyphens :: Parser [Char] ParserState Inline
|
||||
hyphens :: Parser [Char] ParserState Inlines
|
||||
hyphens = do
|
||||
result <- many1 (char '-')
|
||||
option Space endline
|
||||
optional endline
|
||||
-- don't want to treat endline after hyphen or dash as a space
|
||||
return $ Str result
|
||||
return $ B.str result
|
||||
|
||||
escapedChar :: Parser [Char] st Inline
|
||||
escapedChar :: Parser [Char] st Inlines
|
||||
escapedChar = do c <- escaped anyChar
|
||||
return $ if c == ' ' -- '\ ' is null in RST
|
||||
then Str ""
|
||||
else Str [c]
|
||||
then mempty
|
||||
else B.str [c]
|
||||
|
||||
symbol :: Parser [Char] ParserState Inline
|
||||
symbol :: Parser [Char] ParserState Inlines
|
||||
symbol = do
|
||||
result <- oneOf specialChars
|
||||
return $ Str [result]
|
||||
return $ B.str [result]
|
||||
|
||||
-- parses inline code, between codeStart and codeEnd
|
||||
code :: Parser [Char] ParserState Inline
|
||||
code :: Parser [Char] ParserState Inlines
|
||||
code = try $ do
|
||||
string "``"
|
||||
result <- manyTill anyChar (try (string "``"))
|
||||
return $ Code nullAttr
|
||||
$ removeLeadingTrailingSpace $ intercalate " " $ lines result
|
||||
return $ B.code
|
||||
$ removeLeadingTrailingSpace $ unwords $ lines result
|
||||
|
||||
-- succeeds only if we're not right after a str (ie. in middle of word)
|
||||
atStart :: Parser [Char] ParserState a -> Parser [Char] ParserState a
|
||||
|
@ -855,13 +842,13 @@ atStart p = do
|
|||
guard $ stateLastStrPos st /= Just pos
|
||||
p
|
||||
|
||||
emph :: Parser [Char] ParserState Inline
|
||||
emph = enclosed (atStart $ char '*') (char '*') inline >>=
|
||||
return . Emph . normalizeSpaces
|
||||
emph :: Parser [Char] ParserState Inlines
|
||||
emph = B.emph . trimInlines . mconcat <$>
|
||||
enclosed (atStart $ char '*') (char '*') inline
|
||||
|
||||
strong :: Parser [Char] ParserState Inline
|
||||
strong = enclosed (atStart $ string "**") (try $ string "**") inline >>=
|
||||
return . Strong . normalizeSpaces
|
||||
strong :: Parser [Char] ParserState Inlines
|
||||
strong = B.strong . trimInlines . mconcat <$>
|
||||
enclosed (atStart $ string "**") (try $ string "**") inline
|
||||
|
||||
-- Parses inline interpreted text which is required to have the given role.
|
||||
-- This decision is based on the role marker (if present),
|
||||
|
@ -873,8 +860,8 @@ interpreted role = try $ do
|
|||
then try markedInterpretedText <|> unmarkedInterpretedText
|
||||
else markedInterpretedText
|
||||
where
|
||||
markedInterpretedText = try (roleMarker >> unmarkedInterpretedText)
|
||||
<|> (unmarkedInterpretedText >>= (\txt -> roleMarker >> return txt))
|
||||
markedInterpretedText = try (roleMarker *> unmarkedInterpretedText)
|
||||
<|> (unmarkedInterpretedText <* roleMarker)
|
||||
roleMarker = string $ ":" ++ role ++ ":"
|
||||
-- Note, this doesn't precisely implement the complex rule in
|
||||
-- http://docutils.sourceforge.net/docs/ref/rst/restructuredtext.html#inline-markup-recognition-rules
|
||||
|
@ -883,27 +870,27 @@ interpreted role = try $ do
|
|||
result <- enclosed (atStart $ char '`') (char '`') anyChar
|
||||
return result
|
||||
|
||||
superscript :: Parser [Char] ParserState Inline
|
||||
superscript = interpreted "sup" >>= \x -> return (Superscript [Str x])
|
||||
superscript :: Parser [Char] ParserState Inlines
|
||||
superscript = B.superscript . B.str <$> interpreted "sup"
|
||||
|
||||
subscript :: Parser [Char] ParserState Inline
|
||||
subscript = interpreted "sub" >>= \x -> return (Subscript [Str x])
|
||||
subscript :: Parser [Char] ParserState Inlines
|
||||
subscript = B.subscript . B.str <$> interpreted "sub"
|
||||
|
||||
math :: Parser [Char] ParserState Inline
|
||||
math = interpreted "math" >>= \x -> return (Math InlineMath x)
|
||||
math :: Parser [Char] ParserState Inlines
|
||||
math = B.math <$> interpreted "math"
|
||||
|
||||
whitespace :: Parser [Char] ParserState Inline
|
||||
whitespace = many1 spaceChar >> return Space <?> "whitespace"
|
||||
whitespace :: Parser [Char] ParserState Inlines
|
||||
whitespace = B.space <$ skipMany1 spaceChar <?> "whitespace"
|
||||
|
||||
str :: Parser [Char] ParserState Inline
|
||||
str :: Parser [Char] ParserState Inlines
|
||||
str = do
|
||||
let strChar = noneOf ("\t\n " ++ specialChars)
|
||||
result <- many1 strChar
|
||||
updateLastStrPos
|
||||
return $ Str result
|
||||
return $ B.str result
|
||||
|
||||
-- an endline character that can be treated as a space, not a structural break
|
||||
endline :: Parser [Char] ParserState Inline
|
||||
endline :: Parser [Char] ParserState Inlines
|
||||
endline = try $ do
|
||||
newline
|
||||
notFollowedBy blankline
|
||||
|
@ -913,28 +900,27 @@ endline = try $ do
|
|||
then notFollowedBy (anyOrderedListMarker >> spaceChar) >>
|
||||
notFollowedBy' bulletListStart
|
||||
else return ()
|
||||
return Space
|
||||
return B.space
|
||||
|
||||
--
|
||||
-- links
|
||||
--
|
||||
|
||||
link :: Parser [Char] ParserState Inline
|
||||
link :: Parser [Char] ParserState Inlines
|
||||
link = choice [explicitLink, referenceLink, autoLink] <?> "link"
|
||||
|
||||
explicitLink :: Parser [Char] ParserState Inline
|
||||
explicitLink :: Parser [Char] ParserState Inlines
|
||||
explicitLink = try $ do
|
||||
char '`'
|
||||
notFollowedBy (char '`') -- `` marks start of inline code
|
||||
label' <- manyTill (notFollowedBy (char '`') >> inline)
|
||||
(try (spaces >> char '<'))
|
||||
label' <- trimInlines . mconcat <$>
|
||||
manyTill (notFollowedBy (char '`') >> inline) (char '<')
|
||||
src <- manyTill (noneOf ">\n") (char '>')
|
||||
skipSpaces
|
||||
string "`_"
|
||||
return $ Link (normalizeSpaces label')
|
||||
(escapeURI $ removeLeadingTrailingSpace src, "")
|
||||
return $ B.link (escapeURI $ removeLeadingTrailingSpace src) "" label'
|
||||
|
||||
referenceLink :: Parser [Char] ParserState Inline
|
||||
referenceLink :: Parser [Char] ParserState Inlines
|
||||
referenceLink = try $ do
|
||||
(label',ref) <- withRaw (quotedReferenceName <|> simpleReferenceName) >>~
|
||||
char '_'
|
||||
|
@ -953,23 +939,23 @@ referenceLink = try $ do
|
|||
Just target -> return target
|
||||
-- if anonymous link, remove key so it won't be used again
|
||||
when (isAnonKey key) $ updateState $ \s -> s{ stateKeys = M.delete key keyTable }
|
||||
return $ Link (normalizeSpaces label') (src, tit)
|
||||
return $ B.link src tit label'
|
||||
|
||||
autoURI :: Parser [Char] ParserState Inline
|
||||
autoURI :: Parser [Char] ParserState Inlines
|
||||
autoURI = do
|
||||
(orig, src) <- uri
|
||||
return $ Link [Str orig] (src, "")
|
||||
return $ B.link src "" $ B.str orig
|
||||
|
||||
autoEmail :: Parser [Char] ParserState Inline
|
||||
autoEmail :: Parser [Char] ParserState Inlines
|
||||
autoEmail = do
|
||||
(orig, src) <- emailAddress
|
||||
return $ Link [Str orig] (src, "")
|
||||
return $ B.link src "" $ B.str orig
|
||||
|
||||
autoLink :: Parser [Char] ParserState Inline
|
||||
autoLink :: Parser [Char] ParserState Inlines
|
||||
autoLink = autoURI <|> autoEmail
|
||||
|
||||
-- For now, we assume that all substitution references are for images.
|
||||
image :: Parser [Char] ParserState Inline
|
||||
image :: Parser [Char] ParserState Inlines
|
||||
image = try $ do
|
||||
char '|'
|
||||
(_,ref) <- withRaw (manyTill inline (char '|'))
|
||||
|
@ -979,7 +965,7 @@ image = try $ do
|
|||
Nothing -> fail "no corresponding key"
|
||||
Just target -> return target
|
||||
|
||||
note :: Parser [Char] ParserState Inline
|
||||
note :: Parser [Char] ParserState Inlines
|
||||
note = try $ do
|
||||
ref <- noteMarker
|
||||
char '_'
|
||||
|
@ -1000,4 +986,24 @@ note = try $ do
|
|||
then deleteFirstsBy (==) notes [(ref,raw)]
|
||||
else notes
|
||||
updateState $ \st -> st{ stateNotes = newnotes }
|
||||
return $ Note contents
|
||||
return $ B.note contents
|
||||
|
||||
smart :: Parser [Char] ParserState Inlines
|
||||
smart = do
|
||||
getOption readerSmart >>= guard
|
||||
doubleQuoted <|> singleQuoted <|>
|
||||
choice (map (B.singleton <$>) [apostrophe, dash, ellipses])
|
||||
|
||||
singleQuoted :: Parser [Char] ParserState Inlines
|
||||
singleQuoted = try $ do
|
||||
singleQuoteStart
|
||||
withQuoteContext InSingleQuote $
|
||||
B.singleQuoted . trimInlines . mconcat <$>
|
||||
many1Till inline singleQuoteEnd
|
||||
|
||||
doubleQuoted :: Parser [Char] ParserState Inlines
|
||||
doubleQuoted = try $ do
|
||||
doubleQuoteStart
|
||||
withQuoteContext InDoubleQuote $
|
||||
B.doubleQuoted . trimInlines . mconcat <$>
|
||||
many1Till inline doubleQuoteEnd
|
||||
|
|
|
@ -3,115 +3,115 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
[([Str "Revision"],
|
||||
[[Para [Str "3"]]])]
|
||||
,Header 1 [Str "Level",Space,Str "one",Space,Str "header"]
|
||||
,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Str ".",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber",Str "\8217",Str "s",Space,Str "markdown",Space,Str "test",Space,Str "suite",Str "."]
|
||||
,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
|
||||
,Header 2 [Str "Level",Space,Str "two",Space,Str "header"]
|
||||
,Header 3 [Str "Level",Space,Str "three"]
|
||||
,Header 4 [Str "Level",Space,Str "four",Space,Str "with",Space,Emph [Str "emphasis"]]
|
||||
,Header 5 [Str "Level",Space,Str "five"]
|
||||
,Header 1 [Str "Paragraphs"]
|
||||
,Para [Str "Here",Str "\8217",Str "s",Space,Str "a",Space,Str "regular",Space,Str "paragraph",Str "."]
|
||||
,Para [Str "In",Space,Str "Markdown",Space,Str "1",Str ".",Str "0",Str ".",Str "0",Space,Str "and",Space,Str "earlier",Str ".",Space,Str "Version",Space,Str "8",Str ".",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",Space,Str "list",Space,Str "item",Str ".",Space,Str "Because",Space,Str "a",Space,Str "hard",Str "-",Str "wrapped",Space,Str "line",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",Space,Str "looked",Space,Str "like",Space,Str "a",Space,Str "list",Space,Str "item",Str "."]
|
||||
,Para [Str "Here",Str "\8217",Str "s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet",Str ".",Space,Str "*",Space,Str "criminey",Str "."]
|
||||
,Para [Str "Horizontal",Space,Str "rule",Str ":"]
|
||||
,Para [Str "Here\8217s",Space,Str "a",Space,Str "regular",Space,Str "paragraph."]
|
||||
,Para [Str "In",Space,Str "Markdown",Space,Str "1.0.0",Space,Str "and",Space,Str "earlier.",Space,Str "Version",Space,Str "8.",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",Space,Str "list",Space,Str "item.",Space,Str "Because",Space,Str "a",Space,Str "hard-wrapped",Space,Str "line",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",Space,Str "looked",Space,Str "like",Space,Str "a",Space,Str "list",Space,Str "item."]
|
||||
,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",Space,Str "*",Space,Str "criminey."]
|
||||
,Para [Str "Horizontal",Space,Str "rule:"]
|
||||
,HorizontalRule
|
||||
,Para [Str "Another",Str ":"]
|
||||
,Para [Str "Another:"]
|
||||
,HorizontalRule
|
||||
,Header 1 [Str "Block",Space,Str "Quotes"]
|
||||
,Para [Str "Here",Str "\8217",Str "s",Space,Str "a",Space,Str "block",Space,Str "quote",Str ":"]
|
||||
,Para [Str "Here\8217s",Space,Str "a",Space,Str "block",Space,Str "quote:"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote",Str ".",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short",Str "."]]
|
||||
,Para [Str "Here",Str "\8217",Str "s",Space,Str "another,",Space,Str "differently",Space,Str "indented",Str ":"]
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
|
||||
,Para [Str "Here\8217s",Space,Str "another,",Space,Str "differently",Space,Str "indented:"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote",Str ".",Space,Str "It",Str "\8217",Str "s",Space,Str "indented",Space,Str "with",Space,Str "a",Space,Str "tab",Str "."]
|
||||
,Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote",Str ":"]
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",Space,Str "It\8217s",Space,Str "indented",Space,Str "with",Space,Str "a",Space,Str "tab."]
|
||||
,Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote:"]
|
||||
,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"
|
||||
,Para [Str "List",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote",Str ":"]
|
||||
,Para [Str "List",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Plain [Str "item",Space,Str "one"]]
|
||||
,[Plain [Str "item",Space,Str "two"]]]
|
||||
,Para [Str "Nested",Space,Str "block",Space,Str "quotes",Str ":"]
|
||||
,Para [Str "Nested",Space,Str "block",Space,Str "quotes:"]
|
||||
,BlockQuote
|
||||
[Para [Str "nested"]
|
||||
,BlockQuote
|
||||
[Para [Str "nested"]]]]
|
||||
,Header 1 [Str "Code",Space,Str "Blocks"]
|
||||
,Para [Str "Code",Str ":"]
|
||||
,Para [Str "Code:"]
|
||||
,CodeBlock ("",[],[]) "---- (should be four hyphens)\n\nsub status {\n print \"working\";\n}"
|
||||
,CodeBlock ("",[],[]) "this code block is indented by one tab"
|
||||
,Para [Str "And",Str ":"]
|
||||
,Para [Str "And:"]
|
||||
,CodeBlock ("",[],[]) "this block is indented by two tabs\n\nThese should not be escaped: \\$ \\\\ \\> \\[ \\{"
|
||||
,Para [Str "And",Str ":"]
|
||||
,Para [Str "And:"]
|
||||
,CodeBlock ("",["sourceCode","python"],[]) "def my_function(x):\n return x + 1"
|
||||
,Header 1 [Str "Lists"]
|
||||
,Header 2 [Str "Unordered"]
|
||||
,Para [Str "Asterisks",Space,Str "tight",Str ":"]
|
||||
,Para [Str "Asterisks",Space,Str "tight:"]
|
||||
,BulletList
|
||||
[[Plain [Str "asterisk",Space,Str "1"]]
|
||||
,[Plain [Str "asterisk",Space,Str "2"]]
|
||||
,[Plain [Str "asterisk",Space,Str "3"]]]
|
||||
,Para [Str "Asterisks",Space,Str "loose",Str ":"]
|
||||
,Para [Str "Asterisks",Space,Str "loose:"]
|
||||
,BulletList
|
||||
[[Para [Str "asterisk",Space,Str "1"]]
|
||||
,[Para [Str "asterisk",Space,Str "2"]]
|
||||
,[Para [Str "asterisk",Space,Str "3"]]]
|
||||
,Para [Str "Pluses",Space,Str "tight",Str ":"]
|
||||
,Para [Str "Pluses",Space,Str "tight:"]
|
||||
,BulletList
|
||||
[[Plain [Str "Plus",Space,Str "1"]]
|
||||
,[Plain [Str "Plus",Space,Str "2"]]
|
||||
,[Plain [Str "Plus",Space,Str "3"]]]
|
||||
,Para [Str "Pluses",Space,Str "loose",Str ":"]
|
||||
,Para [Str "Pluses",Space,Str "loose:"]
|
||||
,BulletList
|
||||
[[Para [Str "Plus",Space,Str "1"]]
|
||||
,[Para [Str "Plus",Space,Str "2"]]
|
||||
,[Para [Str "Plus",Space,Str "3"]]]
|
||||
,Para [Str "Minuses",Space,Str "tight",Str ":"]
|
||||
,Para [Str "Minuses",Space,Str "tight:"]
|
||||
,BulletList
|
||||
[[Plain [Str "Minus",Space,Str "1"]]
|
||||
,[Plain [Str "Minus",Space,Str "2"]]
|
||||
,[Plain [Str "Minus",Space,Str "3"]]]
|
||||
,Para [Str "Minuses",Space,Str "loose",Str ":"]
|
||||
,Para [Str "Minuses",Space,Str "loose:"]
|
||||
,BulletList
|
||||
[[Para [Str "Minus",Space,Str "1"]]
|
||||
,[Para [Str "Minus",Space,Str "2"]]
|
||||
,[Para [Str "Minus",Space,Str "3"]]]
|
||||
,Header 2 [Str "Ordered"]
|
||||
,Para [Str "Tight",Str ":"]
|
||||
,Para [Str "Tight:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Plain [Str "First"]]
|
||||
,[Plain [Str "Second"]]
|
||||
,[Plain [Str "Third"]]]
|
||||
,Para [Str "and",Str ":"]
|
||||
,Para [Str "and:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Plain [Str "One"]]
|
||||
,[Plain [Str "Two"]]
|
||||
,[Plain [Str "Three"]]]
|
||||
,Para [Str "Loose",Space,Str "using",Space,Str "tabs",Str ":"]
|
||||
,Para [Str "Loose",Space,Str "using",Space,Str "tabs:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "First"]]
|
||||
,[Para [Str "Second"]]
|
||||
,[Para [Str "Third"]]]
|
||||
,Para [Str "and",Space,Str "using",Space,Str "spaces",Str ":"]
|
||||
,Para [Str "and",Space,Str "using",Space,Str "spaces:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "One"]]
|
||||
,[Para [Str "Two"]]
|
||||
,[Para [Str "Three"]]]
|
||||
,Para [Str "Multiple",Space,Str "paragraphs",Str ":"]
|
||||
,Para [Str "Multiple",Space,Str "paragraphs:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one",Str "."]
|
||||
,Para [Str "Item",Space,Str "1",Str ".",Space,Str "graf",Space,Str "two",Str ".",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog",Str "\8217",Str "s",Space,Str "back",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "2",Str "."]]
|
||||
,[Para [Str "Item",Space,Str "3",Str "."]]]
|
||||
,Para [Str "Nested",Str ":"]
|
||||
[[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one."]
|
||||
,Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog\8217s",Space,Str "back."]]
|
||||
,[Para [Str "Item",Space,Str "2."]]
|
||||
,[Para [Str "Item",Space,Str "3."]]]
|
||||
,Para [Str "Nested:"]
|
||||
,BulletList
|
||||
[[Para [Str "Tab"]
|
||||
,BulletList
|
||||
[[Para [Str "Tab"]
|
||||
,BulletList
|
||||
[[Plain [Str "Tab"]]]]]]]
|
||||
,Para [Str "Here",Str "\8217",Str "s",Space,Str "another",Str ":"]
|
||||
,Para [Str "Here\8217s",Space,Str "another:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "First"]]
|
||||
,[Para [Str "Second",Str ":"]
|
||||
,[Para [Str "Second:"]
|
||||
,BlockQuote
|
||||
[BulletList
|
||||
[[Plain [Str "Fee"]]
|
||||
|
@ -129,111 +129,111 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
,OrderedList (1,UpperAlpha,TwoParens)
|
||||
[[Plain [Str "a",Space,Str "subsublist"]]
|
||||
,[Plain [Str "a",Space,Str "subsublist"]]]]]]]
|
||||
,Para [Str "Nesting",Str ":"]
|
||||
,Para [Str "Nesting:"]
|
||||
,OrderedList (1,UpperAlpha,Period)
|
||||
[[Para [Str "Upper",Space,Str "Alpha"]
|
||||
,OrderedList (1,UpperRoman,Period)
|
||||
[[Para [Str "Upper",Space,Str "Roman",Str "."]
|
||||
[[Para [Str "Upper",Space,Str "Roman."]
|
||||
,OrderedList (6,Decimal,TwoParens)
|
||||
[[Para [Str "Decimal",Space,Str "start",Space,Str "with",Space,Str "6"]
|
||||
,OrderedList (3,LowerAlpha,OneParen)
|
||||
[[Plain [Str "Lower",Space,Str "alpha",Space,Str "with",Space,Str "paren"]]]]]]]]]
|
||||
,Para [Str "Autonumbering",Str ":"]
|
||||
,Para [Str "Autonumbering:"]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "Autonumber",Str "."]]
|
||||
,[Para [Str "More",Str "."]
|
||||
[[Plain [Str "Autonumber."]]
|
||||
,[Para [Str "More."]
|
||||
,OrderedList (1,DefaultStyle,DefaultDelim)
|
||||
[[Plain [Str "Nested",Str "."]]]]]
|
||||
,Para [Str "Autonumbering",Space,Str "with",Space,Str "explicit",Space,Str "start",Str ":"]
|
||||
[[Plain [Str "Nested."]]]]]
|
||||
,Para [Str "Autonumbering",Space,Str "with",Space,Str "explicit",Space,Str "start:"]
|
||||
,OrderedList (4,LowerAlpha,TwoParens)
|
||||
[[Plain [Str "item",Space,Str "1"]]
|
||||
,[Plain [Str "item",Space,Str "2"]]]
|
||||
,Header 2 [Str "Definition"]
|
||||
,DefinitionList
|
||||
[([Str "term",Space,Str "1"],
|
||||
[[Para [Str "Definition",Space,Str "1",Str "."]]])
|
||||
[[Para [Str "Definition",Space,Str "1."]]])
|
||||
,([Str "term",Space,Str "2"],
|
||||
[[Para [Str "Definition",Space,Str "2,",Space,Str "paragraph",Space,Str "1",Str "."]
|
||||
,Para [Str "Definition",Space,Str "2,",Space,Str "paragraph",Space,Str "2",Str "."]]])
|
||||
[[Para [Str "Definition",Space,Str "2,",Space,Str "paragraph",Space,Str "1."]
|
||||
,Para [Str "Definition",Space,Str "2,",Space,Str "paragraph",Space,Str "2."]]])
|
||||
,([Str "term",Space,Str "with",Space,Emph [Str "emphasis"]],
|
||||
[[Para [Str "Definition",Space,Str "3",Str "."]]])]
|
||||
[[Para [Str "Definition",Space,Str "3."]]])]
|
||||
,Header 1 [Str "Field",Space,Str "Lists"]
|
||||
,BlockQuote
|
||||
[DefinitionList
|
||||
[([Str "address"],
|
||||
[[Para [Str "61",Space,Str "Main",Space,Str "St",Str "."]]])
|
||||
[[Para [Str "61",Space,Str "Main",Space,Str "St."]]])
|
||||
,([Str "city"],
|
||||
[[Para [Emph [Str "Nowhere"],Str ",",Space,Str "MA,",Space,Str "USA"]]])
|
||||
,([Str "phone"],
|
||||
[[Para [Str "123",Str "-",Str "4567"]]])]]
|
||||
[[Para [Str "123-4567"]]])]]
|
||||
,DefinitionList
|
||||
[([Str "address"],
|
||||
[[Para [Str "61",Space,Str "Main",Space,Str "St",Str "."]]])
|
||||
[[Para [Str "61",Space,Str "Main",Space,Str "St."]]])
|
||||
,([Str "city"],
|
||||
[[Para [Emph [Str "Nowhere"],Str ",",Space,Str "MA,",Space,Str "USA"]]])
|
||||
,([Str "phone"],
|
||||
[[Para [Str "123",Str "-",Str "4567"]]])]
|
||||
[[Para [Str "123-4567"]]])]
|
||||
,Header 1 [Str "HTML",Space,Str "Blocks"]
|
||||
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line",Str ":"]
|
||||
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line:"]
|
||||
,RawBlock "html" "<div>foo</div>\n"
|
||||
,Para [Str "Now,",Space,Str "nested",Str ":"]
|
||||
,Para [Str "Now,",Space,Str "nested:"]
|
||||
,RawBlock "html" "<div>\n <div>\n <div>\n foo\n </div>\n </div>\n</div>\n"
|
||||
,Header 1 [Str "LaTeX",Space,Str "Block"]
|
||||
,RawBlock "latex" "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}\n"
|
||||
,Header 1 [Str "Inline",Space,Str "Markup"]
|
||||
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ".",Space,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str "."]
|
||||
,Para [Str "This",Space,Str "is",Space,Str "code",Str ":",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
|
||||
,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
|
||||
,Para [Str "This",Space,Str "is",Subscript [Str "subscripted"],Space,Str "and",Space,Str "this",Space,Str "is",Space,Superscript [Str "superscripted"],Str "."]
|
||||
,Header 1 [Str "Special",Space,Str "Characters"]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode",Str ":"]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"]
|
||||
,BulletList
|
||||
[[Plain [Str "I",Space,Str "hat",Str ":",Space,Str "\206"]]
|
||||
,[Plain [Str "o",Space,Str "umlaut",Str ":",Space,Str "\246"]]
|
||||
,[Plain [Str "section",Str ":",Space,Str "\167"]]
|
||||
,[Plain [Str "set",Space,Str "membership",Str ":",Space,Str "\8712"]]
|
||||
,[Plain [Str "copyright",Str ":",Space,Str "\169"]]]
|
||||
,Para [Str "AT&T",Space,Str "has",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "their",Space,Str "name",Str "."]
|
||||
,Para [Str "This",Space,Str "&",Space,Str "that",Str "."]
|
||||
,Para [Str "4",Space,Str "<",Space,Str "5",Str "."]
|
||||
,Para [Str "6",Space,Str ">",Space,Str "5",Str "."]
|
||||
,Para [Str "Backslash",Str ":",Space,Str "\\"]
|
||||
,Para [Str "Backtick",Str ":",Space,Str "`"]
|
||||
,Para [Str "Asterisk",Str ":",Space,Str "*"]
|
||||
,Para [Str "Underscore",Str ":",Space,Str "_"]
|
||||
,Para [Str "Left",Space,Str "brace",Str ":",Space,Str "{"]
|
||||
,Para [Str "Right",Space,Str "brace",Str ":",Space,Str "}"]
|
||||
,Para [Str "Left",Space,Str "bracket",Str ":",Space,Str "["]
|
||||
,Para [Str "Right",Space,Str "bracket",Str ":",Space,Str "]"]
|
||||
,Para [Str "Left",Space,Str "paren",Str ":",Space,Str "("]
|
||||
,Para [Str "Right",Space,Str "paren",Str ":",Space,Str ")"]
|
||||
,Para [Str "Greater",Str "-",Str "than",Str ":",Space,Str ">"]
|
||||
,Para [Str "Hash",Str ":",Space,Str "#"]
|
||||
,Para [Str "Period",Str ":",Space,Str "."]
|
||||
,Para [Str "Bang",Str ":",Space,Str "!"]
|
||||
,Para [Str "Plus",Str ":",Space,Str "+"]
|
||||
,Para [Str "Minus",Str ":",Space,Str "-"]
|
||||
[[Plain [Str "I",Space,Str "hat:",Space,Str "\206"]]
|
||||
,[Plain [Str "o",Space,Str "umlaut:",Space,Str "\246"]]
|
||||
,[Plain [Str "section:",Space,Str "\167"]]
|
||||
,[Plain [Str "set",Space,Str "membership:",Space,Str "\8712"]]
|
||||
,[Plain [Str "copyright:",Space,Str "\169"]]]
|
||||
,Para [Str "AT&T",Space,Str "has",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "their",Space,Str "name."]
|
||||
,Para [Str "This",Space,Str "&",Space,Str "that."]
|
||||
,Para [Str "4",Space,Str "<",Space,Str "5."]
|
||||
,Para [Str "6",Space,Str ">",Space,Str "5."]
|
||||
,Para [Str "Backslash:",Space,Str "\\"]
|
||||
,Para [Str "Backtick:",Space,Str "`"]
|
||||
,Para [Str "Asterisk:",Space,Str "*"]
|
||||
,Para [Str "Underscore:",Space,Str "_"]
|
||||
,Para [Str "Left",Space,Str "brace:",Space,Str "{"]
|
||||
,Para [Str "Right",Space,Str "brace:",Space,Str "}"]
|
||||
,Para [Str "Left",Space,Str "bracket:",Space,Str "["]
|
||||
,Para [Str "Right",Space,Str "bracket:",Space,Str "]"]
|
||||
,Para [Str "Left",Space,Str "paren:",Space,Str "("]
|
||||
,Para [Str "Right",Space,Str "paren:",Space,Str ")"]
|
||||
,Para [Str "Greater-than:",Space,Str ">"]
|
||||
,Para [Str "Hash:",Space,Str "#"]
|
||||
,Para [Str "Period:",Space,Str "."]
|
||||
,Para [Str "Bang:",Space,Str "!"]
|
||||
,Para [Str "Plus:",Space,Str "+"]
|
||||
,Para [Str "Minus:",Space,Str "-"]
|
||||
,Header 1 [Str "Links"]
|
||||
,Para [Str "Explicit",Str ":",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."]
|
||||
,Para [Str "Two",Space,Str "anonymous",Space,Str "links",Str ":",Space,Link [Str "the",Space,Str "first"] ("/url1/",""),Space,Str "and",Space,Link [Str "the",Space,Str "second"] ("/url2/","")]
|
||||
,Para [Str "Reference",Space,Str "links",Str ":",Space,Link [Str "link1"] ("/url1/",""),Space,Str "and",Space,Link [Str "link2"] ("/url2/",""),Space,Str "and",Space,Link [Str "link1"] ("/url1/",""),Space,Str "again",Str "."]
|
||||
,Para [Str "Here",Str "\8217",Str "s",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
|
||||
,Para [Str "Here",Str "\8217",Str "s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text",Str ":",Space,Link [Str "AT&T"] ("/url/",""),Str "."]
|
||||
,Para [Str "Autolinks",Str ":",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2",""),Space,Str "and",Space,Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net",""),Str "."]
|
||||
,Para [Str "But",Space,Str "not",Space,Str "here",Str ":"]
|
||||
,Para [Str "Explicit:",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."]
|
||||
,Para [Str "Two",Space,Str "anonymous",Space,Str "links:",Space,Link [Str "the",Space,Str "first"] ("/url1/",""),Space,Str "and",Space,Link [Str "the",Space,Str "second"] ("/url2/","")]
|
||||
,Para [Str "Reference",Space,Str "links:",Space,Link [Str "link1"] ("/url1/",""),Space,Str "and",Space,Link [Str "link2"] ("/url2/",""),Space,Str "and",Space,Link [Str "link1"] ("/url1/",""),Space,Str "again."]
|
||||
,Para [Str "Here\8217s",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
|
||||
,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("/url/",""),Str "."]
|
||||
,Para [Str "Autolinks:",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2",""),Space,Str "and",Space,Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net",""),Str "."]
|
||||
,Para [Str "But",Space,Str "not",Space,Str "here:"]
|
||||
,CodeBlock ("",[],[]) "http://example.com/"
|
||||
,Header 1 [Str "Images"]
|
||||
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(",Str "1902",Str ")",Str ":"]
|
||||
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
|
||||
,Para [Image [Str "image"] ("lalune.jpg","")]
|
||||
,Para [Image [Str "Voyage dans la Lune"] ("lalune.jpg","")]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon",Str "."]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
|
||||
,Para [Str "And",Space,Str "an",Space,Link [Image [Str "A movie"] ("movie.jpg","")] ("/url",""),Str "."]
|
||||
,Header 1 [Str "Comments"]
|
||||
,Para [Str "First",Space,Str "paragraph"]
|
||||
,Para [Str "Another",Space,Str "paragraph"]
|
||||
,Para [Str "A",Space,Str "third",Space,Str "paragraph"]
|
||||
,Header 1 [Str "Line",Space,Str "blocks"]
|
||||
,Para [Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be",LineBreak,Str " ",Str "or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,",LineBreak,Str " ",Str "when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,",LineBreak,Str " ",Str "due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"]
|
||||
,Para [Str "Continuation",Space,Str "line",LineBreak,Str " ",Str "and",Space,Str "another"]
|
||||
,Para [Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be",LineBreak,Str " or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,",LineBreak,Str " when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,",LineBreak,Str " due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"]
|
||||
,Para [Str "Continuation",Space,Str "line",LineBreak,Str " and",Space,Str "another"]
|
||||
,Header 1 [Str "Simple",Space,Str "Tables"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0]
|
||||
[[Plain [Str "col",Space,Str "1"]]
|
||||
|
@ -302,25 +302,25 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
|
|||
,[Plain [Str "b",Space,Str "2"]]]]
|
||||
,[Plain [Str "c",Space,Str "c",Space,Str "2",Space,Str "c",Space,Str "2"]]]]
|
||||
,Header 1 [Str "Footnotes"]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with",Space,Str "one",Space,Str "line",Str "."]]]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with",Space,Str "continuation",Space,Str "line",Str "."]]]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with"],Para [Str "continuation",Space,Str "block",Str "."]]]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with",Space,Str "continuation",Space,Str "line"],Para [Str "and",Space,Str "a",Space,Str "second",Space,Str "para",Str "."]]]
|
||||
,Para [Str "Not",Space,Str "in",Space,Str "note",Str "."]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with",Space,Str "one",Space,Str "line."]]]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with",Space,Str "continuation",Space,Str "line."]]]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with"],Para [Str "continuation",Space,Str "block."]]]
|
||||
,Para [Note [Para [Str "Note",Space,Str "with",Space,Str "continuation",Space,Str "line"],Para [Str "and",Space,Str "a",Space,Str "second",Space,Str "para."]]]
|
||||
,Para [Str "Not",Space,Str "in",Space,Str "note."]
|
||||
,Header 1 [Str "Math"]
|
||||
,Para [Str "Some",Space,Str "inline",Space,Str "math",Space,Math InlineMath "E=mc^2",Str ".",Space,Str "Now",Space,Str "some",Space,Str "display",Space,Str "math",Str ":"]
|
||||
,Para [Str "Some",Space,Str "inline",Space,Str "math",Space,Math InlineMath "E=mc^2",Str ".",Space,Str "Now",Space,Str "some",Space,Str "display",Space,Str "math:"]
|
||||
,Para [Math DisplayMath "E=mc^2"]
|
||||
,Para [Math DisplayMath "E = mc^2"]
|
||||
,Para [Math DisplayMath "E = mc^2",Math DisplayMath "\\alpha = \\beta"]
|
||||
,Para [Math DisplayMath "E &= mc^2\\\\\nF &= \\pi E",Math DisplayMath "F &= \\gamma \\alpha^2"]
|
||||
,Para [Str "All",Space,Str "done",Str "."]
|
||||
,Header 1 [Str "Default",Str "-",Str "Role"]
|
||||
,Para [Str "Try",Space,Str "changing",Space,Str "the",Space,Str "default",Space,Str "role",Space,Str "to",Space,Str "a",Space,Str "few",Space,Str "different",Space,Str "things",Str "."]
|
||||
,Header 2 [Str "Doesn",Str "\8217",Str "t",Space,Str "Break",Space,Str "Title",Space,Str "Parsing"]
|
||||
,Para [Str "Inline",Space,Str "math",Str ":",Space,Math InlineMath "E=mc^2",Space,Str "or",Space,Math InlineMath "E=mc^2",Space,Str "or",Space,Math InlineMath "E=mc^2",Str ".",Space,Str "Other",Space,Str "roles",Str ":",Space,Superscript [Str "super"],Str ",",Space,Subscript [Str "sub"],Str "."]
|
||||
,Para [Str "All",Space,Str "done."]
|
||||
,Header 1 [Str "Default-Role"]
|
||||
,Para [Str "Try",Space,Str "changing",Space,Str "the",Space,Str "default",Space,Str "role",Space,Str "to",Space,Str "a",Space,Str "few",Space,Str "different",Space,Str "things."]
|
||||
,Header 2 [Str "Doesn\8217t",Space,Str "Break",Space,Str "Title",Space,Str "Parsing"]
|
||||
,Para [Str "Inline",Space,Str "math:",Space,Math InlineMath "E=mc^2",Space,Str "or",Space,Math InlineMath "E=mc^2",Space,Str "or",Space,Math InlineMath "E=mc^2",Str ".",Space,Str "Other",Space,Str "roles:",Space,Superscript [Str "super"],Str ",",Space,Subscript [Str "sub"],Str "."]
|
||||
,Para [Math DisplayMath "\\alpha = beta",Math DisplayMath "E = mc^2"]
|
||||
,Para [Str "Some",Space,Superscript [Str "of"],Space,Str "these",Space,Superscript [Str "words"],Space,Str "are",Space,Str "in",Space,Superscript [Str "superscript"],Str "."]
|
||||
,Para [Str "Reset",Space,Str "default",Str "-",Str "role",Space,Str "to",Space,Str "the",Space,Str "default",Space,Str "default",Str "."]
|
||||
,Para [Str "And",Space,Str "now",Space,Str "`",Str "some",Str "-",Str "invalid",Str "-",Str "string",Str "-",Str "3231231",Str "`",Space,Str "is",Space,Str "nonsense",Str "."]
|
||||
,Para [Str "Reset",Space,Str "default-role",Space,Str "to",Space,Str "the",Space,Str "default",Space,Str "default."]
|
||||
,Para [Str "And",Space,Str "now",Space,Str "`some-invalid-string-3231231`",Space,Str "is",Space,Str "nonsense."]
|
||||
,Header 2 [Str "Literal",Space,Str "symbols"]
|
||||
,Para [Str "2",Str "*",Str "2",Space,Str "=",Space,Str "4",Str "*",Str "1"]]
|
||||
,Para [Str "2*2",Space,Str "=",Space,Str "4*1"]]
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
[Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption",Str ":"]
|
||||
[Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.125,0.1125,0.1375,0.15]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
|
@ -16,8 +16,8 @@
|
|||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Para [Str "Table",Str ":",Space,Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax",Str "."]
|
||||
,Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption",Str ":"]
|
||||
,Para [Str "Table:",Space,Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]
|
||||
,Para [Str "Simple",Space,Str "table",Space,Str "without",Space,Str "caption:"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.125,0.1125,0.1375,0.15]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
|
@ -35,7 +35,7 @@
|
|||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Para [Str "Simple",Space,Str "table",Space,Str "indented",Space,Str "two",Space,Str "spaces",Str ":"]
|
||||
,Para [Str "Simple",Space,Str "table",Space,Str "indented",Space,Str "two",Space,Str "spaces:"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.125,0.1125,0.1375,0.15]
|
||||
[[Plain [Str "Right"]]
|
||||
,[Plain [Str "Left"]]
|
||||
|
@ -53,8 +53,8 @@
|
|||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Para [Str "Table",Str ":",Space,Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax",Str "."]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption",Str ":"]
|
||||
,Para [Str "Table:",Space,Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.175,0.1625,0.1875,0.3625]
|
||||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
|
@ -62,14 +62,14 @@
|
|||
,[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 "12.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."]]]
|
||||
,[[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 "Table",Str ":",Space,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 "."]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption",Str ":"]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
,Para [Str "Table:",Space,Str "Here's",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.175,0.1625,0.1875,0.3625]
|
||||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
|
@ -77,13 +77,13 @@
|
|||
,[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 "12.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."]]]
|
||||
,[[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 "Table",Space,Str "without",Space,Str "column",Space,Str "headers",Str ":"]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1,0.1,0.1,0.1]
|
||||
[[]
|
||||
,[]
|
||||
|
@ -101,7 +101,7 @@
|
|||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "column",Space,Str "headers",Str ":"]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "column",Space,Str "headers:"]
|
||||
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.175,0.1625,0.1875,0.3625]
|
||||
[[]
|
||||
,[]
|
||||
|
@ -109,9 +109,9 @@
|
|||
,[]]
|
||||
[[[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 "12.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."]]]
|
||||
,[[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 "."]]]]]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]]
|
||||
|
|
Loading…
Reference in a new issue