aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt1
-rw-r--r--cabal.project5
-rw-r--r--pandoc.cabal6
-rw-r--r--src/Text/Pandoc/Readers.hs3
-rw-r--r--src/Text/Pandoc/Readers/AsciiDoc.hs402
-rw-r--r--stack.yaml6
-rw-r--r--test/Tests/Old.hs12
-rw-r--r--test/asciidoc-reader-include.adoc4
-rw-r--r--test/asciidoc-reader-include.rb4
-rw-r--r--test/asciidoc-reader.adoc908
-rw-r--r--test/asciidoc-reader.native4406
11 files changed, 5751 insertions, 6 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index c3b657f72..3b02b6843 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -233,6 +233,7 @@ header when requesting a document from a URL:
: Specify input format. *FORMAT* can be:
::: {#input-formats}
+ - `asciidoc` ([AsciiDoc] markup)
- `bibtex` ([BibTeX] bibliography)
- `biblatex` ([BibLaTeX] bibliography)
- `bits` ([BITS] XML, alias for `jats`)
diff --git a/cabal.project b/cabal.project
index 8897c8f00..d223052e9 100644
--- a/cabal.project
+++ b/cabal.project
@@ -26,3 +26,8 @@ source-repository-package
type: git
location: https://github.com/jgm/djoths.git
tag: 7dc8da53fc092d2d4d91f5f0988840f4faf90368
+
+source-repository-package
+ type: git
+ location: https://github.com/jgm/asciidoc-hs.git
+ tag: 6a632651458c9b5334d638993a5ed23c6214cb26
diff --git a/pandoc.cabal b/pandoc.cabal
index 8aa2ddd1d..8841fb8dd 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -275,6 +275,10 @@ extra-source-files:
test/command/6466-whole.hs
test/command/7861.yaml
test/command/7861/metadata/placeholder
+ test/asciidoc-reader.adoc
+ test/asciidoc-reader.native
+ test/asciidoc-reader-include.rb
+ test/asciidoc-reader-include.adoc
test/docbook-chapter.docbook
test/docbook-reader.docbook
test/docbook-xref.docbook
@@ -566,6 +570,7 @@ library
typst >= 0.8.0.2 && < 0.9,
vector >= 0.12 && < 0.14,
djot >= 0.1.2.3 && < 0.2,
+ asciidoc >= 0.1 && < 0.2,
tls >= 2.0.1 && < 2.2,
crypton-x509-system >= 1.6.7 && < 1.7
@@ -590,6 +595,7 @@ library
Text.Pandoc.Translations,
Text.Pandoc.Translations.Types,
Text.Pandoc.Readers,
+ Text.Pandoc.Readers.AsciiDoc,
Text.Pandoc.Readers.HTML,
Text.Pandoc.Readers.LaTeX,
Text.Pandoc.Readers.Markdown,
diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs
index beec98587..5fa0ebeb7 100644
--- a/src/Text/Pandoc/Readers.hs
+++ b/src/Text/Pandoc/Readers.hs
@@ -25,6 +25,7 @@ module Text.Pandoc.Readers
-- * Readers: converting /to/ Pandoc format
Reader (..)
, readers
+ , readAsciiDoc
, readDocx
, readPptx
, readXlsx
@@ -84,6 +85,7 @@ import Text.Pandoc.Error
import Text.Pandoc.Extensions
import qualified Text.Pandoc.Format as Format
import Text.Pandoc.Options
+import Text.Pandoc.Readers.AsciiDoc
import Text.Pandoc.Readers.CommonMark
import Text.Pandoc.Readers.Markdown
import Text.Pandoc.Readers.Creole
@@ -142,6 +144,7 @@ readers = [("native" , TextReader readNative)
,("markdown_mmd", TextReader readMarkdown)
,("commonmark" , TextReader readCommonMark)
,("commonmark_x" , TextReader readCommonMark)
+ ,("asciidoc" , TextReader readAsciiDoc)
,("creole" , TextReader readCreole)
,("dokuwiki" , TextReader readDokuWiki)
,("gfm" , TextReader readCommonMark)
diff --git a/src/Text/Pandoc/Readers/AsciiDoc.hs b/src/Text/Pandoc/Readers/AsciiDoc.hs
new file mode 100644
index 000000000..f48eb43d0
--- /dev/null
+++ b/src/Text/Pandoc/Readers/AsciiDoc.hs
@@ -0,0 +1,402 @@
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE FlexibleContexts #-}
+
+{- |
+ Module : Text.Pandoc.Readers.AsciiDoc
+ Copyright : Copyright (C) 2024 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <[email protected]>
+ Stability : alpha
+ Portability : portable
+
+Reads and evaluates a AsciiDoc document as a Pandoc AST.
+-}
+module Text.Pandoc.Readers.AsciiDoc
+ ( readAsciiDoc
+ )
+where
+
+import Text.Pandoc.Class
+import Text.Pandoc.Sources
+import Text.Pandoc.Options
+import Text.Pandoc.Definition
+import Text.Pandoc.Walk
+import Text.Pandoc.Shared (addPandocAttributes, blocksToInlines, safeRead,
+ tshow)
+import qualified Text.Pandoc.UTF8 as UTF8
+import qualified AsciiDoc as A
+import Text.Pandoc.Error
+import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Readers.HTML (readHtml)
+import Control.Monad.Except (throwError)
+import Control.Monad (mplus)
+import Text.Pandoc.Parsing (newPos)
+import Text.Pandoc.Logging
+import Control.Monad.State
+import Data.List (intersperse, foldl')
+import Data.Char (chr)
+import qualified Data.Text as T
+import qualified Data.Map as M
+import Data.Maybe (fromMaybe)
+
+-- import Debug.Trace
+
+-- | Read AsciiDoc from an input string and return a Pandoc document.
+readAsciiDoc :: (PandocMonad m, ToSources a) => ReaderOptions -> a -> m Pandoc
+readAsciiDoc _opts inp =
+ A.parseDocument getIncludeFile raiseError
+ (sourcesToText (toSources inp))
+ >>= resolveFootnotes
+ >>= resolveStem
+ >>= resolveIcons
+ >>= toPandoc
+ where
+ getIncludeFile fp = UTF8.toText <$> readFileStrict fp
+ raiseError pos msg = throwError $ PandocParseError $ T.pack
+ $ msg <> " at position " <> show pos
+
+toPandoc :: PandocMonad m => A.Document -> m Pandoc
+toPandoc doc =
+ Pandoc <$> doMeta (A.docMeta doc)
+ <*> (B.toList <$> doBlocks (A.docBlocks doc))
+
+resolveFootnotes :: Monad m => A.Document -> m A.Document
+resolveFootnotes doc = do
+ evalStateT (A.mapInlines go doc) (mempty :: M.Map T.Text [A.Inline])
+ where
+ go (A.Inline attr (A.Footnote (Just (A.FootnoteId fnid)) ils)) = do
+ fnmap <- get
+ case M.lookup fnid fnmap of
+ Just ils' ->
+ pure $ A.Inline attr (A.Footnote (Just (A.FootnoteId fnid)) ils')
+ Nothing -> do
+ put $ M.insert fnid ils fnmap
+ pure $ A.Inline attr (A.Footnote (Just (A.FootnoteId fnid)) ils)
+ go x = pure x
+
+resolveStem :: Monad m => A.Document -> m A.Document
+resolveStem doc = do
+ let defaultType = case M.lookup "stem" (A.docAttributes (A.docMeta doc)) of
+ Just "asciimath" -> A.AsciiMath
+ _ -> A.LaTeXMath
+ let doInlineStem (A.Inline attr (A.Math Nothing t)) =
+ pure $ A.Inline attr (A.Math (Just defaultType) t)
+ doInlineStem x = pure x
+ let doBlockStem (A.Block attr mbtit (A.MathBlock Nothing t)) =
+ pure $ A.Block attr mbtit (A.MathBlock (Just defaultType) t)
+ doBlockStem x = A.mapInlines doInlineStem x
+ A.mapBlocks doBlockStem doc
+
+-- resolve icons as either characters in an icon font or images
+resolveIcons :: Monad m => A.Document -> m A.Document
+resolveIcons doc = A.mapInlines fromIcon doc
+ where
+ docattrs = A.docAttributes (A.docMeta doc)
+ iconFont = case M.lookup "icons" docattrs of
+ Just "font" -> True
+ _ -> False
+ iconsdir = fromMaybe "./images/icons" $ M.lookup "iconsdir" docattrs
+ icontype = fromMaybe "png" $ M.lookup "icontype" docattrs
+ addClasses cls (A.Attr ps kvs) =
+ A.Attr ps $
+ case M.lookup "role" kvs of
+ Just r -> M.insert "role" (T.unwords (r : cls)) kvs
+ Nothing -> M.insert "role" (T.unwords cls) kvs
+ fromIcon (A.Inline attr (A.Icon name)) =
+ if iconFont
+ then pure $
+ A.Inline (addClasses ["fa", "fa-" <> name] attr) (A.Span [])
+ else pure $ -- default is to use an image
+ A.Inline (addClasses ["icon"] attr)
+ (A.InlineImage
+ (A.Target
+ (iconsdir <> "/" <> name <> "." <> icontype))
+ Nothing Nothing Nothing)
+ fromIcon x = pure x
+
+addAttribution :: Maybe A.Attribution -> B.Blocks -> B.Blocks
+addAttribution Nothing bs = bs
+addAttribution (Just (A.Attribution t)) bs = B.fromList $
+ case B.toList bs of
+ [B.Div attr bls] -> [B.Div attr (bls ++ [attrBlock])]
+ [B.BlockQuote bls] -> [B.BlockQuote (bls ++ [attrBlock])]
+ xs -> xs ++ [attrBlock]
+ where
+ attrBlock = Para (B.toList $ B.text $ "\x2014 " <> t)
+
+doMeta :: PandocMonad m => A.Meta -> m B.Meta
+doMeta meta = do
+ tit' <- doInlines (A.docTitle meta)
+ pure $
+ (if tit' == mempty
+ then id
+ else B.setMeta "title" tit') .
+ (case A.docAuthors meta of
+ [] -> id
+ as -> B.setMeta "author" (map fromAuthor as)) .
+ (case A.docRevision meta of
+ Nothing -> id
+ Just (A.Revision vers mbdate mbremark) ->
+ B.setMeta "version" vers .
+ maybe id (B.setMeta "date") mbdate .
+ maybe id (B.setMeta "remark") mbremark) .
+ flip (foldl' (\m (k,v) ->
+ -- leave out flags that are set just for processing
+ if k == "sectids" || k == "stem"
+ then m
+ else if T.null v
+ then B.setMeta k True m
+ else B.setMeta k v m))
+ (M.toList (A.docAttributes meta))
+ $ mempty
+
+fromAuthor :: A.Author -> B.Inlines
+fromAuthor au = B.text (A.authorName au) <>
+ maybe mempty (\email ->
+ " (" <> B.link ("mailto:" <> email) "" (B.str email) <> ")")
+ (A.authorEmail au)
+
+doBlocks :: PandocMonad m => [A.Block] -> m B.Blocks
+doBlocks = fmap mconcat . mapM doBlock
+
+addBlockAttr :: A.Attr -> B.Blocks -> B.Blocks
+addBlockAttr (A.Attr _ kvs') bs =
+ case B.toList bs of
+ x@(B.OrderedList{}) : xs -> -- "start" is handled in list attribs
+ addPandocAttributes (M.toList $ M.delete "start" kvs)
+ (B.singleton x) <> B.fromList xs
+ x:xs -> addPandocAttributes (M.toList kvs) (B.singleton x)
+ <> B.fromList xs
+ [] -> mempty
+ where
+ kvs = M.mapKeys (\k -> if k == "role" then "class" else k) kvs'
+
+addBlockTitle :: B.Inlines -> B.Blocks -> B.Blocks
+addBlockTitle tit' bs =
+ let tit = B.toList tit'
+ in case B.toList bs of
+ [B.Table attr _ colspecs thead tbody tfoot] ->
+ B.singleton $ B.Table attr (B.Caption Nothing [B.Plain tit])
+ colspecs thead tbody tfoot
+ [B.Figure attr _ bs'] ->
+ B.singleton $ B.Figure attr (B.Caption Nothing [B.Plain tit]) bs'
+ [B.Div attr (B.Div ("",["title"],[]) [Para _] : bs')] ->
+ -- replace existing title, which might be e.g. "Note"
+ B.singleton $ B.Div attr (B.Div ("",["title"],[]) [B.Para tit] : bs')
+ [B.Div attr bs'] -> -- put title Div inside
+ B.singleton $ B.Div attr (B.Div ("",["title"],[]) [B.Para tit] : bs')
+ _ -> B.divWith B.nullAttr (B.divWith ("",["title"],[]) (B.para tit') <> bs)
+
+doBlock :: PandocMonad m => A.Block -> m B.Blocks
+doBlock (A.Block attr@(A.Attr ps kvs) mbtitle bt) = do
+ mbtitle' <- case mbtitle of
+ Nothing -> pure Nothing
+ Just (A.BlockTitle ils) -> Just <$> doInlines ils
+ addBlockAttr attr . maybe id addBlockTitle mbtitle' <$>
+ case bt of
+ A.Section (A.Level lev) ils bs -> do
+ ils' <- doInlines ils
+ bs' <- doBlocks bs
+ pure $ (B.header lev ils') <> bs'
+ A.DiscreteHeading (A.Level lev) ils ->
+ B.header lev <$> doInlines ils
+ A.Paragraph ils -> B.para <$> doInlines ils
+ A.LiteralBlock t -> pure $ B.codeBlock t
+ A.Listing mblang lns -> do
+ let fromCallout (A.Callout i)
+ | i <= 20 = T.pack [' ', chr (0x2460 + i - 1)]
+ | otherwise = "<" <> tshow i <> ">"
+ let fromSourceLine (A.SourceLine t callouts) =
+ t <> mconcat (map fromCallout callouts)
+ let code = T.intercalate "\n" $ map fromSourceLine lns
+ let classes = case mblang of
+ Nothing -> []
+ Just (A.Language l) -> [l]
+ pure $ B.codeBlockWith ("", classes, []) code
+ A.IncludeListing _ _ Nothing -> pure mempty
+ A.IncludeListing mblang _fp (Just lns) ->
+ doBlock (A.Block attr mbtitle (A.Listing mblang lns))
+ A.ExampleBlock bs -> B.divWith ("",["example"],[]) <$> doBlocks bs
+ A.Sidebar bs -> B.divWith ("",["sidebar"],[]) <$> doBlocks bs
+ A.OpenBlock bs -> B.divWith ("",[],[]) <$> doBlocks bs
+ A.QuoteBlock mbattrib bs ->
+ addAttribution mbattrib . B.blockQuote <$> doBlocks bs
+ A.Verse mbattrib bs ->
+ addAttribution mbattrib . B.blockQuote <$> doBlocks bs
+ -- TODO when texmath's asciimath parser works, convert:
+ A.MathBlock (Just A.AsciiMath) t -> pure $ B.para $ B.displayMath t
+ A.MathBlock (Just A.LaTeXMath) t -> pure $ B.para $ B.displayMath t
+ A.MathBlock Nothing _ ->
+ throwError $ PandocParseError "Encountered math type Nothing"
+ A.List (A.BulletList _) items ->
+ B.bulletList <$> mapM doItem items
+ A.List A.CheckList items ->
+ B.bulletList <$> mapM doItem items
+ A.List (A.OrderedList _ mbstart) items -> do
+ let start = fromMaybe (1 :: Int)
+ (mbstart `mplus` (M.lookup "start" kvs >>= safeRead))
+ let getStyle xs = case xs of
+ "arabic":_ -> Decimal
+ "decimal":_ -> Decimal
+ "loweralpha":_ -> LowerAlpha
+ "upperalpha":_ -> UpperAlpha
+ "lowerroman":_ -> LowerRoman
+ "upperroman":_ -> UpperRoman
+ _:rest -> getStyle rest
+ [] -> DefaultStyle
+ let sty = getStyle ps
+ let delim = DefaultDelim
+ B.orderedListWith (start, sty, delim) <$> mapM doItem items
+ A.List A.CalloutList items ->
+ B.divWith ("",["callout-list"],[]) . B.orderedList <$> mapM doItem items
+ A.DefinitionList items
+ | "ordered" `elem` ps ->
+ B.orderedList <$>
+ mapM (fmap (B.definitionList . (:[])) . doDefListItem) items
+ | otherwise -> B.definitionList <$> mapM doDefListItem items
+ A.Table specs mbHeader rows mbFooter -> do
+ let toAlign A.AlignLeft = B.AlignLeft
+ toAlign A.AlignCenter = B.AlignCenter
+ toAlign A.AlignRight = B.AlignRight
+ let fromCell (A.TableCell bs mbHorizAlign _mbVertAlign colspan rowspan) =
+ B.Cell B.nullAttr (maybe B.AlignDefault toAlign mbHorizAlign)
+ (B.RowSpan rowspan) (B.ColSpan colspan) . B.toList
+ <$> doBlocks bs
+ let fromRow (A.TableRow cs) = B.Row B.nullAttr <$> mapM fromCell cs
+ tbody <- B.TableBody B.nullAttr (B.RowHeadColumns 0) [] <$> mapM fromRow rows
+ thead <- B.TableHead B.nullAttr <$> maybe (pure []) (mapM fromRow) mbHeader
+ tfoot <- B.TableFoot B.nullAttr <$> maybe (pure []) (mapM fromRow) mbFooter
+ let totalWidth = sum $ map (fromMaybe 1 . A.colWidth) specs
+ let toColSpec spec = (maybe B.AlignDefault toAlign (A.colHorizAlign spec),
+ maybe B.ColWidthDefault
+ (B.ColWidth . (\x ->
+ fromIntegral x / fromIntegral totalWidth))
+ (A.colWidth spec))
+ let colspecs = map toColSpec specs
+ pure $ B.table (B.Caption Nothing mempty) -- added by addBlockTitle
+ colspecs thead [tbody] tfoot
+ A.BlockImage target mbalt mbw mbh -> do
+ img' <- doInline (A.Inline mempty (A.InlineImage target mbalt mbw mbh))
+ -- TODO have a global function that adds the title to caption here:
+ pure $ B.figure (Caption Nothing mempty) -- added by addBlockTitle
+ (B.plain img')
+ -- TODO alt text?
+ A.BlockAudio (A.Target t) ->
+ pure $ B.plain $ B.image t "" (B.str t)
+ -- TODO alt text?
+ A.BlockVideo (A.Target t) ->
+ pure $ B.plain $ B.image t "" (B.str t)
+ A.TOC -> pure $ B.divWith ("toc",[],[]) mempty
+ A.Admonition admonitionType bs -> do
+ let admon = T.pack $ show admonitionType
+ bs' <- doBlocks bs
+ pure $ B.divWith ("",[T.toLower admon],[])
+ $ B.divWith ("",["title"],[]) (B.para (B.str admon)) <> bs'
+ A.PageBreak ->
+ pure $ B.divWith ("", ["page-break"], [("wrapper", "1")]) B.horizontalRule
+ A.ThematicBreak -> pure $ B.horizontalRule
+ A.Include fp (Just bs) ->
+ B.divWith ("",["included"],[("path",T.pack fp)]) <$> doBlocks bs
+ A.Include fp Nothing -> do
+ report $ CouldNotLoadIncludeFile (T.pack fp) (newPos "" 0 0)
+ pure mempty
+ A.PassthroughBlock t ->
+ case runPure (readHtml def{
+ readerExtensions = extensionsFromList [Ext_raw_html]
+ } t) of
+ Left _ -> pure $ B.rawBlock "html" t
+ Right (Pandoc _ bs) -> pure $ B.fromList bs
+
+doItem :: PandocMonad m => A.ListItem -> m B.Blocks
+doItem (A.ListItem Nothing bs) = doBlocks bs
+doItem (A.ListItem (Just checkstate) bs) = do
+ bs' <- doBlocks bs
+ let check = case checkstate of
+ A.Checked -> Str "\9746"
+ A.Unchecked -> Str "\9744"
+ pure $ B.fromList
+ $ case B.toList bs' of
+ (B.Para ils : rest) -> B.Para (check : B.Space : ils) : rest
+ (B.Plain ils : rest) -> B.Plain (check : B.Space : ils) : rest
+ rest -> B.Para [check] : rest
+
+doDefListItem :: PandocMonad m
+ => ([A.Inline], [A.Block]) -> m (B.Inlines , [B.Blocks])
+doDefListItem (lab, bs) = do
+ lab' <- doInlines lab
+ bs' <- doBlocks bs
+ pure (lab', [bs'])
+
+doInlines :: PandocMonad m => [A.Inline] -> m B.Inlines
+doInlines = fmap mconcat . mapM doInline
+
+doInline :: PandocMonad m => A.Inline -> m B.Inlines
+doInline (A.Inline (A.Attr _ps kvs') it) = do
+ let kvs = M.mapKeys (\k -> if k == "role" then "class" else k) kvs'
+ addPandocAttributes (M.toList kvs) <$>
+ case it of
+ A.Str t -> pure $ B.text t
+ A.HardBreak -> pure B.linebreak
+ A.Bold ils -> B.strong <$> doInlines ils
+ A.Italic ils -> B.emph <$> doInlines ils
+ A.Monospace ils -> walk monospaceStr <$> doInlines ils
+ A.Superscript ils -> B.superscript <$> doInlines ils
+ A.Subscript ils -> B.subscript <$> doInlines ils
+ A.Highlight ils -> B.spanWith ("",["mark"],[]) <$> doInlines ils
+ A.Strikethrough ils -> B.strikeout <$> doInlines ils
+ A.DoubleQuoted ils -> B.doubleQuoted <$> doInlines ils
+ A.SingleQuoted ils -> B.singleQuoted <$> doInlines ils
+ -- TODO when texmath's asciimath parser works, convert:
+ A.Math (Just A.AsciiMath) t -> pure $ B.math t
+ A.Math (Just A.LaTeXMath) t -> pure $ B.math t
+ A.Math Nothing _ ->
+ throwError $ PandocParseError "Encountered math type Nothing"
+ A.Icon t -> pure $ B.spanWith ("",["icon"],[("name",t)])
+ (B.str ("[" <> t <> "]"))
+ A.Button t -> pure $ B.spanWith ("",["button"],[])
+ (B.strong $ B.str ("[" <> t <> "]"))
+ A.Kbd ts -> pure $ mconcat $ intersperse (B.str "+") $
+ map (B.spanWith ("",["kbd"],[]) . B.strong . B.str) ts
+ A.Menu ts -> pure $ B.spanWith ("",["menu"],[]) $
+ B.strong $ B.text $ T.intercalate " › " ts
+ -- TODO do we need linktype?
+ A.Link _linkType (A.Target t) ils -> B.link t "" <$> doInlines ils
+ A.InlineImage (A.Target url) mbalt mbwidth mbheight -> do
+ let alt = case mbalt of
+ Just (A.AltText t) -> B.text t
+ Nothing -> mempty
+ width = case mbwidth of
+ Just (A.Width n) -> [("width", T.pack $ show n <> "px")]
+ Nothing -> []
+ height = case mbheight of
+ Just (A.Height n) -> [("height", T.pack $ show n <> "px")]
+ Nothing -> []
+ pure $ B.imageWith ("",[], width ++ height) url "" alt
+ A.Footnote _ ils -> B.note . B.para <$> doInlines ils
+ A.InlineAnchor t _ -> pure $ B.spanWith (t, [], []) mempty
+ A.BibliographyAnchor t _ -> pure $ B.spanWith (t, [], []) mempty
+ A.CrossReference t Nothing ->
+ pure $ B.linkWith ("",["cross-reference"],[]) ("#" <> t) "" (B.str t)
+ A.CrossReference t (Just ils) -> do
+ B.linkWith ("",["cross-reference"],[]) ("#" <> t) "" <$> doInlines ils
+ A.AttributeReference (A.AttributeName t) -> -- if this is here, it's unresolved
+ pure $ B.str ("{" <> t <> "}")
+ A.Span ils -> B.spanWith B.nullAttr <$> doInlines ils
+ -- Passthrough is hard to get right, because pandoc's RawInline needs
+ -- a format specifier. Often in asciidoc passthrough is used as a form
+ -- of escaping, so the best approach seems to be treating it as HTML
+ -- and parsing it:
+ A.Passthrough t -> do
+ case runPure (readHtml def{
+ readerExtensions = extensionsFromList [Ext_raw_html]
+ } t) of
+ Left _ -> pure $ B.rawInline "html" t
+ Right (Pandoc _ bs) -> pure $ B.fromList . blocksToInlines $ bs
+
+monospaceStr :: Inline -> Inline
+monospaceStr (Str t) = Code B.nullAttr t
+monospaceStr x = x
diff --git a/stack.yaml b/stack.yaml
index 6850fc51d..cb770a39d 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -13,8 +13,6 @@ extra-deps:
- hslua-module-system-1.2.3
- hslua-objectorientation-2.4.0
- hslua-packaging-2.3.2
-- skylighting-core-0.14.7
-- skylighting-0.14.7
- typst-symbols-0.1.9.1
- git: https://github.com/jgm/citeproc.git
commit: 0c062ce77056176d5901963c554053199b6592d5
@@ -24,9 +22,11 @@ extra-deps:
commit: 110322589698df20abf3f3a06c070271802ea598
- git: https://github.com/jgm/djoths.git
commit: 7dc8da53fc092d2d4d91f5f0988840f4faf90368
+- git: https://github.com/jgm/asciidoc-hs.git
+ commit: 6a632651458c9b5334d638993a5ed23c6214cb26
ghc-options:
"$locals": -fhide-source-paths -Wno-missing-home-modules
-resolver: lts-24.9
+resolver: lts-24.20
nix:
packages:
- pkg-config
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 385ee1e66..6e83ea673 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -78,6 +78,14 @@ tests pandocPath =
, s5WriterTest' "inserts" ["-s", "-H", "insert",
"-B", "insert", "-A", "insert", "-c", "main.css"] "html4"
]
+ , testGroup "asciidoc"
+ [ testGroup "writer" (writerTests' "asciidoc" ++
+ writerTests' "asciidoc_legacy")
+ , testGroup "reader"
+ [ test' "basic" ["-f", "asciidoc", "-t", "native", "-s"]
+ "asciidoc-reader.adoc" "asciidoc-reader.native"
+ ]
+ ]
, testGroup "textile"
[ testGroup "writer" $ writerTests' "textile"
, test' "reader" ["-r", "textile", "-w", "native", "-s"]
@@ -183,9 +191,7 @@ tests pandocPath =
"tikiwiki-reader.tikiwiki" "tikiwiki-reader.native" ]
, testGroup "other writers" $ map (\f -> testGroup f $ writerTests' f)
[ "opendocument" , "context" , "texinfo", "icml", "tei"
- , "man" , "plain" , "asciidoc", "asciidoc_legacy"
- , "xwiki", "zimwiki"
- ]
+ , "man" , "plain" , "xwiki", "zimwiki" ]
, testGroup "writers-lang-and-dir"
[ test' "latex" ["-f", "native", "-t", "latex", "-s"]
"writers-lang-and-dir.native" "writers-lang-and-dir.latex"
diff --git a/test/asciidoc-reader-include.adoc b/test/asciidoc-reader-include.adoc
new file mode 100644
index 000000000..2a4f54e75
--- /dev/null
+++ b/test/asciidoc-reader-include.adoc
@@ -0,0 +1,4 @@
+This is a test!
+
+. one
+.. two
diff --git a/test/asciidoc-reader-include.rb b/test/asciidoc-reader-include.rb
new file mode 100644
index 000000000..163144d48
--- /dev/null
+++ b/test/asciidoc-reader-include.rb
@@ -0,0 +1,4 @@
+# A function
+def foo
+ return 42
+end
diff --git a/test/asciidoc-reader.adoc b/test/asciidoc-reader.adoc
new file mode 100644
index 000000000..0f714e312
--- /dev/null
+++ b/test/asciidoc-reader.adoc
@@ -0,0 +1,908 @@
+// Some comment here.
+= AsciiDoc reader test
+John MacFarlane <[email protected]>; John Doe <[email protected]>
+v1.0, 2025-11-24
+:custom: Foo bar \
+baz
+:flag:
+:stem: latexmath
+
+[#firsty]
+== Inline markup
+
+=== Characters and escapes
+
+Dog's has a curved apostrophe, but dog\'s does not.
+
+An escaped symbol: \*star\*.
+
+Character references: &auml;&#160;&#x22E0;
+
+=== Line breaks
+
+This is a hard +
+break.
+
+Or set it for a whole paragraph
+
+[%hardbreaks]
+These are
+all
+hard
+breaks.
+
+=== Autolinks
+
+http://example.com/foobar?a=333&b=no%20body, [email protected]
+
+<http://example.com/foobar?a=333&b=no%20body>, <[email protected]>
+
+=== Cross-reference
+
+See <<firsty>>
+
+See <<firsty,My great section on Inline markup>>
+
+Go to <<anch,an inline anchor>>
+
+=== Anchors
+
+An [[anch]]inline anchor.
+
+[[[bibanchor]]Doe, John. A Book.
+
+=== Inline macros
+
+kbd:[F11]
+
+kbd:[Ctrl+Shift+F]
+
+menu:File[Save]
+
+menu:Reader[Markdown > Pandoc]
+
+btn:[Cancel]
+
+icon:heart[2x,role=red]
+
+anchor:tiger
+
+pass:[<b>*bold*</b>]
+
+link:downloads/report.pdf[Get Report]
+
+link:tools.html#editors[]
+
+link:file:///home/username[Your files]
+
+Tricky cases:
+
+link:pass:[My Documents/report.pdf][Get Report]
+
+link:My&#32;Documents/report.pdf[Get Report]
+
+link:My%20Documents/report.pdf[Get Report]
+
+link:++https://example.org/now_this__link_works.html++[]
+
+mailto:[email protected][Subscribe]
+
+mailto:[email protected]["Click, subscribe, and participate!",role=mail]
+
+xref:link-macro-attributes[use attributes within the link macro]
+
+image::sunset.jpg[Sunset]
+
+image::name.png[]
+
+image::sunset.jpg[Sunset,300,400]
+
+image::sunset.jpg[alt=Sunset,width=300,height=400]
+
+[latexmath]
+++++
+e=mc^2
+++++
+
+[asciimath]
+++++
+sin n / 3
+++++
+
+[stem]
+++++
+e^i
+++++
+
+=== Attribute substitutions
+
+{custom}
+
+{nonexistent}
+
+Built in: x{blank}y{empty}z{sp}a{nbsp}b{zwsp}c{apos}d{lsquo}
+
+=== Bold and italic
+
+Constrained: *this is bold _and italic_*.
+
+Unconstrained: wild**content__with italic__stuff**.
+
+=== Monospace
+
+`simple`
+
+`complex *with bold* text and a link:foo.html[]`
+
+unconstrained``wwow``okay
+
+=== Span and inline attributes
+
+[.red]#Bonjour *monsieur*#
+
+Un[.red]##constrained##content
+
+With #no attribute# it's highlighted.
+
+=== Sub and superscript
+
+H~2~O
+
+H~a{sp}b~O
+
+Not subscript: H~a b~O.
+
+H^2&O
+
+H^a{sp}b^O
+
+Not subscript: H^a b^O.
+
+=== Passthrough
+
+Here the special characters just come through as literal:
+
++<b>*test*</b>+
+
+xx++<b>*test*</b>++xx
+
+But here they are passed through:
+
+xx+++<b>*test*</b>+++xx
+
+=== Quoted
+
+"`double quoted`"
+
+'`single quoted`'
+
+=== Footnotes
+
+Doublefootnote:[The double hail-and-rainbow level makes my toes tingle.]
+
+A bold statement!footnote:disclaimer[Opinions are my own.]
+Another outrageous statement.footnote:disclaimer[]
+
+== Block markup
+
+=== Sections
+
+==== Another level
+
+===== Level 5
+
+#### Markdown style
+
+##### Level 5
+
+=== Discrete heading
+
+[discrete]
+==== A discrete heading, not a section
+
+=== Paragraph
+
+This is a paragraph
+whose source fits on two lines.
+
+{.This is my title}
+A paragraph with a title.
+
+=== Example block
+
+.Optional title
+[example]
+This is an example of an example block.
+
+.Optional title
+====
+Paragraph *one*.
+
+Paragraph *two*.
+====
+
+=== Admonition
+
+Simple form:
+
+WARNING: This is very dangerous.
+Don't do it unless you understand the risks.
+
+[IMPORTANT]
+.Title of the admonition
+====
+Remember:
+
+. Don't do this.
+. And don't do that.
+====
+
+=== Sidebar
+
+[sidebar]
+A simple sidebar.
+
+.Optional Title *with strong emphasis*
+****
+Here is a sidebar.
+
+TIP: It can contain any type of content.
+****
+
+=== Literal block
+
+Short indented code:
+
+ $ ls -a
+ $ cat /foo/bar/baz \
+ /bi/bim/bop
+
+[literal]
+This is
+ a literal block too.
+
+....
+ Fenced
+ $+ *a* literal
+
+****
+not a sidebar
+****
+....
+
+=== Listing
+
+[source,ruby]
+----
+require 'sinatra'
+
+get '/hi' do
+ "Hello World!"
+end
+----
+
+Implied:
+
+[source,ruby]
+----
+require 'sinatra'
+
+get '/hi' do
+ "Hello World!"
+end
+----
+
+[,ruby]
+----
+include::asciidoc-reader-include.rb[]
+----
+
+[#hello.haskell]
+----
+putStrLn $ unwords ["Hello", "world"]
+----
+
+Line numbering:
+
+[%linenums,ruby]
+----
+puts 1
+puts 2
+puts 3
+----
+
+----
+This doesn't have a language.
+ +="hi"
+----
+
+And with a callout list:
+
+[source,ruby]
+----
+require 'sinatra' <1>
+
+get '/hi' do <2> <3>
+ "Hello World!"
+end
+----
+<1> Library import
+<2> URL mapping
+<3> Response block
+
+Markdown-style fenced:
+
+```ruby
+def foo
+ return 5
+end
+```
+
+=== Verse
+
+[verse,Carl Sandburg, two lines from the poem Fog]
+The fog comes
+on little cat feet.
+
+[verse,Carl Sandburg,Fog]
+____
+The fog comes
+on little cat feet.
+It sits looking
+over harbor and city
+on silent haunches
+and then moves on.
+____
+
+=== Collapsible
+
+Click here for more.
+[%collapsible%open]
+====
+This is collapsible.
+
+It can be hidden.
+====
+
+.Click me!
+[%collapsible]
+This paragraph is
+also collapsible.
+
+=== Quote
+
+[quote,Captain James T. Kirk,Star Trek IV: The Voyage Home]
+Everybody remember where we parked.
+
+[quote,Monty Python and the Holy Grail]
+____
+Dennis: Come and see the violence inherent in the system. Help! Help! I'm being
+repressed.
+
+King Arthur: Bloody peasant!
+
+Dennis: Oh, what a giveaway! Did you hear that? Did you hear that, eh? That's what I'm
+on about! Did you see him repressing me? You saw him, Didn't you?
+____
+
+[quote.movie#roads,Dr. Emmett Brown]
+____
+Roads? Where we're going, we don't need roads.
+____
+
+=== Pass
+
+++++
+<p>pass <em>through</em>
+ </p>
+++++
+
+=== Open block
+
+.A title.
+[key="a value"]
+--
+Any content can go here:
+
+. one
+. two
+--
+
+=== Anchor
+
+[[goals]]
+* one
+* two
+
+=== Breaks
+
+Asciidoc thematic break:
+
+'''
+
+Markdown style:
+
+---
+- - -
+***
+* * *
+
+Page breaks:
+
+<<<
+
+[%always]
+<<<
+
+=== List
+
+* Edgar Allan Poe
+* Sheri S. Tepper
+* Bill Bryson
+
+// titled
+
+.Kizmet's Favorite Authors
+* Edgar Allan Poe
+* Sheri S. Tepper
+* Bill Bryson
+
+// hyphen
+
+- Edgar Allan Poe
+- Sheri S. Tepper
+- Bill Bryson
+
+. Nested list
+* West wood maze
+** Maze heart
+*** Reflection pool
+** Secret exit
+* Level 1 list item
+** Level 2 list item
+*** Level 3 list item
+**** Level 4 list item
+***** Level 5 list item
+****** etc.
+* Level 1 list item
+
+// attributes
+
+[square]
+* one
+* two
+* three
+
+// ordered with actual numbers
+
+1. Protons
+2. Electrons
+3. Neutrons
+
+// ordered with .
+
+. Protons
+. Electrons
+. Neutrons
+
+Start with 4:
+
+4. Step four
+5. Step five
+6. Step six
+
+or
+
+[start=4]
+. Step four
+. Step five
+. Step six
+
+Reversed:
+
+[%reversed]
+.Parts of an atom
+. Protons
+. Electrons
+. Neutrons
+
+Nested
+
+. Step 1
+. Step 2
+.. Step 2a
+.. Step 2b
+. Step 3
+
+Mixed nested
+
+. Linux
+* Fedora
+* Ubuntu
+* Slackware
+. BSD
+* FreeBSD
+* NetBSD
+
+With spacing
+
+. Linux
+* Fedora
+* Ubuntu
+* Slackware
+. BSD
+* FreeBSD
+* NetBSD
+
+With number styles
+
+[lowerroman,start=5]
+. Five
+. Six
+[loweralpha]
+.. a
+.. b
+.. c
+. Seven
+
+Checklist
+
+* [*] checked
+* [x] also checked
+* [ ] not checked
+* normal list item
+
+Separate lists with block attribute
+
+* Apples
+* Oranges
+[]
+. Wash
+. Slice
+
+Multiline items
+
+* Blah blah.
+Blah blah.
+* The document header in AsciiDoc is optional.
+If present, it must start with a document title.
+
+* Optional author and revision information lines
+immediately follow the document title.
+
+* The document header must be separated from
+ the remainder of the document by one or more
+ empty lines and it cannot contain empty lines.
+
+Complex item
+
+* The header in AsciiDoc must start with a document title.
++
+----
+= Document Title
+----
++
+Keep in mind that the header is optional.
+* Optional author and revision information lines immediately follow the document
+title.
++
+----
+= Document Title
+Doc Writer <[email protected]>
+v1.0, 2022-01-01
+----
+* Second item
+
+Empty principle element:
+
+. {empty}
++
+----
+test
+----
+
+=== Table
+
+==== Simple with column specs
+
+[cols="3,2,3"]
+|===
+|This content is placed in the first cell of column 1
+|This line starts with a vertical bar so this content is placed in a new cell in
+column 2 |When the processor encounters a whitespace followed by a vertical bar it
+ends the previous cell and starts a new cell
+|===
+
+==== Repeated column in specs
+
+[cols="2*"]
+|===
+>s|This cell's specifier indicates that this cell's content is right-aligned and bold.
+|The cell specifier on this cell hasn't been set explicitly, so the default
+properties are applied.
+|===
+
+==== Simple without column specs
+
+|===
+|Column 1, header row |Column 2, header row
+
+|Cell in column 1, row 2
+|Cell in column 2, row 2
+
+|Cell in column 1, row 3
+|Cell in column 2, row 3
+|===
+
+==== With caption
+
+.My cool table.
+|===
+|Column 1, header row |Column 2, header row
+
+|Cell in column 1, row 2
+|Cell in column 2, row 2
+
+|Cell in column 1, row 3
+|Cell in column 2, row 3
+|===
+
+==== No header
+
+By default the first line should turn into the header, but this
+can be disabled:
+
+[%noheader]
+|===
+|Cell in column 1, row 1 |Cell in column 2, row 1
+|Cell in column 1, row 2 |Cell in column 2, row 2
+|===
+
+And also explicitly enabled:
+
+[%header%footer%autowidth,cols=2*~]
+|===
+|Cell A1 |Cell B1
+|Cell A2 |Cell B2
+|Cell A3 |Cell B3
+|===
+
+==== Footer
+
+[%header%footer,cols="2,2,1"]
+|===
+|Column 1, header row
+|Column 2, header row
+|Column 3, header row
+|Cell in column 1, row 2
+|Cell in column 2, row 2
+|Cell in column 3, row 2
+|Column 1, footer row
+|Column 2, footer row
+|Column 3, footer row
+|===
+
+or
+
+[options="footer"]
+|===
+|Column 1, header row |Column 2, header row
+|Cell in column 1, row 2
+|Cell in column 2, row 2
+|Cell in column 1, row 3
+|Cell in column 2, row 3
+|Column 1, footer row
+|Column 2, footer row
+|===
+
+==== Alignment
+
+|===
+|Column Name |Column Name
+2+^|This cell spans two columns, and its content is horizontally centered because the
+cell specifier includes the `+^+` operator.
+2*^|This content is duplicated in two adjacent columns.
+Its content is horizontally centered because the cell specifier
+includes the `+^+` operator.
+|===
+
+==== Multiple paragraphs in cells
+
+|===
+
+|Single paragraph on row 1
+
+|First paragraph on row 2
+
+Second paragraph on row 2
+|===
+
+==== Complex table
+
+|===
+
+2*>m|This content is duplicated across two columns.
+
+It is aligned right horizontally.
+
+And it is monospaced.
+
+.3+^.>s|This cell spans 3 rows. The content is centered horizontally, aligned to the bottom of the cell, and strong.
+e|This content is emphasized.
+
+.^l|This content is aligned to the top of the cell and literal.
+
+a|
+[source]
+puts "This is a source block!"
+
+|===
+
+==== Column styles
+
+[cols="m,m"]
+|===
+|monospace | mono
+d|default | mono
+|===
+
+==== Block elements in cells
+
+|===
+|Normal Style |AsciiDoc Style
+|This cell isn't prefixed with an `a`, so the processor doesn't interpret the
+following lines as an AsciiDoc list.
+
+* List item 1
+* List item 2
+* List item 3
+
+a|This cell is prefixed with an `a`, so the processor interprets the following lines
+as an AsciiDoc list.
+
+* List item 1
+* List item 2
+* List item 3
+
+|This cell isn't prefixed with an `a`, so the processor doesn't interpret the listing
+block delimiters or the `source` style.
+
+[source,python]
+----
+import os
+print ("%s" %(os.uname()))
+----
+
+a|This cell is prefixed with an `a`, so the listing block is processed and rendered
+according to the `source` style rules.
+
+[source,python]
+----
+import os
+print "%s" %(os.uname())
+----
+|===
+
+==== Col and rowspan
+
+|===
+|Column 1, header row |Column 2, header row | Column 3, header row
+2.2+|This cell spans 2 cols and 2 rows
+|Cell in column 3, row 2
+|Cell in column 3, row 3
+3+|Cell in column 1-3, row 4
+|===
+
+==== CSV table
+
+[%header,format=csv]
+|===
+Artist,Track,Genre
+Baauer,Harlem Shake,Hip Hop
+The Lumineers,Ho Hey,Folk Rock
+|===
+
+or
+
+,===
+Artist,Track,Genre
+Baauer,Harlem Shake,Hip Hop
+,===
+
+==== DSV table
+
+[format=dsv,separator=;]
+|===
+a;b;c
+d;e;f
+|===
+
+or
+
+:===
+Artist:Track:Genre
+Robyn:Indestructible:Dance
+:===
+
+=== Definition list
+
+CPU:: The brain of the computer.
+Hard drive:: Permanent storage for operating system and/or user files.
+
+Mixed
+
+Dairy::
+* Milk
+* Eggs
+Bakery::
+* Bread
+Produce::
+* Bananas
+
+With spaces
+
+Dairy::
+
+ * Milk
+ * Eggs
+
+Bakery::
+
+ * Bread
+
+Produce::
+
+ * Bananas
+
+Nested
+
+Operating Systems::
+Linux:::
+ . Fedora
+ * Desktop
+ . Ubuntu
+ * Desktop
+ * Server
+BSD:::
+ . FreeBSD
+ . NetBSD
+Cloud Providers::
+ PaaS:::
+ . OpenShift
+ . CloudBees
+ IaaS:::
+ . Amazon EC2
+
+This just affects the output:
+
+[horizontal,labelwidth=25,itemwidth=75]
+CPU:: The brain of the computer.
+RAM:: Temporarily stores information the CPU uses during operation.
+
+Q&A list
+
+[qanda]
+What is the answer?::
+This is the answer.
+Are cameras allowed?::
+Are backpacks allowed?::
+No.
+
+Ordered description list (with numbers)
+
+[ordered]
+&:: ampersand
+>:: greater than
+
+=== Block macros
+
+image::sunset.jpg[Sunset,300,200]
+
+video::mymovie.mp4[]
+
+audio::mysong.mp3[]
+
+toc::[]
+
+include::asciidoc-reader-include.adoc[]
+
diff --git a/test/asciidoc-reader.native b/test/asciidoc-reader.native
new file mode 100644
index 000000000..a723ac7fd
--- /dev/null
+++ b/test/asciidoc-reader.native
@@ -0,0 +1,4406 @@
+Pandoc
+ Meta
+ { unMeta =
+ fromList
+ [ ( "author"
+ , MetaList
+ [ MetaInlines
+ [ Str "John"
+ , Space
+ , Str "MacFarlane"
+ , Space
+ , Str "("
+ , Link
+ ( "" , [] , [] )
+ [ Str "[email protected]" ]
+ ( "mailto:[email protected]" , "" )
+ , Str ")"
+ ]
+ , MetaInlines
+ [ Str "John"
+ , Space
+ , Str "Doe"
+ , Space
+ , Str "("
+ , Link
+ ( "" , [] , [] )
+ [ Str "[email protected]" ]
+ ( "mailto:[email protected]" , "" )
+ , Str ")"
+ ]
+ ]
+ )
+ , ( "custom" , MetaString "Foo bar baz" )
+ , ( "date" , MetaString "2025-11-24" )
+ , ( "flag" , MetaBool True )
+ , ( "title"
+ , MetaInlines
+ [ Str "AsciiDoc"
+ , Space
+ , Str "reader"
+ , Space
+ , Str "test"
+ ]
+ )
+ , ( "version" , MetaString "1.0" )
+ ]
+ }
+ [ Header
+ 1
+ ( "firsty" , [] , [] )
+ [ Str "Inline" , Space , Str "markup" ]
+ , Header
+ 2
+ ( "_characters_and_escapes" , [] , [] )
+ [ Str "Characters"
+ , Space
+ , Str "and"
+ , Space
+ , Str "escapes"
+ ]
+ , Para
+ [ Str "Dog\8217s"
+ , Space
+ , Str "has"
+ , Space
+ , Str "a"
+ , Space
+ , Str "curved"
+ , Space
+ , Str "apostrophe,"
+ , Space
+ , Str "but"
+ , Space
+ , Str "dog's"
+ , Space
+ , Str "does"
+ , Space
+ , Str "not."
+ ]
+ , Para
+ [ Str "An"
+ , Space
+ , Str "escaped"
+ , Space
+ , Str "symbol:"
+ , Space
+ , Str "*star*."
+ ]
+ , Para
+ [ Str "Character"
+ , Space
+ , Str "references:"
+ , Space
+ , Str "\228\160\8928"
+ ]
+ , Header
+ 2
+ ( "_line_breaks" , [] , [] )
+ [ Str "Line" , Space , Str "breaks" ]
+ , Para
+ [ Str "This"
+ , Space
+ , Str "is"
+ , Space
+ , Str "a"
+ , Space
+ , Str "hard"
+ , LineBreak
+ , Str "break."
+ ]
+ , Para
+ [ Str "Or"
+ , Space
+ , Str "set"
+ , Space
+ , Str "it"
+ , Space
+ , Str "for"
+ , Space
+ , Str "a"
+ , Space
+ , Str "whole"
+ , Space
+ , Str "paragraph"
+ ]
+ , Div
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" ) , ( "options" , "hardbreaks" ) ]
+ )
+ [ Para
+ [ Str "These"
+ , Space
+ , Str "are"
+ , LineBreak
+ , Str "all"
+ , LineBreak
+ , Str "hard"
+ , LineBreak
+ , Str "breaks."
+ ]
+ ]
+ , Header 2 ( "_autolinks" , [] , [] ) [ Str "Autolinks" ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "http://example.com/foobar?a=333&b=no%20body" ]
+ ( "http://example.com/foobar?a=333&b=no%20body" , "" )
+ , Str ","
+ , Space
+ , Link
+ ( "" , [] , [] )
+ [ Str "[email protected]" ]
+ ( "[email protected]" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "http://example.com/foobar?a=333&b=no%20body" ]
+ ( "http://example.com/foobar?a=333&b=no%20body" , "" )
+ , Str ","
+ , Space
+ , Str "<"
+ , Link
+ ( "" , [] , [] )
+ [ Str "[email protected]" ]
+ ( "[email protected]" , "" )
+ , Str ">"
+ ]
+ , Header
+ 2 ( "_cross_reference" , [] , [] ) [ Str "Cross-reference" ]
+ , Para
+ [ Str "See"
+ , Space
+ , Link
+ ( "" , [ "cross-reference" ] , [] )
+ [ Str "Inline" , Space , Str "markup" ]
+ ( "#firsty" , "" )
+ ]
+ , Para
+ [ Str "See"
+ , Space
+ , Link
+ ( "" , [ "cross-reference" ] , [] )
+ [ Str "My"
+ , Space
+ , Str "great"
+ , Space
+ , Str "section"
+ , Space
+ , Str "on"
+ , Space
+ , Str "Inline"
+ , Space
+ , Str "markup"
+ ]
+ ( "#firsty" , "" )
+ ]
+ , Para
+ [ Str "Go"
+ , Space
+ , Str "to"
+ , Space
+ , Link
+ ( "" , [ "cross-reference" ] , [] )
+ [ Str "an" , Space , Str "inline" , Space , Str "anchor" ]
+ ( "#anch" , "" )
+ ]
+ , Header 2 ( "_anchors" , [] , [] ) [ Str "Anchors" ]
+ , Para
+ [ Str "An"
+ , Space
+ , Span ( "anch" , [] , [] ) []
+ , Str "inline"
+ , Space
+ , Str "anchor."
+ ]
+ , Para
+ [ Span ( "[bibanchor" , [] , [] ) []
+ , Str "Doe,"
+ , Space
+ , Str "John."
+ , Space
+ , Str "A"
+ , Space
+ , Str "Book."
+ ]
+ , Header
+ 2
+ ( "_inline_macros" , [] , [] )
+ [ Str "Inline" , Space , Str "macros" ]
+ , Para
+ [ Span ( "" , [ "kbd" ] , [] ) [ Strong [ Str "F11" ] ] ]
+ , Para
+ [ Span ( "" , [ "kbd" ] , [] ) [ Strong [ Str "Ctrl" ] ]
+ , Str "+"
+ , Span ( "" , [ "kbd" ] , [] ) [ Strong [ Str "Shift" ] ]
+ , Str "+"
+ , Span ( "" , [ "kbd" ] , [] ) [ Strong [ Str "F" ] ]
+ ]
+ , Para
+ [ Span
+ ( "" , [ "menu" ] , [] )
+ [ Strong [ Str "File\160\8250\160Save" ] ]
+ ]
+ , Para
+ [ Span
+ ( "" , [ "menu" ] , [] )
+ [ Strong
+ [ Str "Reader\160\8250\160Markdown\160\8250\160Pandoc" ]
+ ]
+ ]
+ , Para
+ [ Span
+ ( "" , [ "button" ] , [] ) [ Strong [ Str "[Cancel]" ] ]
+ ]
+ , Para
+ [ Image
+ ( "" , [ "red icon" ] , [] )
+ []
+ ( "./images/icons/heart.png" , "" )
+ ]
+ , Para [ Str "anchor:tiger" ]
+ , Para [ Strong [ Str "*bold*" ] ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "Get" , Space , Str "Report" ]
+ ( "downloads/report.pdf" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "tools.html#editors" ]
+ ( "tools.html#editors" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "Your" , Space , Str "files" ]
+ ( "file:///home/username" , "" )
+ ]
+ , Para [ Str "Tricky" , Space , Str "cases:" ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "Get" , Space , Str "Report" ]
+ ( "My Documents/report.pdf" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "Get" , Space , Str "Report" ]
+ ( "My&#32;Documents/report.pdf" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "Get" , Space , Str "Report" ]
+ ( "My%20Documents/report.pdf" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "https://example.org/now_this__link_works.html" ]
+ ( "https://example.org/now_this__link_works.html" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "Subscribe" ]
+ ( "[email protected]" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [ "mail" ] , [] )
+ [ Str "Click,"
+ , Space
+ , Str "subscribe,"
+ , Space
+ , Str "and"
+ , Space
+ , Str "participate!"
+ ]
+ ( "[email protected]" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [ "cross-reference" ] , [] )
+ [ Str "use"
+ , Space
+ , Str "attributes"
+ , Space
+ , Str "within"
+ , Space
+ , Str "the"
+ , Space
+ , Str "link"
+ , Space
+ , Str "macro"
+ ]
+ ( "#link-macro-attributes" , "" )
+ ]
+ , Figure
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ Plain
+ [ Image
+ ( "" , [] , [] ) [ Str "Sunset" ] ( "sunset.jpg" , "" )
+ ]
+ ]
+ , Figure
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ Plain [ Image ( "" , [] , [] ) [] ( "name.png" , "" ) ] ]
+ , Figure
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ Plain
+ [ Image
+ ( ""
+ , []
+ , [ ( "width" , "300px" ) , ( "height" , "400px" ) ]
+ )
+ [ Str "Sunset" ]
+ ( "sunset.jpg" , "" )
+ ]
+ ]
+ , Div
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" )
+ , ( "alt" , "Sunset" )
+ , ( "height" , "400" )
+ , ( "width" , "300" )
+ ]
+ )
+ [ Figure
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ Plain [ Image ( "" , [] , [] ) [] ( "sunset.jpg" , "" ) ]
+ ]
+ ]
+ , Para [ Math DisplayMath "e=mc^2\n" ]
+ , Para [ Math DisplayMath "sin n / 3\n" ]
+ , Para [ Math DisplayMath "e^i\n" ]
+ , Header
+ 2
+ ( "_attribute_substitutions" , [] , [] )
+ [ Str "Attribute" , Space , Str "substitutions" ]
+ , Para [ Str "Foo" , Space , Str "bar" , Space , Str "baz" ]
+ , Para [ Str "{nonexistent}" ]
+ , Para
+ [ Str "Built"
+ , Space
+ , Str "in:"
+ , Space
+ , Str "xyz"
+ , Space
+ , Str "a\160b\8203c'd\8216"
+ ]
+ , Header
+ 2
+ ( "_bold_and_italic" , [] , [] )
+ [ Str "Bold" , Space , Str "and" , Space , Str "italic" ]
+ , Para
+ [ Str "Constrained:"
+ , Space
+ , Strong
+ [ Str "this"
+ , Space
+ , Str "is"
+ , Space
+ , Str "bold"
+ , Space
+ , Emph [ Str "and" , Space , Str "italic" ]
+ ]
+ , Str "."
+ ]
+ , Para
+ [ Str "Unconstrained:"
+ , Space
+ , Str "wild"
+ , Strong
+ [ Str "content"
+ , Emph [ Str "with" , Space , Str "italic" ]
+ , Str "stuff"
+ ]
+ , Str "."
+ ]
+ , Header 2 ( "_monospace" , [] , [] ) [ Str "Monospace" ]
+ , Para [ Code ( "" , [] , [] ) "simple" ]
+ , Para
+ [ Code ( "" , [] , [] ) "complex"
+ , Space
+ , Strong
+ [ Code ( "" , [] , [] ) "with"
+ , Space
+ , Code ( "" , [] , [] ) "bold"
+ ]
+ , Space
+ , Code ( "" , [] , [] ) "text"
+ , Space
+ , Code ( "" , [] , [] ) "and"
+ , Space
+ , Code ( "" , [] , [] ) "a"
+ , Space
+ , Link
+ ( "" , [] , [] )
+ [ Code ( "" , [] , [] ) "foo.html" ]
+ ( "foo.html" , "" )
+ ]
+ , Para
+ [ Str "unconstrained"
+ , Code ( "" , [] , [] ) "wwow"
+ , Str "okay"
+ ]
+ , Header
+ 2
+ ( "_span_and_inline_attributes" , [] , [] )
+ [ Str "Span"
+ , Space
+ , Str "and"
+ , Space
+ , Str "inline"
+ , Space
+ , Str "attributes"
+ ]
+ , Para
+ [ Span
+ ( "" , [ "red" ] , [] )
+ [ Str "Bonjour" , Space , Strong [ Str "monsieur" ] ]
+ ]
+ , Para
+ [ Str "Un"
+ , Span ( "" , [ "red" ] , [] ) [ Str "constrained" ]
+ , Str "content"
+ ]
+ , Para
+ [ Str "With"
+ , Space
+ , Span
+ ( "" , [ "mark" ] , [] )
+ [ Str "no" , Space , Str "attribute" ]
+ , Space
+ , Str "it\8217s"
+ , Space
+ , Str "highlighted."
+ ]
+ , Header
+ 2
+ ( "_sub_and_superscript" , [] , [] )
+ [ Str "Sub"
+ , Space
+ , Str "and"
+ , Space
+ , Str "superscript"
+ ]
+ , Para [ Str "H" , Subscript [ Str "2" ] , Str "O" ]
+ , Para
+ [ Str "H"
+ , Subscript [ Str "a" , Space , Str "b" ]
+ , Str "O"
+ ]
+ , Para
+ [ Str "Not"
+ , Space
+ , Str "subscript:"
+ , Space
+ , Str "H~a"
+ , Space
+ , Str "b~O."
+ ]
+ , Para [ Str "H^2&O" ]
+ , Para
+ [ Str "H"
+ , Superscript [ Str "a" , Space , Str "b" ]
+ , Str "O"
+ ]
+ , Para
+ [ Str "Not"
+ , Space
+ , Str "subscript:"
+ , Space
+ , Str "H^a"
+ , Space
+ , Str "b^O."
+ ]
+ , Header
+ 2 ( "_passthrough" , [] , [] ) [ Str "Passthrough" ]
+ , Para
+ [ Str "Here"
+ , Space
+ , Str "the"
+ , Space
+ , Str "special"
+ , Space
+ , Str "characters"
+ , Space
+ , Str "just"
+ , Space
+ , Str "come"
+ , Space
+ , Str "through"
+ , Space
+ , Str "as"
+ , Space
+ , Str "literal:"
+ ]
+ , Para [ Str "<b>*test*</b>" ]
+ , Para [ Str "xx<b>*test*</b>xx" ]
+ , Para
+ [ Str "But"
+ , Space
+ , Str "here"
+ , Space
+ , Str "they"
+ , Space
+ , Str "are"
+ , Space
+ , Str "passed"
+ , Space
+ , Str "through:"
+ ]
+ , Para [ Str "xx" , Strong [ Str "*test*" ] , Str "xx" ]
+ , Header 2 ( "_quoted" , [] , [] ) [ Str "Quoted" ]
+ , Para
+ [ Quoted DoubleQuote [ Str "double" , Space , Str "quoted" ]
+ ]
+ , Para
+ [ Quoted SingleQuote [ Str "single" , Space , Str "quoted" ]
+ ]
+ , Header 2 ( "_footnotes" , [] , [] ) [ Str "Footnotes" ]
+ , Para
+ [ Str "Double"
+ , Note
+ [ Para
+ [ Str "The"
+ , Space
+ , Str "double"
+ , Space
+ , Str "hail-and-rainbow"
+ , Space
+ , Str "level"
+ , Space
+ , Str "makes"
+ , Space
+ , Str "my"
+ , Space
+ , Str "toes"
+ , Space
+ , Str "tingle."
+ ]
+ ]
+ ]
+ , Para
+ [ Str "A"
+ , Space
+ , Str "bold"
+ , Space
+ , Str "statement!"
+ , Note
+ [ Para
+ [ Str "Opinions"
+ , Space
+ , Str "are"
+ , Space
+ , Str "my"
+ , Space
+ , Str "own."
+ ]
+ ]
+ , SoftBreak
+ , Str "Another"
+ , Space
+ , Str "outrageous"
+ , Space
+ , Str "statement."
+ , Note
+ [ Para
+ [ Str "Opinions"
+ , Space
+ , Str "are"
+ , Space
+ , Str "my"
+ , Space
+ , Str "own."
+ ]
+ ]
+ ]
+ , Header
+ 1
+ ( "_block_markup" , [] , [] )
+ [ Str "Block" , Space , Str "markup" ]
+ , Header 2 ( "_sections" , [] , [] ) [ Str "Sections" ]
+ , Header
+ 3
+ ( "_another_level" , [] , [] )
+ [ Str "Another" , Space , Str "level" ]
+ , Header
+ 4 ( "_level_5" , [] , [] ) [ Str "Level" , Space , Str "5" ]
+ , Header
+ 3
+ ( "_markdown_style" , [] , [] )
+ [ Str "Markdown" , Space , Str "style" ]
+ , Header
+ 4
+ ( "_level_5_2" , [] , [] )
+ [ Str "Level" , Space , Str "5" ]
+ , Header
+ 2
+ ( "_discrete_heading" , [] , [] )
+ [ Str "Discrete" , Space , Str "heading" ]
+ , Header
+ 3
+ ( "" , [] , [] )
+ [ Str "A"
+ , Space
+ , Str "discrete"
+ , Space
+ , Str "heading,"
+ , Space
+ , Str "not"
+ , Space
+ , Str "a"
+ , Space
+ , Str "section"
+ ]
+ , Header 2 ( "_paragraph" , [] , [] ) [ Str "Paragraph" ]
+ , Para
+ [ Str "This"
+ , Space
+ , Str "is"
+ , Space
+ , Str "a"
+ , Space
+ , Str "paragraph"
+ , SoftBreak
+ , Str "whose"
+ , Space
+ , Str "source"
+ , Space
+ , Str "fits"
+ , Space
+ , Str "on"
+ , Space
+ , Str "two"
+ , Space
+ , Str "lines."
+ ]
+ , Para
+ [ Str "{.This"
+ , Space
+ , Str "is"
+ , Space
+ , Str "my"
+ , Space
+ , Str "title}"
+ , SoftBreak
+ , Str "A"
+ , Space
+ , Str "paragraph"
+ , Space
+ , Str "with"
+ , Space
+ , Str "a"
+ , Space
+ , Str "title."
+ ]
+ , Header
+ 2
+ ( "_example_block" , [] , [] )
+ [ Str "Example" , Space , Str "block" ]
+ , Div
+ ( "" , [] , [] )
+ [ Div
+ ( "" , [ "title" ] , [] )
+ [ Para [ Str "Optional" , Space , Str "title" ] ]
+ , Para
+ [ Str "This"
+ , Space
+ , Str "is"
+ , Space
+ , Str "an"
+ , Space
+ , Str "example"
+ , Space
+ , Str "of"
+ , Space
+ , Str "an"
+ , Space
+ , Str "example"
+ , Space
+ , Str "block."
+ ]
+ ]
+ , Div
+ ( "" , [ "example" ] , [] )
+ [ Div
+ ( "" , [ "title" ] , [] )
+ [ Para [ Str "Optional" , Space , Str "title" ] ]
+ , Para
+ [ Str "Paragraph" , Space , Strong [ Str "one" ] , Str "." ]
+ , Para
+ [ Str "Paragraph" , Space , Strong [ Str "two" ] , Str "." ]
+ ]
+ , Header 2 ( "_admonition" , [] , [] ) [ Str "Admonition" ]
+ , Para [ Str "Simple" , Space , Str "form:" ]
+ , Div
+ ( "" , [ "warning" ] , [] )
+ [ Div ( "" , [ "title" ] , [] ) [ Para [ Str "Warning" ] ]
+ , Para
+ [ Str "This"
+ , Space
+ , Str "is"
+ , Space
+ , Str "very"
+ , Space
+ , Str "dangerous."
+ , SoftBreak
+ , Str "Don\8217t"
+ , Space
+ , Str "do"
+ , Space
+ , Str "it"
+ , Space
+ , Str "unless"
+ , Space
+ , Str "you"
+ , Space
+ , Str "understand"
+ , Space
+ , Str "the"
+ , Space
+ , Str "risks."
+ ]
+ ]
+ , Div
+ ( "" , [ "important" ] , [] )
+ [ Div
+ ( "" , [ "title" ] , [] )
+ [ Para
+ [ Str "Title"
+ , Space
+ , Str "of"
+ , Space
+ , Str "the"
+ , Space
+ , Str "admonition"
+ ]
+ ]
+ , Para [ Str "Remember:" ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para
+ [ Str "Don\8217t"
+ , Space
+ , Str "do"
+ , Space
+ , Str "this."
+ ]
+ ]
+ , [ Para
+ [ Str "And"
+ , Space
+ , Str "don\8217t"
+ , Space
+ , Str "do"
+ , Space
+ , Str "that."
+ ]
+ ]
+ ]
+ ]
+ , Header 2 ( "_sidebar" , [] , [] ) [ Str "Sidebar" ]
+ , Para
+ [ Str "A" , Space , Str "simple" , Space , Str "sidebar." ]
+ , Div
+ ( "" , [ "sidebar" ] , [] )
+ [ Div
+ ( "" , [ "title" ] , [] )
+ [ Para
+ [ Str "Optional"
+ , Space
+ , Str "Title"
+ , Space
+ , Strong
+ [ Str "with"
+ , Space
+ , Str "strong"
+ , Space
+ , Str "emphasis"
+ ]
+ ]
+ ]
+ , Para
+ [ Str "Here"
+ , Space
+ , Str "is"
+ , Space
+ , Str "a"
+ , Space
+ , Str "sidebar."
+ ]
+ , Div
+ ( "" , [ "tip" ] , [] )
+ [ Div ( "" , [ "title" ] , [] ) [ Para [ Str "Tip" ] ]
+ , Para
+ [ Str "It"
+ , Space
+ , Str "can"
+ , Space
+ , Str "contain"
+ , Space
+ , Str "any"
+ , Space
+ , Str "type"
+ , Space
+ , Str "of"
+ , Space
+ , Str "content."
+ ]
+ ]
+ ]
+ , Header
+ 2
+ ( "_literal_block" , [] , [] )
+ [ Str "Literal" , Space , Str "block" ]
+ , Para
+ [ Str "Short"
+ , Space
+ , Str "indented"
+ , Space
+ , Str "code:"
+ ]
+ , CodeBlock
+ ( "" , [] , [] )
+ "$ ls -a\n$ cat /foo/bar/baz \\\n /bi/bim/bop\n"
+ , CodeBlock
+ ( "" , [] , [] ) "This is\n a literal block too.\n"
+ , CodeBlock
+ ( "" , [] , [] )
+ " Fenced\n $+ *a* literal\n\n****\nnot a sidebar\n****\n"
+ , Header 2 ( "_listing" , [] , [] ) [ Str "Listing" ]
+ , CodeBlock
+ ( "" , [ "ruby" ] , [] )
+ "require 'sinatra'\n\nget '/hi' do\n \"Hello World!\"\nend"
+ , Para [ Str "Implied:" ]
+ , CodeBlock
+ ( "" , [ "ruby" ] , [] )
+ "require 'sinatra'\n\nget '/hi' do\n \"Hello World!\"\nend"
+ , CodeBlock
+ ( "" , [ "ruby" ] , [] )
+ "# A function\ndef foo\n return 42\nend"
+ , CodeBlock
+ ( "hello" , [ "haskell" ] , [] )
+ "putStrLn $ unwords [\"Hello\", \"world\"]"
+ , Para [ Str "Line" , Space , Str "numbering:" ]
+ , CodeBlock
+ ( "" , [] , [ ( "options" , "linenums" ) ] )
+ "puts 1\nputs 2\nputs 3"
+ , CodeBlock
+ ( "" , [] , [] ) "This doesn't have a language.\n +=\"hi\""
+ , Para
+ [ Str "And"
+ , Space
+ , Str "with"
+ , Space
+ , Str "a"
+ , Space
+ , Str "callout"
+ , Space
+ , Str "list:"
+ ]
+ , CodeBlock
+ ( "" , [ "ruby" ] , [] )
+ "require 'sinatra' \9312\n\nget '/hi' do \9313 \9314\n \"Hello World!\"\nend"
+ , Div
+ ( "" , [ "callout-list" ] , [] )
+ [ OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Library" , Space , Str "import" ] ]
+ , [ Para [ Str "URL" , Space , Str "mapping" ] ]
+ , [ Para [ Str "Response" , Space , Str "block" ] ]
+ ]
+ ]
+ , Para [ Str "Markdown-style" , Space , Str "fenced:" ]
+ , CodeBlock
+ ( "" , [ "ruby" ] , [] ) "def foo\n return 5\nend"
+ , Header 2 ( "_verse" , [] , [] ) [ Str "Verse" ]
+ , BlockQuote
+ [ Para
+ [ Str "The"
+ , Space
+ , Str "fog"
+ , Space
+ , Str "comes"
+ , LineBreak
+ , Str "on"
+ , Space
+ , Str "little"
+ , Space
+ , Str "cat"
+ , Space
+ , Str "feet."
+ ]
+ , Para
+ [ Str "\8212"
+ , Space
+ , Str "Carl"
+ , Space
+ , Str "Sandburg,"
+ , Space
+ , Str "two"
+ , Space
+ , Str "lines"
+ , Space
+ , Str "from"
+ , Space
+ , Str "the"
+ , Space
+ , Str "poem"
+ , Space
+ , Str "Fog"
+ ]
+ ]
+ , BlockQuote
+ [ Para
+ [ Str "The"
+ , Space
+ , Str "fog"
+ , Space
+ , Str "comes"
+ , LineBreak
+ , Str "on"
+ , Space
+ , Str "little"
+ , Space
+ , Str "cat"
+ , Space
+ , Str "feet."
+ , LineBreak
+ , Str "It"
+ , Space
+ , Str "sits"
+ , Space
+ , Str "looking"
+ , LineBreak
+ , Str "over"
+ , Space
+ , Str "harbor"
+ , Space
+ , Str "and"
+ , Space
+ , Str "city"
+ , LineBreak
+ , Str "on"
+ , Space
+ , Str "silent"
+ , Space
+ , Str "haunches"
+ , LineBreak
+ , Str "and"
+ , Space
+ , Str "then"
+ , Space
+ , Str "moves"
+ , Space
+ , Str "on."
+ ]
+ , Para
+ [ Str "\8212"
+ , Space
+ , Str "Carl"
+ , Space
+ , Str "Sandburg,"
+ , Space
+ , Str "Fog"
+ ]
+ ]
+ , Header
+ 2 ( "_collapsible" , [] , [] ) [ Str "Collapsible" ]
+ , Para
+ [ Str "Click"
+ , Space
+ , Str "here"
+ , Space
+ , Str "for"
+ , Space
+ , Str "more."
+ ]
+ , Div
+ ( ""
+ , [ "example" ]
+ , [ ( "options" , "collapsible,open" ) ]
+ )
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "is"
+ , Space
+ , Str "collapsible."
+ ]
+ , Para
+ [ Str "It"
+ , Space
+ , Str "can"
+ , Space
+ , Str "be"
+ , Space
+ , Str "hidden."
+ ]
+ ]
+ , Div
+ ( "" , [] , [ ( "options" , "collapsible" ) ] )
+ [ Div
+ ( "" , [ "title" ] , [] )
+ [ Para [ Str "Click" , Space , Str "me!" ] ]
+ , Para
+ [ Str "This"
+ , Space
+ , Str "paragraph"
+ , Space
+ , Str "is"
+ , SoftBreak
+ , Str "also"
+ , Space
+ , Str "collapsible."
+ ]
+ ]
+ , Header 2 ( "_quote" , [] , [] ) [ Str "Quote" ]
+ , BlockQuote
+ [ Para
+ [ Str "Everybody"
+ , Space
+ , Str "remember"
+ , Space
+ , Str "where"
+ , Space
+ , Str "we"
+ , Space
+ , Str "parked."
+ ]
+ , Para
+ [ Str "\8212"
+ , Space
+ , Str "Captain"
+ , Space
+ , Str "James"
+ , Space
+ , Str "T."
+ , Space
+ , Str "Kirk,"
+ , Space
+ , Str "Star"
+ , Space
+ , Str "Trek"
+ , Space
+ , Str "IV:"
+ , Space
+ , Str "The"
+ , Space
+ , Str "Voyage"
+ , Space
+ , Str "Home"
+ ]
+ ]
+ , BlockQuote
+ [ Para
+ [ Str "Dennis:"
+ , Space
+ , Str "Come"
+ , Space
+ , Str "and"
+ , Space
+ , Str "see"
+ , Space
+ , Str "the"
+ , Space
+ , Str "violence"
+ , Space
+ , Str "inherent"
+ , Space
+ , Str "in"
+ , Space
+ , Str "the"
+ , Space
+ , Str "system."
+ , Space
+ , Str "Help!"
+ , Space
+ , Str "Help!"
+ , Space
+ , Str "I\8217m"
+ , Space
+ , Str "being"
+ , LineBreak
+ , Str "repressed."
+ ]
+ , Para
+ [ Str "King"
+ , Space
+ , Str "Arthur:"
+ , Space
+ , Str "Bloody"
+ , Space
+ , Str "peasant!"
+ ]
+ , Para
+ [ Str "Dennis:"
+ , Space
+ , Str "Oh,"
+ , Space
+ , Str "what"
+ , Space
+ , Str "a"
+ , Space
+ , Str "giveaway!"
+ , Space
+ , Str "Did"
+ , Space
+ , Str "you"
+ , Space
+ , Str "hear"
+ , Space
+ , Str "that?"
+ , Space
+ , Str "Did"
+ , Space
+ , Str "you"
+ , Space
+ , Str "hear"
+ , Space
+ , Str "that,"
+ , Space
+ , Str "eh?"
+ , Space
+ , Str "That\8217s"
+ , Space
+ , Str "what"
+ , Space
+ , Str "I\8217m"
+ , LineBreak
+ , Str "on"
+ , Space
+ , Str "about!"
+ , Space
+ , Str "Did"
+ , Space
+ , Str "you"
+ , Space
+ , Str "see"
+ , Space
+ , Str "him"
+ , Space
+ , Str "repressing"
+ , Space
+ , Str "me?"
+ , Space
+ , Str "You"
+ , Space
+ , Str "saw"
+ , Space
+ , Str "him,"
+ , Space
+ , Str "Didn\8217t"
+ , Space
+ , Str "you?"
+ ]
+ , Para
+ [ Str "\8212"
+ , Space
+ , Str "Monty"
+ , Space
+ , Str "Python"
+ , Space
+ , Str "and"
+ , Space
+ , Str "the"
+ , Space
+ , Str "Holy"
+ , Space
+ , Str "Grail"
+ ]
+ ]
+ , BlockQuote
+ [ Para
+ [ Str "Roads?"
+ , Space
+ , Str "Where"
+ , Space
+ , Str "we\8217re"
+ , Space
+ , Str "going,"
+ , Space
+ , Str "we"
+ , Space
+ , Str "don\8217t"
+ , Space
+ , Str "need"
+ , Space
+ , Str "roads."
+ ]
+ ]
+ , Header 2 ( "_pass" , [] , [] ) [ Str "Pass" ]
+ , Para [ Str "pass" , Space , Emph [ Str "through" ] ]
+ , Header
+ 2
+ ( "_open_block" , [] , [] )
+ [ Str "Open" , Space , Str "block" ]
+ , Div
+ ( "" , [] , [ ( "key" , "a value" ) ] )
+ [ Div
+ ( "" , [ "title" ] , [] )
+ [ Para [ Str "A" , Space , Str "title." ] ]
+ , Para
+ [ Str "Any"
+ , Space
+ , Str "content"
+ , Space
+ , Str "can"
+ , Space
+ , Str "go"
+ , Space
+ , Str "here:"
+ ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "one" ] ] , [ Para [ Str "two" ] ] ]
+ ]
+ , Header 2 ( "_anchor" , [] , [] ) [ Str "Anchor" ]
+ , Div
+ ( "goals" , [] , [ ( "wrapper" , "1" ) ] )
+ [ BulletList
+ [ [ Para [ Str "one" ] ] , [ Para [ Str "two" ] ] ]
+ ]
+ , Header 2 ( "_breaks" , [] , [] ) [ Str "Breaks" ]
+ , Para
+ [ Str "Asciidoc"
+ , Space
+ , Str "thematic"
+ , Space
+ , Str "break:"
+ ]
+ , HorizontalRule
+ , Para [ Str "Markdown" , Space , Str "style:" ]
+ , HorizontalRule
+ , HorizontalRule
+ , HorizontalRule
+ , HorizontalRule
+ , Para [ Str "Page" , Space , Str "breaks:" ]
+ , Div
+ ( "" , [ "page-break" ] , [ ( "wrapper" , "1" ) ] )
+ [ HorizontalRule ]
+ , Div
+ ( ""
+ , [ "page-break" ]
+ , [ ( "options" , "always" ) , ( "wrapper" , "1" ) ]
+ )
+ [ HorizontalRule ]
+ , Header 2 ( "_list" , [] , [] ) [ Str "List" ]
+ , BulletList
+ [ [ Para
+ [ Str "Edgar" , Space , Str "Allan" , Space , Str "Poe" ]
+ ]
+ , [ Para
+ [ Str "Sheri" , Space , Str "S." , Space , Str "Tepper" ]
+ ]
+ , [ Para [ Str "Bill" , Space , Str "Bryson" ] ]
+ ]
+ , Div
+ ( "" , [] , [] )
+ [ Div
+ ( "" , [ "title" ] , [] )
+ [ Para
+ [ Str "Kizmet\8217s"
+ , Space
+ , Str "Favorite"
+ , Space
+ , Str "Authors"
+ ]
+ ]
+ , BulletList
+ [ [ Para
+ [ Str "Edgar"
+ , Space
+ , Str "Allan"
+ , Space
+ , Str "Poe"
+ ]
+ ]
+ , [ Para
+ [ Str "Sheri"
+ , Space
+ , Str "S."
+ , Space
+ , Str "Tepper"
+ ]
+ ]
+ , [ Para [ Str "Bill" , Space , Str "Bryson" ] ]
+ ]
+ ]
+ , BulletList
+ [ [ Para
+ [ Str "Edgar" , Space , Str "Allan" , Space , Str "Poe" ]
+ ]
+ , [ Para
+ [ Str "Sheri" , Space , Str "S." , Space , Str "Tepper" ]
+ ]
+ , [ Para [ Str "Bill" , Space , Str "Bryson" ] ]
+ ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Nested" , Space , Str "list" ]
+ , BulletList
+ [ [ Para
+ [ Str "West"
+ , Space
+ , Str "wood"
+ , Space
+ , Str "maze"
+ ]
+ , BulletList
+ [ [ Para [ Str "Maze" , Space , Str "heart" ]
+ , BulletList
+ [ [ Para
+ [ Str "Reflection" , Space , Str "pool" ]
+ ]
+ ]
+ ]
+ , [ Para [ Str "Secret" , Space , Str "exit" ] ]
+ ]
+ ]
+ , [ Para
+ [ Str "Level"
+ , Space
+ , Str "1"
+ , Space
+ , Str "list"
+ , Space
+ , Str "item"
+ ]
+ , BulletList
+ [ [ Para
+ [ Str "Level"
+ , Space
+ , Str "2"
+ , Space
+ , Str "list"
+ , Space
+ , Str "item"
+ ]
+ , BulletList
+ [ [ Para
+ [ Str "Level"
+ , Space
+ , Str "3"
+ , Space
+ , Str "list"
+ , Space
+ , Str "item"
+ ]
+ , BulletList
+ [ [ Para
+ [ Str "Level"
+ , Space
+ , Str "4"
+ , Space
+ , Str "list"
+ , Space
+ , Str "item"
+ ]
+ , BulletList
+ [ [ Para
+ [ Str "Level"
+ , Space
+ , Str "5"
+ , Space
+ , Str "list"
+ , Space
+ , Str "item"
+ ]
+ , BulletList
+ [ [ Para [ Str "etc." ] ] ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ , [ Para
+ [ Str "Level"
+ , Space
+ , Str "1"
+ , Space
+ , Str "list"
+ , Space
+ , Str "item"
+ ]
+ ]
+ ]
+ ]
+ ]
+ , BulletList
+ [ [ Para [ Str "one" ] ]
+ , [ Para [ Str "two" ] ]
+ , [ Para [ Str "three" ] ]
+ ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Protons" ] ]
+ , [ Para [ Str "Electrons" ] ]
+ , [ Para [ Str "Neutrons" ] ]
+ ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Protons" ] ]
+ , [ Para [ Str "Electrons" ] ]
+ , [ Para [ Str "Neutrons" ] ]
+ ]
+ , Para
+ [ Str "Start" , Space , Str "with" , Space , Str "4:" ]
+ , OrderedList
+ ( 4 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Step" , Space , Str "four" ] ]
+ , [ Para [ Str "Step" , Space , Str "five" ] ]
+ , [ Para [ Str "Step" , Space , Str "six" ] ]
+ ]
+ , Para [ Str "or" ]
+ , OrderedList
+ ( 4 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Step" , Space , Str "four" ] ]
+ , [ Para [ Str "Step" , Space , Str "five" ] ]
+ , [ Para [ Str "Step" , Space , Str "six" ] ]
+ ]
+ , Para [ Str "Reversed:" ]
+ , Div
+ ( "" , [] , [ ( "options" , "reversed" ) ] )
+ [ Div
+ ( "" , [ "title" ] , [] )
+ [ Para
+ [ Str "Parts"
+ , Space
+ , Str "of"
+ , Space
+ , Str "an"
+ , Space
+ , Str "atom"
+ ]
+ ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Protons" ] ]
+ , [ Para [ Str "Electrons" ] ]
+ , [ Para [ Str "Neutrons" ] ]
+ ]
+ ]
+ , Para [ Str "Nested" ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Step" , Space , Str "1" ] ]
+ , [ Para [ Str "Step" , Space , Str "2" ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Step" , Space , Str "2a" ] ]
+ , [ Para [ Str "Step" , Space , Str "2b" ] ]
+ ]
+ ]
+ , [ Para [ Str "Step" , Space , Str "3" ] ]
+ ]
+ , Para [ Str "Mixed" , Space , Str "nested" ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Linux" ]
+ , BulletList
+ [ [ Para [ Str "Fedora" ] ]
+ , [ Para [ Str "Ubuntu" ] ]
+ , [ Para [ Str "Slackware" ] ]
+ ]
+ ]
+ , [ Para [ Str "BSD" ]
+ , BulletList
+ [ [ Para [ Str "FreeBSD" ] ] , [ Para [ Str "NetBSD" ] ] ]
+ ]
+ ]
+ , Para [ Str "With" , Space , Str "spacing" ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Linux" ]
+ , BulletList
+ [ [ Para [ Str "Fedora" ] ]
+ , [ Para [ Str "Ubuntu" ] ]
+ , [ Para [ Str "Slackware" ] ]
+ ]
+ ]
+ , [ Para [ Str "BSD" ]
+ , BulletList
+ [ [ Para [ Str "FreeBSD" ] ] , [ Para [ Str "NetBSD" ] ] ]
+ ]
+ ]
+ , Para
+ [ Str "With" , Space , Str "number" , Space , Str "styles" ]
+ , OrderedList
+ ( 5 , LowerRoman , DefaultDelim )
+ [ [ Para [ Str "Five" ] ]
+ , [ Para [ Str "Six" ]
+ , OrderedList
+ ( 1 , LowerAlpha , DefaultDelim )
+ [ [ Para [ Str "a" ] ]
+ , [ Para [ Str "b" ] ]
+ , [ Para [ Str "c" ] ]
+ ]
+ ]
+ , [ Para [ Str "Seven" ] ]
+ ]
+ , Para [ Str "Checklist" ]
+ , BulletList
+ [ [ Para [ Str "\9746" , Space , Str "checked" ] ]
+ , [ Para
+ [ Str "\9746" , Space , Str "also" , Space , Str "checked" ]
+ ]
+ , [ Para
+ [ Str "\9744" , Space , Str "not" , Space , Str "checked" ]
+ ]
+ , [ Para
+ [ Str "normal" , Space , Str "list" , Space , Str "item" ]
+ ]
+ ]
+ , Para
+ [ Str "Separate"
+ , Space
+ , Str "lists"
+ , Space
+ , Str "with"
+ , Space
+ , Str "block"
+ , Space
+ , Str "attribute"
+ ]
+ , BulletList
+ [ [ Para [ Str "Apples" ] ]
+ , [ Para [ Str "Oranges" ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Wash" ] ] , [ Para [ Str "Slice" ] ] ]
+ ]
+ ]
+ , Para [ Str "Multiline" , Space , Str "items" ]
+ , BulletList
+ [ [ Para
+ [ Str "Blah"
+ , Space
+ , Str "blah."
+ , SoftBreak
+ , Str "Blah"
+ , Space
+ , Str "blah."
+ ]
+ ]
+ , [ Para
+ [ Str "The"
+ , Space
+ , Str "document"
+ , Space
+ , Str "header"
+ , Space
+ , Str "in"
+ , Space
+ , Str "AsciiDoc"
+ , Space
+ , Str "is"
+ , Space
+ , Str "optional."
+ , SoftBreak
+ , Str "If"
+ , Space
+ , Str "present,"
+ , Space
+ , Str "it"
+ , Space
+ , Str "must"
+ , Space
+ , Str "start"
+ , Space
+ , Str "with"
+ , Space
+ , Str "a"
+ , Space
+ , Str "document"
+ , Space
+ , Str "title."
+ ]
+ ]
+ ]
+ , BulletList
+ [ [ Para
+ [ Str "Optional"
+ , Space
+ , Str "author"
+ , Space
+ , Str "and"
+ , Space
+ , Str "revision"
+ , Space
+ , Str "information"
+ , Space
+ , Str "lines"
+ , SoftBreak
+ , Str "immediately"
+ , Space
+ , Str "follow"
+ , Space
+ , Str "the"
+ , Space
+ , Str "document"
+ , Space
+ , Str "title."
+ ]
+ ]
+ ]
+ , BulletList
+ [ [ Para
+ [ Str "The"
+ , Space
+ , Str "document"
+ , Space
+ , Str "header"
+ , Space
+ , Str "must"
+ , Space
+ , Str "be"
+ , Space
+ , Str "separated"
+ , Space
+ , Str "from"
+ , SoftBreak
+ , Str "the"
+ , Space
+ , Str "remainder"
+ , Space
+ , Str "of"
+ , Space
+ , Str "the"
+ , Space
+ , Str "document"
+ , Space
+ , Str "by"
+ , Space
+ , Str "one"
+ , Space
+ , Str "or"
+ , Space
+ , Str "more"
+ , SoftBreak
+ , Str "empty"
+ , Space
+ , Str "lines"
+ , Space
+ , Str "and"
+ , Space
+ , Str "it"
+ , Space
+ , Str "cannot"
+ , Space
+ , Str "contain"
+ , Space
+ , Str "empty"
+ , Space
+ , Str "lines."
+ ]
+ ]
+ ]
+ , Para [ Str "Complex" , Space , Str "item" ]
+ , BulletList
+ [ [ Para
+ [ Str "The"
+ , Space
+ , Str "header"
+ , Space
+ , Str "in"
+ , Space
+ , Str "AsciiDoc"
+ , Space
+ , Str "must"
+ , Space
+ , Str "start"
+ , Space
+ , Str "with"
+ , Space
+ , Str "a"
+ , Space
+ , Str "document"
+ , Space
+ , Str "title."
+ ]
+ , CodeBlock ( "" , [] , [] ) "= Document Title"
+ , Para
+ [ Str "Keep"
+ , Space
+ , Str "in"
+ , Space
+ , Str "mind"
+ , Space
+ , Str "that"
+ , Space
+ , Str "the"
+ , Space
+ , Str "header"
+ , Space
+ , Str "is"
+ , Space
+ , Str "optional."
+ ]
+ ]
+ , [ Para
+ [ Str "Optional"
+ , Space
+ , Str "author"
+ , Space
+ , Str "and"
+ , Space
+ , Str "revision"
+ , Space
+ , Str "information"
+ , Space
+ , Str "lines"
+ , Space
+ , Str "immediately"
+ , Space
+ , Str "follow"
+ , Space
+ , Str "the"
+ , Space
+ , Str "document"
+ , SoftBreak
+ , Str "title."
+ ]
+ , CodeBlock
+ ( "" , [] , [] )
+ "= Document Title\nDoc Writer <[email protected]>\nv1.0, 2022-01-01"
+ ]
+ , [ Para [ Str "Second" , Space , Str "item" ] ]
+ ]
+ , Para
+ [ Str "Empty"
+ , Space
+ , Str "principle"
+ , Space
+ , Str "element:"
+ ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [] , CodeBlock ( "" , [] , [] ) "test" ] ]
+ , Header 2 ( "_table" , [] , [] ) [ Str "Table" ]
+ , Header
+ 3
+ ( "_simple_with_column_specs" , [] , [] )
+ [ Str "Simple"
+ , Space
+ , Str "with"
+ , Space
+ , Str "column"
+ , Space
+ , Str "specs"
+ ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidth 0.375 )
+ , ( AlignDefault , ColWidth 0.25 )
+ , ( AlignDefault , ColWidth 0.375 )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "placed"
+ , Space
+ , Str "in"
+ , Space
+ , Str "the"
+ , Space
+ , Str "first"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "of"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "line"
+ , Space
+ , Str "starts"
+ , Space
+ , Str "with"
+ , Space
+ , Str "a"
+ , Space
+ , Str "vertical"
+ , Space
+ , Str "bar"
+ , Space
+ , Str "so"
+ , Space
+ , Str "this"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "placed"
+ , Space
+ , Str "in"
+ , Space
+ , Str "a"
+ , Space
+ , Str "new"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "in"
+ , SoftBreak
+ , Str "column"
+ , Space
+ , Str "2"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "When"
+ , Space
+ , Str "the"
+ , Space
+ , Str "processor"
+ , Space
+ , Str "encounters"
+ , Space
+ , Str "a"
+ , Space
+ , Str "whitespace"
+ , Space
+ , Str "followed"
+ , Space
+ , Str "by"
+ , Space
+ , Str "a"
+ , Space
+ , Str "vertical"
+ , Space
+ , Str "bar"
+ , Space
+ , Str "it"
+ , SoftBreak
+ , Str "ends"
+ , Space
+ , Str "the"
+ , Space
+ , Str "previous"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "and"
+ , Space
+ , Str "starts"
+ , Space
+ , Str "a"
+ , Space
+ , Str "new"
+ , Space
+ , Str "cell"
+ ]
+ ]
+ ]
+ ])
+ [ TableBody ( "" , [] , [] ) (RowHeadColumns 0) [] [] ]
+ (TableFoot ( "" , [] , [] ) [])
+ , Header
+ 3
+ ( "_repeated_column_in_specs" , [] , [] )
+ [ Str "Repeated"
+ , Space
+ , Str "column"
+ , Space
+ , Str "in"
+ , Space
+ , Str "specs"
+ ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignRight
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Strong
+ [ Str "This"
+ , Space
+ , Str "cell\8217s"
+ , Space
+ , Str "specifier"
+ , Space
+ , Str "indicates"
+ , Space
+ , Str "that"
+ , Space
+ , Str "this"
+ , Space
+ , Str "cell\8217s"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "right-aligned"
+ , Space
+ , Str "and"
+ , Space
+ , Str "bold."
+ ]
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "The"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "specifier"
+ , Space
+ , Str "on"
+ , Space
+ , Str "this"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "hasn\8217t"
+ , Space
+ , Str "been"
+ , Space
+ , Str "set"
+ , Space
+ , Str "explicitly,"
+ , Space
+ , Str "so"
+ , Space
+ , Str "the"
+ , Space
+ , Str "default"
+ , SoftBreak
+ , Str "properties"
+ , Space
+ , Str "are"
+ , Space
+ , Str "applied."
+ ]
+ ]
+ ]
+ ])
+ [ TableBody ( "" , [] , [] ) (RowHeadColumns 0) [] [] ]
+ (TableFoot ( "" , [] , [] ) [])
+ , Header
+ 3
+ ( "_simple_without_column_specs" , [] , [] )
+ [ Str "Simple"
+ , Space
+ , Str "without"
+ , Space
+ , Str "column"
+ , Space
+ , Str "specs"
+ ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "3"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "3"
+ ]
+ ]
+ ]
+ ])
+ , Header
+ 3
+ ( "_with_caption" , [] , [] )
+ [ Str "With" , Space , Str "caption" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption
+ Nothing
+ [ Plain
+ [ Str "My" , Space , Str "cool" , Space , Str "table." ]
+ ])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "3"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "3"
+ ]
+ ]
+ ]
+ ])
+ , Header
+ 3
+ ( "_no_header" , [] , [] )
+ [ Str "No" , Space , Str "header" ]
+ , Para
+ [ Str "By"
+ , Space
+ , Str "default"
+ , Space
+ , Str "the"
+ , Space
+ , Str "first"
+ , Space
+ , Str "line"
+ , Space
+ , Str "should"
+ , Space
+ , Str "turn"
+ , Space
+ , Str "into"
+ , Space
+ , Str "the"
+ , Space
+ , Str "header,"
+ , Space
+ , Str "but"
+ , Space
+ , Str "this"
+ , SoftBreak
+ , Str "can"
+ , Space
+ , Str "be"
+ , Space
+ , Str "disabled:"
+ ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead ( "" , [] , [] ) [])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "1"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "1"
+ ]
+ ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ ]
+ ])
+ , Para
+ [ Str "And"
+ , Space
+ , Str "also"
+ , Space
+ , Str "explicitly"
+ , Space
+ , Str "enabled:"
+ ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Cell" , Space , Str "A1" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Cell" , Space , Str "B1" ] ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Cell" , Space , Str "A2" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Cell" , Space , Str "B2" ] ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Cell" , Space , Str "A3" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Cell" , Space , Str "B3" ] ]
+ ]
+ ])
+ , Header 3 ( "_footer" , [] , [] ) [ Str "Footer" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidth 0.4 )
+ , ( AlignDefault , ColWidth 0.4 )
+ , ( AlignDefault , ColWidth 0.2 )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "3,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "3,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "footer"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "footer"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "3,"
+ , Space
+ , Str "footer"
+ , Space
+ , Str "row"
+ ]
+ ]
+ ]
+ ])
+ , Para [ Str "or" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "3"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "3"
+ ]
+ ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "footer"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "footer"
+ , Space
+ , Str "row"
+ ]
+ ]
+ ]
+ ])
+ , Header 3 ( "_alignment" , [] , [] ) [ Str "Alignment" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Column" , Space , Str "Name" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Column" , Space , Str "Name" ] ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignCenter
+ (RowSpan 1)
+ (ColSpan 2)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "spans"
+ , Space
+ , Str "two"
+ , Space
+ , Str "columns,"
+ , Space
+ , Str "and"
+ , Space
+ , Str "its"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "horizontally"
+ , Space
+ , Str "centered"
+ , Space
+ , Str "because"
+ , Space
+ , Str "the"
+ , SoftBreak
+ , Str "cell"
+ , Space
+ , Str "specifier"
+ , Space
+ , Str "includes"
+ , Space
+ , Str "the"
+ , Space
+ , Code ( "" , [] , [] ) "^"
+ , Space
+ , Str "operator."
+ ]
+ ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignCenter
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "duplicated"
+ , Space
+ , Str "in"
+ , Space
+ , Str "two"
+ , Space
+ , Str "adjacent"
+ , Space
+ , Str "columns."
+ , SoftBreak
+ , Str "Its"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "horizontally"
+ , Space
+ , Str "centered"
+ , Space
+ , Str "because"
+ , Space
+ , Str "the"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "specifier"
+ , SoftBreak
+ , Str "includes"
+ , Space
+ , Str "the"
+ , Space
+ , Code ( "" , [] , [] ) "^"
+ , Space
+ , Str "operator."
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignCenter
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "duplicated"
+ , Space
+ , Str "in"
+ , Space
+ , Str "two"
+ , Space
+ , Str "adjacent"
+ , Space
+ , Str "columns."
+ , SoftBreak
+ , Str "Its"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "horizontally"
+ , Space
+ , Str "centered"
+ , Space
+ , Str "because"
+ , Space
+ , Str "the"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "specifier"
+ , SoftBreak
+ , Str "includes"
+ , Space
+ , Str "the"
+ , Space
+ , Code ( "" , [] , [] ) "^"
+ , Space
+ , Str "operator."
+ ]
+ ]
+ ]
+ ])
+ , Header
+ 3
+ ( "_multiple_paragraphs_in_cells" , [] , [] )
+ [ Str "Multiple"
+ , Space
+ , Str "paragraphs"
+ , Space
+ , Str "in"
+ , Space
+ , Str "cells"
+ ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault ) ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Single"
+ , Space
+ , Str "paragraph"
+ , Space
+ , Str "on"
+ , Space
+ , Str "row"
+ , Space
+ , Str "1"
+ ]
+ ]
+ ]
+ ])
+ [ TableBody ( "" , [] , [] ) (RowHeadColumns 0) [] [] ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "First"
+ , Space
+ , Str "paragraph"
+ , Space
+ , Str "on"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ , Para
+ [ Str "Second"
+ , Space
+ , Str "paragraph"
+ , Space
+ , Str "on"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ ]
+ ])
+ , Header
+ 3
+ ( "_complex_table" , [] , [] )
+ [ Str "Complex" , Space , Str "table" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignRight
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Code ( "" , [] , [] ) "This"
+ , Space
+ , Code ( "" , [] , [] ) "content"
+ , Space
+ , Code ( "" , [] , [] ) "is"
+ , Space
+ , Code ( "" , [] , [] ) "duplicated"
+ , Space
+ , Code ( "" , [] , [] ) "across"
+ , Space
+ , Code ( "" , [] , [] ) "two"
+ , Space
+ , Code ( "" , [] , [] ) "columns."
+ ]
+ , Para
+ [ Code ( "" , [] , [] ) "It"
+ , Space
+ , Code ( "" , [] , [] ) "is"
+ , Space
+ , Code ( "" , [] , [] ) "aligned"
+ , Space
+ , Code ( "" , [] , [] ) "right"
+ , Space
+ , Code ( "" , [] , [] ) "horizontally."
+ ]
+ , Para
+ [ Code ( "" , [] , [] ) "And"
+ , Space
+ , Code ( "" , [] , [] ) "it"
+ , Space
+ , Code ( "" , [] , [] ) "is"
+ , Space
+ , Code ( "" , [] , [] ) "monospaced."
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignRight
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Code ( "" , [] , [] ) "This"
+ , Space
+ , Code ( "" , [] , [] ) "content"
+ , Space
+ , Code ( "" , [] , [] ) "is"
+ , Space
+ , Code ( "" , [] , [] ) "duplicated"
+ , Space
+ , Code ( "" , [] , [] ) "across"
+ , Space
+ , Code ( "" , [] , [] ) "two"
+ , Space
+ , Code ( "" , [] , [] ) "columns."
+ ]
+ , Para
+ [ Code ( "" , [] , [] ) "It"
+ , Space
+ , Code ( "" , [] , [] ) "is"
+ , Space
+ , Code ( "" , [] , [] ) "aligned"
+ , Space
+ , Code ( "" , [] , [] ) "right"
+ , Space
+ , Code ( "" , [] , [] ) "horizontally."
+ ]
+ , Para
+ [ Code ( "" , [] , [] ) "And"
+ , Space
+ , Code ( "" , [] , [] ) "it"
+ , Space
+ , Code ( "" , [] , [] ) "is"
+ , Space
+ , Code ( "" , [] , [] ) "monospaced."
+ ]
+ ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignCenter
+ (RowSpan 2)
+ (ColSpan 1)
+ [ Para
+ [ Strong
+ [ Str "This"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "spans"
+ , Space
+ , Str "3"
+ , Space
+ , Str "rows."
+ , Space
+ , Str "The"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "centered"
+ , Space
+ , Str "horizontally,"
+ , Space
+ , Str "aligned"
+ , Space
+ , Str "to"
+ , Space
+ , Str "the"
+ , Space
+ , Str "bottom"
+ , Space
+ , Str "of"
+ , Space
+ , Str "the"
+ , Space
+ , Str "cell,"
+ , Space
+ , Str "and"
+ , Space
+ , Str "strong."
+ ]
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Emph
+ [ Str "This"
+ , Space
+ , Str "content"
+ , Space
+ , Str "is"
+ , Space
+ , Str "emphasized."
+ ]
+ ]
+ ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ CodeBlock
+ ( "" , [] , [] )
+ "This content is aligned to the top of the cell and literal.\n\n"
+ ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ CodeBlock
+ ( "" , [] , [] ) "puts \"This is a source block!\""
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ []
+ ]
+ ])
+ , Header
+ 3
+ ( "_column_styles" , [] , [] )
+ [ Str "Column" , Space , Str "styles" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Code ( "" , [] , [] ) "monospace" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Code ( "" , [] , [] ) "mono" ] ]
+ ]
+ ])
+ [ TableBody ( "" , [] , [] ) (RowHeadColumns 0) [] [] ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "default" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Code ( "" , [] , [] ) "mono" ] ]
+ ]
+ ])
+ , Header
+ 3
+ ( "_block_elements_in_cells" , [] , [] )
+ [ Str "Block"
+ , Space
+ , Str "elements"
+ , Space
+ , Str "in"
+ , Space
+ , Str "cells"
+ ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Normal" , Space , Str "Style" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "AsciiDoc" , Space , Str "Style" ] ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "isn\8217t"
+ , Space
+ , Str "prefixed"
+ , Space
+ , Str "with"
+ , Space
+ , Str "an"
+ , Space
+ , Code ( "" , [] , [] ) "a"
+ , Str ","
+ , Space
+ , Str "so"
+ , Space
+ , Str "the"
+ , Space
+ , Str "processor"
+ , Space
+ , Str "doesn\8217t"
+ , Space
+ , Str "interpret"
+ , Space
+ , Str "the"
+ , SoftBreak
+ , Str "following"
+ , Space
+ , Str "lines"
+ , Space
+ , Str "as"
+ , Space
+ , Str "an"
+ , Space
+ , Str "AsciiDoc"
+ , Space
+ , Str "list."
+ ]
+ , Para
+ [ Str "*"
+ , Space
+ , Str "List"
+ , Space
+ , Str "item"
+ , Space
+ , Str "1"
+ , SoftBreak
+ , Str "*"
+ , Space
+ , Str "List"
+ , Space
+ , Str "item"
+ , Space
+ , Str "2"
+ , SoftBreak
+ , Str "*"
+ , Space
+ , Str "List"
+ , Space
+ , Str "item"
+ , Space
+ , Str "3"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "is"
+ , Space
+ , Str "prefixed"
+ , Space
+ , Str "with"
+ , Space
+ , Str "an"
+ , Space
+ , Code ( "" , [] , [] ) "a"
+ , Str ","
+ , Space
+ , Str "so"
+ , Space
+ , Str "the"
+ , Space
+ , Str "processor"
+ , Space
+ , Str "interprets"
+ , Space
+ , Str "the"
+ , Space
+ , Str "following"
+ , Space
+ , Str "lines"
+ , SoftBreak
+ , Str "as"
+ , Space
+ , Str "an"
+ , Space
+ , Str "AsciiDoc"
+ , Space
+ , Str "list."
+ ]
+ , BulletList
+ [ [ Para
+ [ Str "List"
+ , Space
+ , Str "item"
+ , Space
+ , Str "1"
+ ]
+ ]
+ , [ Para
+ [ Str "List"
+ , Space
+ , Str "item"
+ , Space
+ , Str "2"
+ ]
+ ]
+ , [ Para
+ [ Str "List"
+ , Space
+ , Str "item"
+ , Space
+ , Str "3"
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "isn\8217t"
+ , Space
+ , Str "prefixed"
+ , Space
+ , Str "with"
+ , Space
+ , Str "an"
+ , Space
+ , Code ( "" , [] , [] ) "a"
+ , Str ","
+ , Space
+ , Str "so"
+ , Space
+ , Str "the"
+ , Space
+ , Str "processor"
+ , Space
+ , Str "doesn\8217t"
+ , Space
+ , Str "interpret"
+ , Space
+ , Str "the"
+ , Space
+ , Str "listing"
+ , SoftBreak
+ , Str "block"
+ , Space
+ , Str "delimiters"
+ , Space
+ , Str "or"
+ , Space
+ , Str "the"
+ , Space
+ , Code ( "" , [] , [] ) "source"
+ , Space
+ , Str "style."
+ ]
+ , Para
+ [ Str "----"
+ , SoftBreak
+ , Str "import"
+ , Space
+ , Str "os"
+ , SoftBreak
+ , Str "print"
+ , Space
+ , Str "(\"%s\""
+ , Space
+ , Str "%(os.uname()))"
+ , SoftBreak
+ , Str "----"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "is"
+ , Space
+ , Str "prefixed"
+ , Space
+ , Str "with"
+ , Space
+ , Str "an"
+ , Space
+ , Code ( "" , [] , [] ) "a"
+ , Str ","
+ , Space
+ , Str "so"
+ , Space
+ , Str "the"
+ , Space
+ , Str "listing"
+ , Space
+ , Str "block"
+ , Space
+ , Str "is"
+ , Space
+ , Str "processed"
+ , Space
+ , Str "and"
+ , Space
+ , Str "rendered"
+ , SoftBreak
+ , Str "according"
+ , Space
+ , Str "to"
+ , Space
+ , Str "the"
+ , Space
+ , Code ( "" , [] , [] ) "source"
+ , Space
+ , Str "style"
+ , Space
+ , Str "rules."
+ ]
+ , CodeBlock
+ ( "" , [ "python" ] , [] )
+ "import os\nprint \"%s\" %(os.uname())"
+ ]
+ ]
+ ])
+ , Header
+ 3
+ ( "_col_and_rowspan" , [] , [] )
+ [ Str "Col" , Space , Str "and" , Space , Str "rowspan" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "1,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "2,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Column"
+ , Space
+ , Str "3,"
+ , Space
+ , Str "header"
+ , Space
+ , Str "row"
+ ]
+ ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 2)
+ (ColSpan 2)
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "cell"
+ , Space
+ , Str "spans"
+ , Space
+ , Str "2"
+ , Space
+ , Str "cols"
+ , Space
+ , Str "and"
+ , Space
+ , Str "2"
+ , Space
+ , Str "rows"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "3,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "2"
+ ]
+ ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "3,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "3"
+ ]
+ ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 3)
+ [ Para
+ [ Str "Cell"
+ , Space
+ , Str "in"
+ , Space
+ , Str "column"
+ , Space
+ , Str "1-3,"
+ , Space
+ , Str "row"
+ , Space
+ , Str "4"
+ ]
+ ]
+ ]
+ ])
+ , Header
+ 3
+ ( "_csv_table" , [] , [] )
+ [ Str "CSV" , Space , Str "table" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Artist" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Track" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Genre" ] ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Baauer" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Harlem" , Space , Str "Shake" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Hip" , Space , Str "Hop" ] ]
+ ]
+ ]
+ ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "The" , Space , Str "Lumineers" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Ho" , Space , Str "Hey" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Folk" , Space , Str "Rock" ] ]
+ ]
+ ])
+ , Para [ Str "or" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Artist" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Track" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Genre" ] ]
+ ]
+ ])
+ [ TableBody ( "" , [] , [] ) (RowHeadColumns 0) [] [] ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Baauer" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Harlem" , Space , Str "Shake" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Hip" , Space , Str "Hop" ] ]
+ ]
+ ])
+ , Header
+ 3
+ ( "_dsv_table" , [] , [] )
+ [ Str "DSV" , Space , Str "table" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "a" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "b" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "c" ] ]
+ ]
+ ])
+ [ TableBody ( "" , [] , [] ) (RowHeadColumns 0) [] [] ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "d" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "e" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "f" ] ]
+ ]
+ ])
+ , Para [ Str "or" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Artist" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Track" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Genre" ] ]
+ ]
+ ])
+ [ TableBody ( "" , [] , [] ) (RowHeadColumns 0) [] [] ]
+ (TableFoot
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Robyn" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Indestructible" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Para [ Str "Dance" ] ]
+ ]
+ ])
+ , Header
+ 2
+ ( "_definition_list" , [] , [] )
+ [ Str "Definition" , Space , Str "list" ]
+ , DefinitionList
+ [ ( [ Str "CPU" ]
+ , [ [ Para
+ [ Str "The"
+ , Space
+ , Str "brain"
+ , Space
+ , Str "of"
+ , Space
+ , Str "the"
+ , Space
+ , Str "computer."
+ ]
+ ]
+ ]
+ )
+ , ( [ Str "Hard" , Space , Str "drive" ]
+ , [ [ Para
+ [ Str "Permanent"
+ , Space
+ , Str "storage"
+ , Space
+ , Str "for"
+ , Space
+ , Str "operating"
+ , Space
+ , Str "system"
+ , Space
+ , Str "and/or"
+ , Space
+ , Str "user"
+ , Space
+ , Str "files."
+ ]
+ ]
+ ]
+ )
+ ]
+ , Para [ Str "Mixed" ]
+ , DefinitionList
+ [ ( [ Str "Dairy" ]
+ , [ [ BulletList
+ [ [ Para [ Str "Milk" ] ]
+ , [ Para [ Str "Eggs" ]
+ , DefinitionList [ ( [ Str "Bakery" ] , [ [] ] ) ]
+ ]
+ , [ Para [ Str "Bread" ]
+ , DefinitionList [ ( [ Str "Produce" ] , [ [] ] ) ]
+ ]
+ , [ Para [ Str "Bananas" ] ]
+ ]
+ ]
+ ]
+ )
+ ]
+ , Para [ Str "With" , Space , Str "spaces" ]
+ , DefinitionList [ ( [ Str "Dairy" ] , [ [] ] ) ]
+ , BulletList
+ [ [ Para [ Str "Milk" ] ] , [ Para [ Str "Eggs" ] ] ]
+ , DefinitionList [ ( [ Str "Bakery" ] , [ [] ] ) ]
+ , BulletList [ [ Para [ Str "Bread" ] ] ]
+ , DefinitionList [ ( [ Str "Produce" ] , [ [] ] ) ]
+ , BulletList [ [ Para [ Str "Bananas" ] ] ]
+ , Para [ Str "Nested" ]
+ , DefinitionList
+ [ ( [ Str "Operating" , Space , Str "Systems" ]
+ , [ [ DefinitionList
+ [ ( [ Str "Linux" ]
+ , [ [ OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Fedora" ]
+ , BulletList [ [ Para [ Str "Desktop" ] ] ]
+ ]
+ , [ Para [ Str "Ubuntu" ]
+ , BulletList
+ [ [ Para [ Str "Desktop" ] ]
+ , [ Para [ Str "Server" ] ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ )
+ , ( [ Str "BSD" ]
+ , [ [ OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "FreeBSD" ] ]
+ , [ Para [ Str "NetBSD" ]
+ , DefinitionList
+ [ ( [ Str "Cloud"
+ , Space
+ , Str "Providers"
+ ]
+ , [ [ DefinitionList
+ [ ( [ Str "PaaS" ] , [ [] ] )
+ ]
+ ]
+ ]
+ )
+ ]
+ ]
+ , [ Para [ Str "OpenShift" ] ]
+ , [ Para [ Str "CloudBees" ] ]
+ ]
+ ]
+ ]
+ )
+ , ( [ Str "IaaS" ]
+ , [ [ OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "Amazon" , Space , Str "EC2" ]
+ ]
+ ]
+ ]
+ ]
+ )
+ ]
+ , Para
+ [ Str "This"
+ , Space
+ , Str "just"
+ , Space
+ , Str "affects"
+ , Space
+ , Str "the"
+ , Space
+ , Str "output:"
+ ]
+ ]
+ ]
+ )
+ ]
+ , Div
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" )
+ , ( "itemwidth" , "75" )
+ , ( "labelwidth" , "25" )
+ ]
+ )
+ [ DefinitionList
+ [ ( [ Str "CPU" ]
+ , [ [ Para
+ [ Str "The"
+ , Space
+ , Str "brain"
+ , Space
+ , Str "of"
+ , Space
+ , Str "the"
+ , Space
+ , Str "computer."
+ ]
+ ]
+ ]
+ )
+ , ( [ Str "RAM" ]
+ , [ [ Para
+ [ Str "Temporarily"
+ , Space
+ , Str "stores"
+ , Space
+ , Str "information"
+ , Space
+ , Str "the"
+ , Space
+ , Str "CPU"
+ , Space
+ , Str "uses"
+ , Space
+ , Str "during"
+ , Space
+ , Str "operation."
+ ]
+ ]
+ ]
+ )
+ ]
+ ]
+ , Para [ Str "Q&A" , Space , Str "list" ]
+ , DefinitionList
+ [ ( [ Str "What"
+ , Space
+ , Str "is"
+ , Space
+ , Str "the"
+ , Space
+ , Str "answer?"
+ ]
+ , [ [ Para
+ [ Str "This"
+ , Space
+ , Str "is"
+ , Space
+ , Str "the"
+ , Space
+ , Str "answer."
+ ]
+ ]
+ ]
+ )
+ , ( [ Str "Are"
+ , Space
+ , Str "cameras"
+ , Space
+ , Str "allowed?"
+ ]
+ , [ [] ]
+ )
+ , ( [ Str "Are"
+ , Space
+ , Str "backpacks"
+ , Space
+ , Str "allowed?"
+ ]
+ , [ [ Para [ Str "No." ] ] ]
+ )
+ ]
+ , Para
+ [ Str "Ordered"
+ , Space
+ , Str "description"
+ , Space
+ , Str "list"
+ , Space
+ , Str "(with"
+ , Space
+ , Str "numbers)"
+ ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ DefinitionList
+ [ ( [ Str "&" ] , [ [ Para [ Str "ampersand" ] ] ] ) ]
+ ]
+ , [ DefinitionList
+ [ ( [ Str ">" ]
+ , [ [ Para [ Str "greater" , Space , Str "than" ] ] ]
+ )
+ ]
+ ]
+ ]
+ , Header
+ 2
+ ( "_block_macros" , [] , [] )
+ [ Str "Block" , Space , Str "macros" ]
+ , Figure
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ Plain
+ [ Image
+ ( ""
+ , []
+ , [ ( "width" , "300px" ) , ( "height" , "200px" ) ]
+ )
+ [ Str "Sunset" ]
+ ( "sunset.jpg" , "" )
+ ]
+ ]
+ , Plain
+ [ Image
+ ( "" , [] , [] )
+ [ Str "mymovie.mp4" ]
+ ( "mymovie.mp4" , "" )
+ ]
+ , Plain
+ [ Image
+ ( "" , [] , [] ) [ Str "mysong.mp3" ] ( "mysong.mp3" , "" )
+ ]
+ , Div ( "toc" , [] , [] ) []
+ , Div
+ ( ""
+ , [ "included" ]
+ , [ ( "path" , "asciidoc-reader-include.adoc" ) ]
+ )
+ [ Para
+ [ Str "This"
+ , Space
+ , Str "is"
+ , Space
+ , Str "a"
+ , Space
+ , Str "test!"
+ ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "one" ]
+ , OrderedList
+ ( 1 , DefaultStyle , DefaultDelim )
+ [ [ Para [ Str "two" ] ] ]
+ ]
+ ]
+ ]
+ ]