aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2024-01-13 10:17:15 -0800
committerJohn MacFarlane <[email protected]>2024-02-13 23:10:42 -0800
commit8c42926cb2161efac51e259a25d2047d31de3538 (patch)
treee60c0eccc5a81aacb191702b5de24dc5108ea4e7
parentea2466724b80da6f2163d0a29def3090ca3a5618 (diff)
Add djot reader and writer.djot
Djot is a light markup syntax (https://djot.net). This patch adds djot as input and output formats. API changes: Add Text.Pandoc.Readers.Djot Add Text.Pandoc.Writers.Djot
-rw-r--r--.github/workflows/ci.yml2
-rw-r--r--MANUAL.txt3
-rw-r--r--cabal.project5
-rw-r--r--data/templates/default.djot27
-rw-r--r--pandoc.cabal8
-rw-r--r--src/Text/Pandoc/Extensions.hs1
-rw-r--r--src/Text/Pandoc/Format.hs1
-rw-r--r--src/Text/Pandoc/Readers.hs4
-rw-r--r--src/Text/Pandoc/Readers/Djot.hs274
-rw-r--r--src/Text/Pandoc/Writers.hs3
-rw-r--r--src/Text/Pandoc/Writers/Djot.hs296
-rw-r--r--stack.yaml2
-rw-r--r--test/Tests/Old.hs5
-rw-r--r--test/djot-reader.djot749
-rw-r--r--test/djot-reader.native986
-rw-r--r--test/tables.djot54
-rw-r--r--test/writer.djot749
17 files changed, 3166 insertions, 3 deletions
diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml
index d2e35641d..3b5ff8b87 100644
--- a/.github/workflows/ci.yml
+++ b/.github/workflows/ci.yml
@@ -5,7 +5,7 @@ on:
branches:
- '*'
- '!rc/*'
- - '!typst-writer'
+ - '!djot'
paths-ignore:
- 'doc/*.md'
- 'MANUAL.txt'
diff --git a/MANUAL.txt b/MANUAL.txt
index 4c885cea1..a09e8c9f4 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -233,6 +233,7 @@ header when requesting a document from a URL:
- `csljson` ([CSL JSON] bibliography)
- `csv` ([CSV] table)
- `tsv` ([TSV] table)
+ - `djot` ([Djot markup])
- `docbook` ([DocBook])
- `docx` ([Word docx])
- `dokuwiki` ([DokuWiki markup])
@@ -295,6 +296,7 @@ header when requesting a document from a URL:
- `commonmark_x` ([CommonMark] Markdown with extensions)
- `context` ([ConTeXt])
- `csljson` ([CSL JSON] bibliography)
+ - `djot` ([Djot markup])
- `docbook` or `docbook4` ([DocBook] 4)
- `docbook5` (DocBook 5)
- `docx` ([Word docx])
@@ -479,6 +481,7 @@ header when requesting a document from a URL:
[ConTeXt]: https://www.contextgarden.net/
[Rich Text Format]: https://en.wikipedia.org/wiki/Rich_Text_Format
[DocBook]: https://docbook.org
+[Djot markup]: https://djot.net
[JATS]: https://jats.nlm.nih.gov
[BITS]: https://jats.nlm.nih.gov/extensions/bits/
[Jira]: https://jira.atlassian.com/secure/WikiRendererHelpAction.jspa?section=all
diff --git a/cabal.project b/cabal.project
index 90a6747de..29cbd7cc6 100644
--- a/cabal.project
+++ b/cabal.project
@@ -23,3 +23,8 @@ source-repository-package
type: git
location: https://github.com/jgm/typst-hs
tag: abfe46fd48ae3610c6522c3dbb1d84a2b2fafb74
+
+source-repository-package
+ type: git
+ location: https://github.com/jgm/djoths
+ tag: 3d53e40442d22726430b6a89bfb7fba92cd99a91
diff --git a/data/templates/default.djot b/data/templates/default.djot
new file mode 100644
index 000000000..d3d815f55
--- /dev/null
+++ b/data/templates/default.djot
@@ -0,0 +1,27 @@
+$if(title)$
+# $title$
+
+$endif$
+$if(author)$
+$for(author)$
+$author$
+$endfor$
+
+$endif$
+$if(date)$
+$date$
+
+$endif$
+$for(header-includes)$
+$header-includes$
+
+$endfor$
+$for(include-before)$
+$include-before$
+
+$endfor$
+$body$
+$for(include-after)$
+$include-after$
+
+$endfor$
diff --git a/pandoc.cabal b/pandoc.cabal
index f74225710..b0f6304be 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -271,6 +271,7 @@ extra-source-files:
test/media/rId27.jpg
test/typst-reader.typ
test/undergradmath.typ
+ test/djot-reader.latex
test/latex-reader.latex
test/textile-reader.textile
test/markdown-reader-more.txt
@@ -293,6 +294,7 @@ extra-source-files:
test/tables.jats_articleauthoring
test/tables.jats_publishing
test/tables.jira
+ test/tables.djot
test/tables.dokuwiki
test/tables.zimwiki
test/tables.icml
@@ -329,6 +331,7 @@ extra-source-files:
test/testsuite.txt
test/writer.latex
test/writer.context
+ test/writer.djot
test/writer.docbook4
test/writer.docbook5
test/writer.jats_archiving
@@ -523,7 +526,8 @@ library
zlib >= 0.5 && < 0.8,
xml >= 1.3.12 && < 1.4,
typst >= 0.5 && < 0.5.1,
- vector >= 0.12 && < 0.14
+ vector >= 0.12 && < 0.14,
+ djot >= 0.1 && < 0.2
if !os(windows)
build-depends: unix >= 2.4 && < 2.9
@@ -580,6 +584,7 @@ library
Text.Pandoc.Readers.CSV,
Text.Pandoc.Readers.RTF,
Text.Pandoc.Readers.Typst,
+ Text.Pandoc.Readers.Djot,
Text.Pandoc.Writers,
Text.Pandoc.Writers.Native,
Text.Pandoc.Writers.DocBook,
@@ -592,6 +597,7 @@ library
Text.Pandoc.Writers.Jira,
Text.Pandoc.Writers.LaTeX,
Text.Pandoc.Writers.ConTeXt,
+ Text.Pandoc.Writers.Djot,
Text.Pandoc.Writers.Typst,
Text.Pandoc.Writers.OpenDocument,
Text.Pandoc.Writers.Texinfo,
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index 22e7cc845..c23f6f1f8 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -654,4 +654,5 @@ getAllExtensions f = universalExtensions <> getAll f
extensionsFromList
[ Ext_smart ]
getAll "typst" = extensionsFromList [Ext_citations]
+ getAll "djot" = extensionsFromList [Ext_sourcepos]
getAll _ = mempty
diff --git a/src/Text/Pandoc/Format.hs b/src/Text/Pandoc/Format.hs
index 5f9459e3e..96f905b35 100644
--- a/src/Text/Pandoc/Format.hs
+++ b/src/Text/Pandoc/Format.hs
@@ -179,6 +179,7 @@ formatFromFilePath x =
".csv" -> defFlavor "csv"
".ctx" -> defFlavor "context"
".db" -> defFlavor "docbook"
+ ".dj" -> defFlavor "djot"
".doc" -> defFlavor "doc" -- so we get an "unknown reader" error
".docx" -> defFlavor "docx"
".dokuwiki" -> defFlavor "dokuwiki"
diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs
index 1b7be5163..83f0d3c2e 100644
--- a/src/Text/Pandoc/Readers.hs
+++ b/src/Text/Pandoc/Readers.hs
@@ -112,6 +112,7 @@ import Text.Pandoc.Readers.EndNote
import Text.Pandoc.Readers.RIS
import Text.Pandoc.Readers.RTF
import Text.Pandoc.Readers.Typst
+import Text.Pandoc.Readers.Djot
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Sources (ToSources(..), sourcesToText)
@@ -165,7 +166,8 @@ readers = [("native" , TextReader readNative)
,("ris" , TextReader readRIS)
,("rtf" , TextReader readRTF)
,("typst" , TextReader readTypst)
- ]
+ ,("djot" , TextReader readDjot)
+ ]
-- | Retrieve reader, extensions based on format spec (format+extensions).
getReader :: PandocMonad m => Format.FlavoredFormat -> m (Reader m, Extensions)
diff --git a/src/Text/Pandoc/Readers/Djot.hs b/src/Text/Pandoc/Readers/Djot.hs
new file mode 100644
index 000000000..6cb67f41e
--- /dev/null
+++ b/src/Text/Pandoc/Readers/Djot.hs
@@ -0,0 +1,274 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
+{- |
+ Module : Text.Pandoc.Readers.Djot
+ 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 Djot document as a Pandoc AST.
+-}
+module Text.Pandoc.Readers.Djot
+ ( readDjot
+ )
+where
+
+import Text.Pandoc.Class
+import Text.Pandoc.Sources
+import Text.Parsec.Pos (newPos)
+import Text.Pandoc.Options
+import Text.Pandoc.Definition
+import Text.Pandoc.Shared (addPandocAttributes, tshow)
+import qualified Text.Pandoc.UTF8 as UTF8
+import Djot (ParseOptions(..), SourcePosOption(..), parseDoc, Pos(..))
+import qualified Djot.AST as D
+import Text.Pandoc.Error (PandocError(..))
+import Control.Monad.Except (throwError)
+import qualified Data.Text as T
+import Text.Pandoc.Builder
+import Text.Pandoc.Logging
+import Text.Pandoc.Emoji (emojiToInline)
+import Control.Monad.Reader
+import qualified Data.Foldable as F
+import Data.List (foldl')
+import Data.ByteString (ByteString)
+-- import Debug.Trace
+
+-- | Read Djot from an input string and return a Pandoc document.
+readDjot :: (PandocMonad m, ToSources a) => ReaderOptions -> a -> m Pandoc
+readDjot opts inp = do
+ let sources = toSources inp
+ case parseDoc ParseOptions{ sourcePositions =
+ if isEnabled Ext_sourcepos opts
+ then AllSourcePos
+ else NoSourcePos }
+ (UTF8.fromText $ sourcesToText sources) of
+ Left e -> throwError $ PandocParseError $ T.pack $ show e
+ Right d ->
+ runReaderT (doc <$> convertBlocks (D.docBlocks d))
+ Env{ references = D.docReferences d <> D.docAutoReferences d
+ , footnotes = D.docFootnotes d
+ }
+
+data Env =
+ Env{ references :: D.ReferenceMap
+ , footnotes :: D.NoteMap
+ }
+ deriving (Show, Ord, Eq)
+
+convertBlocks :: PandocMonad m => D.Blocks -> ReaderT Env m Blocks
+convertBlocks = fmap mconcat . mapM convertBlock . F.toList . D.unMany
+
+convertBlock :: PandocMonad m => D.Node D.Block -> ReaderT Env m Blocks
+convertBlock (D.Node pos attr bl) = addAttrToBlock pos attr <$>
+ case bl of
+ D.Para ils -> para <$> convertInlines ils
+ D.Section bls -> divWith ("",["section"],[]) <$> convertBlocks bls
+ D.Heading lev ils -> header lev <$> convertInlines ils
+ D.BlockQuote bls -> blockQuote <$> convertBlocks bls
+ D.CodeBlock lang bs -> pure $
+ codeBlockWith ("", [UTF8.toText lang], []) $ UTF8.toText bs
+ D.Div bls -> divWith nullAttr <$> convertBlocks bls
+ D.OrderedList olattr listSpacing items ->
+ orderedListWith olattr' .
+ (case listSpacing of
+ D.Tight -> map toTight
+ D.Loose -> id) <$> mapM convertBlocks items
+ where
+ olattr' = ( D.orderedListStart olattr
+ , case D.orderedListStyle olattr of
+ D.Decimal -> Decimal
+ D.LetterUpper -> UpperAlpha
+ D.LetterLower -> LowerAlpha
+ D.RomanUpper -> UpperRoman
+ D.RomanLower -> LowerRoman
+ , case D.orderedListDelim olattr of
+ D.RightPeriod -> Period
+ D.RightParen -> OneParen
+ D.LeftRightParen -> TwoParens
+ )
+ D.BulletList listSpacing items ->
+ bulletList .
+ (case listSpacing of
+ D.Tight -> map toTight
+ D.Loose -> id) <$> mapM convertBlocks items
+ D.TaskList listSpacing items ->
+ bulletList .
+ (case listSpacing of
+ D.Tight -> map toTight
+ D.Loose -> id) <$> mapM toTaskListItem items
+ D.DefinitionList listSpacing items ->
+ definitionList .
+ (case listSpacing of
+ D.Tight -> map (\(t,d) -> (t, map toTight d))
+ D.Loose -> id) <$> mapM toDlItem items
+ where
+ toDlItem (ils,bls) = (,) <$> convertInlines ils
+ <*> ((:[]) <$> convertBlocks bls)
+ D.ThematicBreak -> pure horizontalRule
+ D.Table mbCaption rows -> do
+ capt <- case mbCaption of
+ Just (D.Caption bls') ->
+ Caption Nothing . toList <$> convertBlocks bls'
+ Nothing -> pure $ Caption Nothing mempty
+ let toAlign D.AlignLeft = AlignLeft
+ toAlign D.AlignRight = AlignRight
+ toAlign D.AlignCenter = AlignCenter
+ toAlign D.AlignDefault = AlignDefault
+ let toColSpec (D.Cell _ align _) = (toAlign align, ColWidthDefault)
+ let colspecs = case rows of
+ [] -> []
+ (cells:_) -> map toColSpec cells
+ let (headrow, rest) =
+ case rows of
+ (r@(D.Cell D.HeadCell _ _ : _) : rs) -> (r, rs)
+ _ -> ([],rows)
+ let getBody bods row =
+ case row of
+ (D.Cell D.HeadCell _ _ : _) ->
+ case bods of
+ [] -> [([row],[])]
+ ([],_):_ -> (([row],[]):bods)
+ (hs,bs):rs -> (hs,row:bs):rs
+ _ -> case bods of
+ (hs,bs):rs -> (hs,row:bs):rs
+ [] -> [([],[row])]
+ let reverseSnd (as,bs) = (as,reverse bs)
+ let bodies = reverse $ map reverseSnd $ foldl' getBody [] rest
+ let toCell (D.Cell _ al ils) =
+ Cell nullAttr (toAlign al) (RowSpan 1) (ColSpan 1)
+ . (\is -> [Para $ toList is]) <$> convertInlines ils
+ let toRow = fmap (Row nullAttr) . mapM toCell
+ thead <- TableHead mempty <$> mapM toRow [headrow]
+ let toTableBody (hs, rs) =
+ TableBody mempty (RowHeadColumns 0) <$>
+ mapM toRow hs <*> mapM toRow rs
+ tbodies <- mapM toTableBody bodies
+ let tfoot = TableFoot mempty []
+ pure $ singleton $ Table mempty capt colspecs thead tbodies tfoot
+ D.RawBlock (D.Format fmt) bs -> pure $
+ rawBlock (UTF8.toText fmt) (UTF8.toText bs)
+
+addAttrToBlock :: Pos -> D.Attr -> Blocks -> Blocks
+addAttrToBlock pos (D.Attr as) =
+ addPandocAttributes $
+ case pos of
+ NoPos -> textkvs
+ Pos sl sc el ec ->
+ ("data-pos", tshow sl <> ":" <> tshow sc <>
+ "-" <> tshow el <> ":" <> tshow ec) : textkvs
+ where
+ textkvs = (map (\(k,v) -> (UTF8.toText k, UTF8.toText v))
+ (filter (not . internalAttribute) as))
+
+addAttrToInline :: Pos -> D.Attr -> Inlines -> Inlines
+addAttrToInline pos (D.Attr as) =
+ addPandocAttributes $
+ case pos of
+ NoPos -> textkvs
+ Pos sl sc el ec ->
+ ("data-pos", tshow sl <> ":" <> tshow sc <>
+ "-" <> tshow el <> ":" <> tshow ec) : textkvs
+ where
+ textkvs = (map (\(k,v) -> (UTF8.toText k, UTF8.toText v))
+ (filter (not . internalAttribute) as))
+
+convertInlines :: PandocMonad m => D.Inlines -> ReaderT Env m Inlines
+convertInlines = fmap mconcat . mapM convertInline . F.toList . D.unMany
+
+convertInline :: PandocMonad m => D.Node D.Inline -> ReaderT Env m Inlines
+convertInline (D.Node pos attr il) = addAttrToInline pos attr <$>
+ case il of
+ D.Str bs -> pure $ str (UTF8.toText bs)
+ D.Emph ils -> emph <$> convertInlines ils
+ D.Strong ils -> strong <$> convertInlines ils
+ D.Highlight ils -> spanWith ("",["highlighted"],[]) <$> convertInlines ils
+ D.Insert ils -> spanWith ("",["inserted"],[]) <$> convertInlines ils
+ D.Delete ils -> spanWith ("",["deleted"],[]) <$> convertInlines ils
+ D.Subscript ils -> subscript <$> convertInlines ils
+ D.Superscript ils -> superscript <$> convertInlines ils
+ D.Span ils -> spanWith nullAttr <$> convertInlines ils
+ D.Quoted D.DoubleQuotes ils -> doubleQuoted <$> convertInlines ils
+ D.Quoted D.SingleQuotes ils -> singleQuoted <$> convertInlines ils
+ D.Verbatim bs -> pure $ code (UTF8.toText bs)
+ D.Symbol bs -> pure $
+ let s = UTF8.toText bs
+ in maybe (spanWith ("",["symbol"],[]) (str s)) singleton $ emojiToInline s
+ D.Math sty bs -> pure $
+ (case sty of
+ D.DisplayMath -> displayMath
+ D.InlineMath -> math) (UTF8.toText bs)
+ D.Link ils target ->
+ case target of
+ D.Direct url -> link (UTF8.toText url) "" <$> convertInlines ils
+ D.Reference label -> do
+ refs <- asks references
+ case D.lookupReference label refs of
+ Just (url, lattr) ->
+ addAttrToInline pos lattr .
+ link (UTF8.toText url) "" <$> convertInlines ils
+ Nothing -> do
+ report $ ReferenceNotFound (UTF8.toText label) (newPos "" 0 0)
+ link "" "" <$> convertInlines ils
+ D.Image ils target ->
+ case target of
+ D.Direct url -> image (UTF8.toText url) "" <$> convertInlines ils
+ D.Reference label -> do
+ refs <- asks references
+ case D.lookupReference label refs of
+ Just (url, lattr) ->
+ addAttrToInline pos lattr .
+ image (UTF8.toText url) "" <$> convertInlines ils
+ Nothing -> do
+ report $ ReferenceNotFound (UTF8.toText label) (newPos "" 0 0)
+ image "" "" <$> convertInlines ils
+ D.FootnoteReference bs -> do
+ notes <- asks footnotes
+ case D.lookupNote bs notes of
+ Just bls -> note <$> convertBlocks bls
+ Nothing -> do
+ -- TODO consider new warning for this?
+ report $ IgnoredElement ("Undefined footnote reference " <> tshow bs)
+ pure mempty
+ D.UrlLink bs -> do
+ let url = UTF8.toText bs
+ pure $ linkWith ("",["uri"],[]) url "" (str url)
+ D.EmailLink bs -> do
+ let email = UTF8.toText bs
+ pure $ linkWith ("",["email"],[]) ("mailto:" <> email) "" (str email)
+ D.RawInline (D.Format fbs) bs -> pure $
+ rawInline (UTF8.toText fbs) (UTF8.toText bs)
+ D.NonBreakingSpace -> pure $ str "\160"
+ D.SoftBreak -> pure softbreak
+ D.HardBreak -> pure linebreak
+
+internalAttribute :: (ByteString, ByteString) -> Bool
+internalAttribute ("_implicit",_) = True
+internalAttribute ("_autogen",_) = True
+internalAttribute _ = False
+
+toTight :: Blocks -> Blocks
+toTight (Many bls) = Many $ paraToPlain <$> bls
+ where
+ paraToPlain (Para ils) = Plain ils
+ paraToPlain x = x
+
+toTaskListItem :: PandocMonad m
+ => (D.TaskStatus, D.Blocks) -> ReaderT Env m Blocks
+toTaskListItem (status, bls) = do
+ bls' <- convertBlocks bls
+ case toList bls' of
+ (Para ils : rest) -> pure $
+ fromList $ Para (Str taskmarker : Space : ils) : rest
+ _ -> pure $ para (str taskmarker) <> bls'
+ where
+ taskmarker
+ | status == D.Complete = "[X]"
+ | otherwise = "[ ]"
diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs
index bc0f9bb2a..9443c2003 100644
--- a/src/Text/Pandoc/Writers.hs
+++ b/src/Text/Pandoc/Writers.hs
@@ -30,6 +30,7 @@ module Text.Pandoc.Writers
, writeConTeXt
, writeCslJson
, writeDZSlides
+ , writeDjot
, writeDocBook4
, writeDocBook5
, writeDocx
@@ -95,6 +96,7 @@ import Text.Pandoc.Writers.ChunkedHTML
import Text.Pandoc.Writers.CommonMark
import Text.Pandoc.Writers.ConTeXt
import Text.Pandoc.Writers.CslJson
+import Text.Pandoc.Writers.Djot
import Text.Pandoc.Writers.DocBook
import Text.Pandoc.Writers.Docx
import Text.Pandoc.Writers.DokuWiki
@@ -197,6 +199,7 @@ writers = [
,("biblatex" , TextWriter writeBibLaTeX)
,("markua" , TextWriter writeMarkua)
,("chunkedhtml" , ByteStringWriter writeChunkedHTML)
+ ,("djot" , TextWriter writeDjot)
]
-- | Retrieve writer, extensions based on formatSpec (format+extensions).
diff --git a/src/Text/Pandoc/Writers/Djot.hs b/src/Text/Pandoc/Writers/Djot.hs
new file mode 100644
index 000000000..0e605398e
--- /dev/null
+++ b/src/Text/Pandoc/Writers/Djot.hs
@@ -0,0 +1,296 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{- |
+ Module : Text.Pandoc.Writers.Djot
+ Copyright : Copyright (C) 2024 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <[email protected]>
+ Stability : alpha
+ Portability : portable
+
+Conversion of 'Pandoc' format into Djot markup (<https://djot.net>).
+-}
+module Text.Pandoc.Writers.Djot (
+ writeDjot
+ ) where
+import Text.Pandoc.Definition
+import Text.Pandoc.Logging
+import Text.Pandoc.Class ( PandocMonad , report )
+import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..))
+import Data.Text (Text)
+import Data.Set (Set)
+import qualified Data.Set as Set
+import qualified Data.ByteString as B
+import qualified Data.ByteString.Char8 as B8
+import Data.List (intersperse)
+import qualified Data.Text as T
+import qualified Data.Map as M
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.Pandoc.Writers.Shared ( metaToContext, defField, toLegacyTable )
+import Text.Pandoc.Shared (isTightList, tshow, stringify, onlySimpleTableCells,
+ makeSections)
+import Text.DocLayout
+import Text.DocTemplates (renderTemplate)
+
+import Control.Monad.State
+import Control.Monad (zipWithM, when)
+import Data.Maybe (fromMaybe)
+import qualified Djot.AST as D
+import Djot (renderDjot, RenderOptions(..), toIdentifier)
+import Text.Pandoc.UTF8 (fromText)
+
+-- | Convert Pandoc to Djot.
+writeDjot :: PandocMonad m => WriterOptions -> Pandoc -> m Text
+writeDjot opts (Pandoc meta blocks) = do
+ let colwidth = if writerWrapText opts == WrapAuto
+ then Just $ writerColumns opts
+ else Nothing
+ let ropts = RenderOptions{ preserveSoftBreaks =
+ writerWrapText opts == WrapPreserve }
+ metadata <- metaToContext opts
+ (fmap (renderDjot ropts) . bodyToDjot opts)
+ (fmap (chomp . renderDjot ropts) . bodyToDjot opts .
+ (:[]) . Plain)
+ meta
+ main <- renderDjot ropts <$>
+ bodyToDjot opts (makeSections False Nothing blocks)
+ let context = defField "body" main metadata
+ return $ render colwidth $
+ case writerTemplate opts of
+ Nothing -> main
+ Just tpl -> renderTemplate tpl context
+
+data DjotState =
+ DjotState
+ { footnotes :: D.NoteMap
+ , references :: D.ReferenceMap
+ , autoReferences :: D.ReferenceMap
+ , autoIds :: Set B.ByteString
+ , options :: WriterOptions }
+
+bodyToDjot :: PandocMonad m => WriterOptions -> [Block] -> m D.Doc
+bodyToDjot opts bls = do
+ (bs, st) <- runStateT (blocksToDjot bls)
+ (DjotState mempty mempty mempty mempty opts)
+ let D.ReferenceMap autos = autoReferences st
+ let D.ReferenceMap refs = references st
+ pure $ D.Doc{ D.docBlocks = bs
+ , D.docFootnotes = footnotes st
+ , D.docReferences = D.ReferenceMap $ M.difference refs autos
+ , D.docAutoReferences = D.ReferenceMap autos
+ , D.docAutoIdentifiers = autoIds st
+ }
+
+blocksToDjot :: PandocMonad m => [Block] -> StateT DjotState m D.Blocks
+blocksToDjot = fmap mconcat . mapM blockToDjot
+
+blockToDjot :: PandocMonad m => Block -> StateT DjotState m D.Blocks
+blockToDjot (Para ils) = D.para <$> inlinesToDjot ils
+blockToDjot (Plain ils) = D.para <$> inlinesToDjot ils
+blockToDjot (LineBlock ls) =
+ D.para . mconcat . intersperse D.hardBreak <$> mapM inlinesToDjot ls
+blockToDjot (CodeBlock attr@(_,_,kvs) t) = do
+ let lang = fromMaybe mempty $ lookup "lang" kvs
+ pure $ D.addAttr (toDjotAttr attr)
+ <$> D.codeBlock (fromText lang) (fromText t)
+blockToDjot (RawBlock (Format f) t) =
+ pure $ D.rawBlock (D.Format (fromText f)) (fromText t)
+blockToDjot (BlockQuote bls) = D.blockQuote <$> blocksToDjot bls
+blockToDjot (Header lev attr ils) =
+ fmap (D.addAttr (toDjotAttr attr)) . D.heading lev <$> inlinesToDjot ils
+blockToDjot HorizontalRule = pure D.thematicBreak
+blockToDjot (Div (ident,"section":cls,kvs) bls@(Header _ _ ils : _)) = do
+ ilsBs <- D.inlinesToByteString <$> inlinesToDjot ils
+ let ident' = toIdentifier ilsBs
+ let label = D.normalizeLabel ilsBs
+ let autoid = UTF8.toText ident' == ident
+ when autoid $
+ modify $ \st -> st{ autoIds = Set.insert ident' (autoIds st) }
+ modify $ \st -> st{ autoReferences = D.insertReference label
+ (B8.cons '#' ident', mempty) (autoReferences st) }
+ fmap
+ (D.addAttr (toDjotAttr (if autoid then "" else ident,
+ filter (/= "section") cls,
+ filter (\(k,_) -> k /= "wrapper") kvs))) . D.section
+ <$> blocksToDjot bls
+blockToDjot (Div attr@(ident,cls,kvs) bls)
+ | Just "1" <- lookup "wrapper" kvs
+ = fmap (D.addAttr
+ (toDjotAttr (ident,cls,filter (\(k,_) -> k /= "wrapper") kvs)))
+ <$> blocksToDjot bls
+ | otherwise
+ = fmap (D.addAttr (toDjotAttr attr)) . D.div <$> blocksToDjot bls
+blockToDjot (BulletList items) =
+ D.bulletList spacing <$> mapM blocksToDjot items
+ where
+ spacing = if isTightList items then D.Tight else D.Loose
+blockToDjot (OrderedList (start, sty, delim) items) =
+ D.orderedList listAttr spacing <$> mapM blocksToDjot items
+ where
+ spacing = if isTightList items then D.Tight else D.Loose
+ listAttr = D.OrderedListAttributes {
+ D.orderedListStyle =
+ case sty of
+ DefaultStyle -> D.Decimal
+ Example -> D.Decimal
+ Decimal -> D.Decimal
+ LowerRoman -> D.RomanLower
+ UpperRoman -> D.RomanUpper
+ LowerAlpha -> D.LetterLower
+ UpperAlpha -> D.LetterUpper,
+ D.orderedListDelim =
+ case delim of
+ DefaultDelim -> D.RightPeriod
+ Period -> D.RightPeriod
+ OneParen -> D.RightParen
+ TwoParens -> D.LeftRightParen,
+ D.orderedListStart = start }
+blockToDjot (DefinitionList items) =
+ D.definitionList spacing <$> mapM toDLItem items
+ where
+ spacing = if isTightList (map (concat . snd) items)
+ then D.Tight
+ else D.Loose
+ toDLItem (term, defs) = do
+ term' <- inlinesToDjot term
+ def' <- mconcat <$> mapM blocksToDjot defs
+ pure (term', def')
+blockToDjot (Figure attr (Caption _ capt) bls) = do
+ content <- blocksToDjot bls
+ caption <- fmap (D.addAttr (D.Attr [("class","caption")])) . D.div <$>
+ blocksToDjot capt
+ pure $ fmap (D.addAttr (toDjotAttr attr)) $ D.div $ content <> caption
+blockToDjot (Table attr capt' colspecs thead tbodies tfoot) = do
+ let (capt, aligns, _, headRow, bodyRows) =
+ toLegacyTable capt' colspecs thead tbodies tfoot
+ if onlySimpleTableCells (headRow : bodyRows)
+ then do
+ let alignToAlign al = case al of
+ AlignDefault -> D.AlignDefault
+ AlignLeft -> D.AlignLeft
+ AlignRight -> D.AlignRight
+ AlignCenter -> D.AlignCenter
+ let defAligns = map alignToAlign aligns
+ let cellToCell isHeader bls al =
+ D.Cell (if isHeader then D.HeadCell else D.BodyCell) al
+ <$> case bls of
+ [Para ils] -> inlinesToDjot ils
+ [Plain ils] -> inlinesToDjot ils
+ [] -> pure mempty
+ bs -> do
+ mapM_ (report . BlockNotRendered) bs
+ pure $ D.str "((omitted))"
+ let rowToRow isHeader cells = zipWithM (cellToCell isHeader) cells defAligns
+ hrows <- if null headRow
+ then pure []
+ else (:[]) <$> rowToRow True headRow
+ rows <- mapM (rowToRow False) bodyRows
+ caption <- case capt of
+ [] -> pure Nothing
+ _ -> Just . D.Caption . D.para <$> inlinesToDjot capt
+ pure $ D.addAttr (toDjotAttr attr) <$> D.table caption (hrows <> rows)
+ else do -- table can't be represented as a simple pipe table, use list
+ tableList <- D.bulletList D.Loose <$> mapM
+ (fmap (D.bulletList D.Loose) . mapM blocksToDjot)
+ (headRow:bodyRows)
+ pure $ D.addAttr (D.Attr [("class", "table")]) <$> tableList
+
+inlinesToDjot :: PandocMonad m => [Inline] -> StateT DjotState m D.Inlines
+inlinesToDjot = fmap mconcat . mapM inlineToDjot
+
+inlineToDjot :: PandocMonad m => Inline -> StateT DjotState m D.Inlines
+inlineToDjot (Str t) = pure $ D.str (fromText t)
+inlineToDjot Space = pure $ D.str " "
+inlineToDjot SoftBreak = pure D.softBreak
+inlineToDjot LineBreak = pure D.hardBreak
+inlineToDjot (Emph ils) = D.emph <$> inlinesToDjot ils
+inlineToDjot (Underline ils) =
+ fmap (D.addAttr (D.Attr [("class","underline")])) . D.span_
+ <$> inlinesToDjot ils
+inlineToDjot (Strong ils) = D.strong <$> inlinesToDjot ils
+inlineToDjot (Strikeout ils) = D.delete <$> inlinesToDjot ils
+inlineToDjot (Subscript ils) = D.subscript <$> inlinesToDjot ils
+inlineToDjot (Superscript ils) = D.superscript <$> inlinesToDjot ils
+inlineToDjot (Span attr@(ident,cls,kvs) ils)
+ | Just "1" <- lookup "wrapper" kvs
+ = fmap (D.addAttr
+ (toDjotAttr (ident,cls,filter (\(k,_) -> k /= "wrapper") kvs)))
+ <$> inlinesToDjot ils
+ | otherwise
+ = fmap (D.addAttr (toDjotAttr attr)) . D.span_ <$> inlinesToDjot ils
+inlineToDjot (SmallCaps ils) =
+ fmap (D.addAttr (D.Attr [("class","smallcaps")])) . D.span_
+ <$> inlinesToDjot ils
+inlineToDjot (Quoted DoubleQuote ils) = D.doubleQuoted <$> inlinesToDjot ils
+inlineToDjot (Quoted SingleQuote ils) = D.singleQuoted <$> inlinesToDjot ils
+inlineToDjot (Cite _cs ils) = inlinesToDjot ils
+inlineToDjot (Code attr t) =
+ pure $ D.addAttr (toDjotAttr attr) <$> D.verbatim (fromText t)
+inlineToDjot (Math mt t) =
+ pure $ (if mt == InlineMath
+ then D.inlineMath
+ else D.displayMath) (fromText t)
+inlineToDjot (RawInline (Format f) t) =
+ pure $ D.rawInline (D.Format (fromText f)) (fromText t)
+inlineToDjot (Link attr ils (src,tit)) = do
+ opts <- gets options
+ description <- inlinesToDjot ils
+ let ilstring = stringify ils
+ let autolink = ilstring == src
+ let email = ("mailto:" <> ilstring) == src
+ let removeClass name (ident, cls, kvs) = (ident, filter (/= name) cls, kvs)
+ let attr' = D.Attr [("title", fromText tit) | not (T.null tit)] <>
+ toDjotAttr ( (if autolink
+ then removeClass "uri"
+ else id) .
+ (if email
+ then removeClass "email"
+ else id) $ attr)
+ case () of
+ _ | autolink -> pure $ D.addAttr attr' <$> D.urlLink (fromText ilstring)
+ | email -> pure $ D.addAttr attr' <$> D.emailLink (fromText ilstring)
+ | writerReferenceLinks opts
+ -> do refs@(D.ReferenceMap m) <- gets references
+ autoRefs <- gets autoReferences
+ let lab' = D.inlinesToByteString description
+ lab <- case D.lookupReference lab' (refs <> autoRefs) of
+ Just _ -> pure lab'
+ Nothing -> do
+ let refnum = M.size m + 1
+ let lab = fromText $ tshow refnum
+ modify $ \st -> st{ references =
+ D.insertReference lab
+ (fromText src, attr') refs }
+ pure lab
+ pure $ D.addAttr attr' <$> D.link description (D.Reference lab)
+ | otherwise
+ -> pure $ D.addAttr attr' <$> D.link description (D.Direct (fromText src))
+inlineToDjot (Image attr ils (src,tit)) = do
+ opts <- gets options
+ description <- inlinesToDjot ils
+ let attr' = D.Attr [("title", fromText tit) | not (T.null tit)] <>
+ toDjotAttr attr
+ if writerReferenceLinks opts
+ then do
+ refs@(D.ReferenceMap m) <- gets references
+ let refnum = M.size m + 1
+ let lab = fromText $ tshow refnum
+ modify $ \st -> st{ references =
+ D.insertReference lab
+ (fromText src, attr') refs }
+ pure $ D.addAttr attr' <$> D.image description (D.Reference lab)
+ else pure $ D.addAttr attr' <$> D.image description (D.Direct (fromText src))
+inlineToDjot (Note bs) = do
+ notes@(D.NoteMap m) <- gets footnotes
+ let notenum = M.size m + 1
+ let lab = fromText $ tshow notenum
+ contents <- blocksToDjot bs
+ modify $ \st -> st{ footnotes = D.insertNote lab contents notes }
+ pure $ D.footnoteReference lab
+
+toDjotAttr :: (Text, [Text], [(Text, Text)]) -> D.Attr
+toDjotAttr (ident, classes, kvs) =
+ D.Attr $ [("id", fromText ident) | not (T.null ident)] ++
+ [("class", fromText (T.unwords classes)) | not (null classes)] ++
+ map (\(k,v) -> (fromText k, fromText v)) kvs
diff --git a/stack.yaml b/stack.yaml
index 202ecd191..b97e67327 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -32,6 +32,8 @@ extra-deps:
- git: https://github.com/jgm/commonmark-hs
subdirs: [commonmark-pandoc, commonmark-extensions]
commit: f0b96532e36f31f47cc34602ecac694ffde8a27a
+- git: https://github.com/jgm/djoths
+ commit: 3d53e40442d22726430b6a89bfb7fba92cd99a91
ghc-options:
"$locals": -fhide-source-paths -Wno-missing-home-modules
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 04855455a..97c1eb8a7 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -83,6 +83,11 @@ tests pandocPath =
, test' "reader" ["-r", "textile", "-w", "native", "-s"]
"textile-reader.textile" "textile-reader.native"
]
+ , testGroup "djot"
+ [ testGroup "writer" $ writerTests' "djot"
+ , test' "reader" ["-f", "djot", "-t" ,"native", "-s"]
+ "djot-reader.djot" "djot-reader.native"
+ ]
, testGroup "docbook"
[ testGroup "writer" $ writerTests' "docbook4"
, test' "reader" ["-r", "docbook", "-w", "native", "-s"]
diff --git a/test/djot-reader.djot b/test/djot-reader.djot
new file mode 100644
index 000000000..1faef6d4e
--- /dev/null
+++ b/test/djot-reader.djot
@@ -0,0 +1,749 @@
+# Pandoc Test Suite
+
+John MacFarlane
+Anonymous
+
+July 17, 2006
+
+This is a set of tests for pandoc. Most of them are adapted from John Gruber's
+markdown test suite.
+
+* * * *
+
+{#headers}
+# Headers
+
+{#level-2-with-an-embedded-link}
+## Level 2 with an [embedded link](/url)
+
+{#level-3-with-emphasis}
+### Level 3 with _emphasis_
+
+{#level-4}
+#### Level 4
+
+{#level-5}
+##### Level 5
+
+{#level-1}
+# Level 1
+
+{#level-2-with-emphasis}
+## Level 2 with _emphasis_
+
+{#level-3}
+### Level 3
+
+with no blank line
+
+{#level-2}
+## Level 2
+
+with no blank line
+
+* * * *
+
+{#paragraphs}
+# Paragraphs
+
+Here's a regular paragraph.
+
+In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item.
+Because a hard-wrapped line in the middle of a paragraph looked like a list
+item.
+
+Here's one with a bullet. \* criminey.
+
+There should be a hard line break\
+here.
+
+* * * *
+
+{#block-quotes}
+# Block Quotes
+
+E-mail style:
+
+> This is a block quote. It is pretty short.
+
+> Code in a block quote:
+>
+> ```
+> sub status {
+> print "working";
+> }
+> ```
+>
+> A list:
+>
+> 1. item one
+> 2. item two
+>
+> Nested block quotes:
+>
+> > nested
+>
+> > nested
+
+This should not be a block quote: 2 \> 1.
+
+And a following paragraph.
+
+* * * *
+
+{#code-blocks}
+# Code Blocks
+
+Code:
+
+```
+---- (should be four hyphens)
+
+sub status {
+ print "working";
+}
+
+this code block is indented by one tab
+```
+
+And:
+
+```
+ this code block is indented by two tabs
+
+These should not be escaped: \$ \\ \> \[ \{
+```
+
+* * * *
+
+{#lists}
+# Lists
+
+{#unordered}
+## Unordered
+
+Asterisks tight:
+
+- asterisk 1
+- asterisk 2
+- asterisk 3
+
+Asterisks loose:
+
+- asterisk 1
+
+- asterisk 2
+
+- asterisk 3
+
+Pluses tight:
+
+- Plus 1
+- Plus 2
+- Plus 3
+
+Pluses loose:
+
+- Plus 1
+
+- Plus 2
+
+- Plus 3
+
+Minuses tight:
+
+- Minus 1
+- Minus 2
+- Minus 3
+
+Minuses loose:
+
+- Minus 1
+
+- Minus 2
+
+- Minus 3
+
+{#ordered}
+## Ordered
+
+Tight:
+
+1. First
+2. Second
+3. Third
+
+and:
+
+1. One
+2. Two
+3. Three
+
+Loose using tabs:
+
+1. First
+
+2. Second
+
+3. Third
+
+and using spaces:
+
+1. One
+
+2. Two
+
+3. Three
+
+Multiple paragraphs:
+
+1. Item 1, graf one.
+
+ Item 1. graf two. The quick brown fox jumped over the lazy dog's back.
+
+2. Item 2.
+
+3. Item 3.
+
+{#nested}
+## Nested
+
+- Tab
+
+ - Tab
+
+ - Tab
+
+Here's another:
+
+1. First
+2. Second:
+
+ - Fee
+ - Fie
+ - Foe
+3. Third
+
+Same thing but with paragraphs:
+
+1. First
+
+2. Second:
+
+ - Fee
+ - Fie
+ - Foe
+
+3. Third
+
+{#tabs-and-spaces}
+## Tabs and spaces
+
+- this is a list item indented with tabs
+
+- this is a list item indented with spaces
+
+ - this is an example list item indented with tabs
+
+ - this is an example list item indented with spaces
+
+{#fancy-list-markers}
+## Fancy list markers
+
+(2) begins with 2
+
+(3) and now 3
+
+ with a continuation
+
+ iv. sublist with roman numerals, starting with 4
+ v. more items
+
+ (A) a subsublist
+ (B) a subsublist
+
+Nesting:
+
+A. Upper Alpha
+
+ I. Upper Roman.
+
+ (6) Decimal start with 6
+
+ c) Lower alpha with paren
+
+Autonumbering:
+
+1. Autonumber.
+2. More.
+
+ 1. Nested.
+
+Should not be a list item:
+
+M.A. 2007
+
+B. Williams
+
+* * * *
+
+{#definition-lists}
+# Definition Lists
+
+Tight using spaces:
+
+: apple
+
+ red fruit
+: orange
+
+ orange fruit
+: banana
+
+ yellow fruit
+
+Tight using tabs:
+
+: apple
+
+ red fruit
+: orange
+
+ orange fruit
+: banana
+
+ yellow fruit
+
+Loose:
+
+: apple
+
+ red fruit
+
+: orange
+
+ orange fruit
+
+: banana
+
+ yellow fruit
+
+Multiple blocks with italics:
+
+: _apple_
+
+ red fruit
+
+ contains seeds, crisp, pleasant to taste
+
+: _orange_
+
+ orange fruit
+
+ ```
+ { orange code block }
+ ```
+
+ > orange block quote
+
+Multiple definitions, tight:
+
+: apple
+
+ red fruit
+
+ computer
+: orange
+
+ orange fruit
+
+ bank
+
+Multiple definitions, loose:
+
+: apple
+
+ red fruit
+
+ computer
+
+: orange
+
+ orange fruit
+
+ bank
+
+Blank line after term, indented marker, alternate markers:
+
+: apple
+
+ red fruit
+
+ computer
+
+: orange
+
+ orange fruit
+
+ 1. sublist
+ 2. sublist
+
+{#html-blocks}
+# HTML Blocks
+
+Simple block on one line:
+
+:::
+foo
+
+:::
+
+And nested without indentation:
+
+::::::
+::::
+:::
+foo
+
+:::
+
+::::
+
+:::
+bar
+
+:::
+
+::::::
+
+Interpreted markdown in a table:
+
+This is _emphasized_
+
+And this is *strong*
+
+Here's a simple block:
+
+:::
+foo
+
+:::
+
+This should be a code block, though:
+
+```
+<div>
+ foo
+</div>
+```
+
+As should this:
+
+```
+<div>foo</div>
+```
+
+Now, nested:
+
+:::::
+::::
+:::
+foo
+
+:::
+
+::::
+
+:::::
+
+This should just be an HTML comment:
+
+Multiline:
+
+Code block:
+
+```
+<!-- Comment -->
+```
+
+Just plain comment, with trailing spaces on the line:
+
+Code:
+
+```
+<hr />
+```
+
+Hr's:
+
+* * * *
+
+{#inline-markup}
+# Inline Markup
+
+This is _emphasized_, and so _is this_.
+
+This is *strong*, and so *is this*.
+
+An _[emphasized link](/url)_.
+
+*_This is strong and em._*
+
+So is *_this_* word.
+
+*_This is strong and em._*
+
+So is *_this_* word.
+
+This is code: `>`, `$`, `\`, `\$`, `<html>`.
+
+{-This is _strikeout_.-}
+
+Superscripts: a^bc^d a^_hello_^ a^hello there^.
+
+Subscripts: H~2~O, H~23~O, H~many of them~O.
+
+These should not be superscripts or subscripts, because of the unescaped spaces:
+a\^b c\^d, a\~b c\~d.
+
+* * * *
+
+{#smart-quotes-ellipses-dashes}
+# Smart quotes, ellipses, dashes
+
+"Hello," said the spider. "'Shelob' is my name."
+
+'A', 'B', and 'C' are letters.
+
+'Oak,' 'elm,' and 'beech' are names of trees. So is 'pine.'
+
+'He said, "I want to go."' Were you alive in the 70's?
+
+Here is some quoted '`code`' and a "[quoted
+link](http://example.com/?foo=1&bar=2)".
+
+Some dashes: one---two --- three---four --- five.
+
+Dashes between numbers: 5--7, 255--66, 1987--1999.
+
+Ellipses...and...and....
+
+* * * *
+
+{#latex}
+# LaTeX
+
+-
+- $`2+2=4`
+- $`x \in y`
+- $`\alpha \wedge \omega`
+- $`223`
+- $`p`-Tree
+- Here's some display math:
+ $$`\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}`
+- Here's one that has a line break in it: $`\alpha + \omega \times x^2`.
+
+These shouldn't be math:
+
+- To get the famous equation, write `$e = mc^2$`.
+- $22,000 is a _lot_ of money. So is $34,000. (It worked if "lot" is
+ emphasized.)
+- Shoes ($20) and socks ($5).
+- Escaped `$`\: $73 _this should be emphasized_ 23$.
+
+Here's a LaTeX table:
+
+* * * *
+
+{#special-characters}
+# Special Characters
+
+Here is some unicode:
+
+- I hat: Î
+- o umlaut: ö
+- section: §
+- set membership: ∈
+- copyright: ©
+
+AT&T has an ampersand in their name.
+
+AT&T is another way to write it.
+
+This & that.
+
+4 \< 5.
+
+6 \> 5.
+
+Backslash: \\
+
+Backtick: \`
+
+Asterisk: \*
+
+Underscore: \_
+
+Left brace: \{
+
+Right brace: \}
+
+Left bracket: \[
+
+Right bracket: \]
+
+Left paren: (
+
+Right paren: )
+
+Greater-than: \>
+
+Hash: #
+
+Period: .
+
+Bang: \!
+
+Plus: +
+
+Minus: -
+
+* * * *
+
+{#links}
+# Links
+
+{#explicit}
+## Explicit
+
+Just a [URL](/url/).
+
+[URL and title](/url/){title="title"}.
+
+[URL and title](/url/){title="title preceded by two spaces"}.
+
+[URL and title](/url/){title="title preceded by a tab"}.
+
+[URL and title](/url/){title="title with \"quotes\" in it"}
+
+[URL and title](/url/){title="title with single quotes"}
+
+[with\_underscore](/url/with_underscore)
+
+[Email link](mailto:[email protected])
+
+[Empty]().
+
+{#reference}
+## Reference
+
+Foo [bar](/url/).
+
+With [embedded \[brackets\]](/url/).
+
+[b](/url/) by itself should be a link.
+
+Indented [once](/url).
+
+Indented [twice](/url).
+
+Indented [thrice](/url).
+
+This should \[not\]\[\] be a link.
+
+```
+[not]: /url
+```
+
+Foo [bar](/url/){title="Title with \"quotes\" inside"}.
+
+Foo [biz](/url/){title="Title with \"quote\" inside"}.
+
+{#with-ampersands}
+## With ampersands
+
+Here's a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2).
+
+Here's a link with an amersand in the link text:
+[AT&T](http://att.com/){title="AT&T"}.
+
+Here's an [inline link](/script?foo=1&bar=2).
+
+Here's an [inline link in pointy braces](/script?foo=1&bar=2).
+
+{#autolinks}
+## Autolinks
+
+With an ampersand: <http://example.com/?foo=1&bar=2>
+
+- In a list?
+- <http://example.com/>
+- It should.
+
+An e-mail address: <[email protected]>
+
+> Blockquoted: <http://example.com/>
+
+Auto-links should not occur here: `<http://example.com/>`
+
+```
+or here: <http://example.com/>
+```
+
+* * * *
+
+{#images}
+# Images
+
+From "Voyage dans la Lune" by Georges Melies (1902):
+
+::::
+![lalune](lalune.jpg){title="Voyage dans la Lune"}
+
+{.caption}
+:::
+lalune
+
+:::
+
+::::
+
+Here is a movie ![movie](movie.jpg) icon.
+
+* * * *
+
+{#footnotes}
+# Footnotes
+
+Here is a footnote reference,[^1] and another.[^2] This should _not_ be a
+footnote reference, because it contains a space.\[\^my note\] Here is an inline
+note.[^3]
+
+> Notes can go in quotes.[^4]
+
+1. And in list items.[^5]
+
+This paragraph should not be part of the note, as it is not indented.
+
+[^1]: Here is the footnote. It can go anywhere after the footnote reference. It
+ need not be placed at the end of the document.
+
+[^2]: Here's the long note. This one contains multiple blocks.
+
+ Subsequent blocks are indented to show that they belong to the footnote (as
+ with list items).
+
+ ```
+ { <code> }
+ ```
+
+ If you want, you can indent every line, but you can also be lazy and just
+ indent the first line of each block.
+
+[^3]: This is _easier_ to type. Inline notes may contain
+ [links](http://google.com) and `]` verbatim characters, as well as
+ \[bracketed text\].
+
+[^4]: In quote.
+
+[^5]: In list.
diff --git a/test/djot-reader.native b/test/djot-reader.native
new file mode 100644
index 000000000..528c34e04
--- /dev/null
+++ b/test/djot-reader.native
@@ -0,0 +1,986 @@
+Pandoc
+ Meta { unMeta = fromList [] }
+ [ Div
+ ( "Pandoc-Test-Suite"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header 1 ( "" , [] , [] ) [ Str "Pandoc Test Suite" ]
+ , Para
+ [ Str "John MacFarlane" , SoftBreak , Str "Anonymous" ]
+ , Para [ Str "July 17, 2006" ]
+ , Para
+ [ Str
+ "This is a set of tests for pandoc. Most of them are adapted from John Gruber\8217s"
+ , SoftBreak
+ , Str "markdown test suite."
+ ]
+ , HorizontalRule
+ ]
+ , Div
+ ( "headers" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "Headers" ]
+ , Div
+ ( "level-2-with-an-embedded-link"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header
+ 2
+ ( "" , [] , [] )
+ [ Str "Level 2 with an "
+ , Link
+ ( "" , [] , [] )
+ [ Str "embedded link" ]
+ ( "/url" , "" )
+ ]
+ , Div
+ ( "level-3-with-emphasis"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header
+ 3
+ ( "" , [] , [] )
+ [ Str "Level 3 with " , Emph [ Str "emphasis" ] ]
+ , Div
+ ( "level-4"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header 4 ( "" , [] , [] ) [ Str "Level 4" ]
+ , Div
+ ( "level-5"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header 5 ( "" , [] , [] ) [ Str "Level 5" ] ]
+ ]
+ ]
+ ]
+ ]
+ , Div
+ ( "level-1" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "Level 1" ]
+ , Div
+ ( "level-2-with-emphasis"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header
+ 2
+ ( "" , [] , [] )
+ [ Str "Level 2 with " , Emph [ Str "emphasis" ] ]
+ , Div
+ ( "level-3" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 3 ( "" , [] , [] ) [ Str "Level 3" ]
+ , Para [ Str "with no blank line" ]
+ ]
+ ]
+ , Div
+ ( "level-2" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 2 ( "" , [] , [] ) [ Str "Level 2" ]
+ , Para [ Str "with no blank line" ]
+ , HorizontalRule
+ ]
+ ]
+ , Div
+ ( "paragraphs" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "Paragraphs" ]
+ , Para [ Str "Here\8217s a regular paragraph." ]
+ , Para
+ [ Str
+ "In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item."
+ , SoftBreak
+ , Str
+ "Because a hard-wrapped line in the middle of a paragraph looked like a list"
+ , SoftBreak
+ , Str "item."
+ ]
+ , Para [ Str "Here\8217s one with a bullet. * criminey." ]
+ , Para
+ [ Str "There should be a hard line break"
+ , LineBreak
+ , Str "here."
+ ]
+ , HorizontalRule
+ ]
+ , Div
+ ( "block-quotes" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "Block Quotes" ]
+ , Para [ Str "E-mail style:" ]
+ , BlockQuote
+ [ Para [ Str "This is a block quote. It is pretty short." ]
+ ]
+ , BlockQuote
+ [ Para [ Str "Code in a block quote:" ]
+ , CodeBlock
+ ( "" , [ "" ] , [] )
+ "sub status {\nprint \"working\";\n}\n"
+ , Para [ Str "A list:" ]
+ , OrderedList
+ ( 1 , Decimal , Period )
+ [ [ Plain [ Str "item one" ] ]
+ , [ Plain [ Str "item two" ] ]
+ ]
+ , BlockQuote [ Para [ Str "nested" ] ]
+ , BlockQuote [ Para [ Str "nested" ] ]
+ ]
+ , Para [ Str "This should not be a block quote: 2 > 1." ]
+ , Para [ Str "And a following paragraph." ]
+ , HorizontalRule
+ ]
+ , Div
+ ( "code-blocks" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "Code Blocks" ]
+ , Para [ Str "Code:" ]
+ , CodeBlock
+ ( "" , [ "" ] , [] )
+ "---- (should be four hyphens)\n\nsub status {\n print \"working\";\n}\n\nthis code block is indented by one tab\n"
+ , Para [ Str "And:" ]
+ , CodeBlock
+ ( "" , [ "" ] , [] )
+ " this code block is indented by two tabs\n\nThese should not be escaped: \\$ \\\\ \\> \\[ \\{\n"
+ , HorizontalRule
+ ]
+ , Div
+ ( "lists" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "Lists" ]
+ , Div
+ ( "unordered" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 2 ( "" , [] , [] ) [ Str "Unordered" ]
+ , Para [ Str "Asterisks tight:" ]
+ , BulletList
+ [ [ Para [ Str "asterisk 1" ] ]
+ , [ Para [ Str "asterisk 2" ] ]
+ , [ Para [ Str "asterisk 3" ] ]
+ , [ Para [ Str "asterisk 1" ] ]
+ , [ Para [ Str "asterisk 2" ] ]
+ , [ Para [ Str "asterisk 3" ] ]
+ , [ Para [ Str "Plus 1" ] ]
+ , [ Para [ Str "Plus 2" ] ]
+ , [ Para [ Str "Plus 3" ] ]
+ , [ Para [ Str "Plus 1" ] ]
+ , [ Para [ Str "Plus 2" ] ]
+ , [ Para [ Str "Plus 3" ] ]
+ , [ Para [ Str "Minus 1" ] ]
+ , [ Para [ Str "Minus 2" ] ]
+ , [ Para [ Str "Minus 3" ] ]
+ , [ Para [ Str "Minus 1" ] ]
+ , [ Para [ Str "Minus 2" ] ]
+ , [ Para [ Str "Minus 3" ] ]
+ ]
+ ]
+ , Div
+ ( "ordered" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 2 ( "" , [] , [] ) [ Str "Ordered" ]
+ , Para [ Str "Tight:" ]
+ , OrderedList
+ ( 1 , Decimal , Period )
+ [ [ Para [ Str "First" ] ]
+ , [ Para [ Str "Second" ] ]
+ , [ Para [ Str "Third" ] ]
+ , [ Para [ Str "One" ] ]
+ , [ Para [ Str "Two" ] ]
+ , [ Para [ Str "Three" ] ]
+ , [ Para [ Str "First" ] ]
+ , [ Para [ Str "Second" ] ]
+ , [ Para [ Str "Third" ] ]
+ , [ Para [ Str "One" ] ]
+ , [ Para [ Str "Two" ] ]
+ , [ Para [ Str "Three" ] ]
+ , [ Para [ Str "Item 1, graf one." ]
+ , Para
+ [ Str
+ "Item 1. graf two. The quick brown fox jumped over the lazy dog\8217s back."
+ ]
+ ]
+ , [ Para [ Str "Item 2." ] ]
+ , [ Para [ Str "Item 3." ] ]
+ ]
+ ]
+ , Div
+ ( "nested" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 2 ( "" , [] , [] ) [ Str "Nested" ]
+ , BulletList
+ [ [ Plain [ Str "Tab" ]
+ , BulletList
+ [ [ Plain [ Str "Tab" ]
+ , BulletList [ [ Plain [ Str "Tab" ] ] ]
+ ]
+ ]
+ ]
+ ]
+ , OrderedList
+ ( 1 , Decimal , Period )
+ [ [ Para [ Str "First" ] ]
+ , [ Para [ Str "Second:" ]
+ , BulletList
+ [ [ Plain [ Str "Fee" ] ]
+ , [ Plain [ Str "Fie" ] ]
+ , [ Plain [ Str "Foe" ] ]
+ ]
+ ]
+ , [ Para [ Str "Third" ] ]
+ , [ Para [ Str "First" ] ]
+ , [ Para [ Str "Second:" ]
+ , BulletList
+ [ [ Plain [ Str "Fee" ] ]
+ , [ Plain [ Str "Fie" ] ]
+ , [ Plain [ Str "Foe" ] ]
+ ]
+ ]
+ , [ Para [ Str "Third" ] ]
+ ]
+ ]
+ , Div
+ ( "tabs-and-spaces"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header 2 ( "" , [] , [] ) [ Str "Tabs and spaces" ]
+ , BulletList
+ [ [ Para [ Str "this is a list item indented with tabs" ]
+ ]
+ , [ Para
+ [ Str "this is a list item indented with spaces" ]
+ , BulletList
+ [ [ Para
+ [ Str
+ "this is an example list item indented with tabs"
+ ]
+ ]
+ , [ Para
+ [ Str
+ "this is an example list item indented with spaces"
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ , Div
+ ( "fancy-list-markers"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header 2 ( "" , [] , [] ) [ Str "Fancy list markers" ]
+ , OrderedList
+ ( 2 , Decimal , TwoParens )
+ [ [ Para [ Str "begins with 2" ] ]
+ , [ Para [ Str "and now 3" ]
+ , Para [ Str "with a continuation" ]
+ , OrderedList
+ ( 4 , LowerRoman , Period )
+ [ [ Plain
+ [ Str
+ "sublist with roman numerals, starting with 4"
+ ]
+ ]
+ , [ Plain [ Str "more items" ]
+ , OrderedList
+ ( 1 , UpperAlpha , TwoParens )
+ [ [ Plain [ Str "a subsublist" ] ]
+ , [ Plain [ Str "a subsublist" ] ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ , OrderedList
+ ( 1 , UpperAlpha , Period )
+ [ [ Plain [ Str "Upper Alpha" ]
+ , OrderedList
+ ( 1 , UpperRoman , Period )
+ [ [ Plain [ Str "Upper Roman." ]
+ , OrderedList
+ ( 6 , Decimal , TwoParens )
+ [ [ Plain [ Str "Decimal start with 6" ]
+ , OrderedList
+ ( 3 , LowerAlpha , OneParen )
+ [ [ Plain
+ [ Str "Lower alpha with paren" ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ , OrderedList
+ ( 1 , Decimal , Period )
+ [ [ Plain [ Str "Autonumber." ] ]
+ , [ Plain [ Str "More." ]
+ , OrderedList
+ ( 1 , Decimal , Period )
+ [ [ Plain [ Str "Nested." ] ] ]
+ ]
+ ]
+ , OrderedList
+ ( 2 , UpperAlpha , Period )
+ [ [ Plain [ Str "Williams" ] ] ]
+ , HorizontalRule
+ ]
+ ]
+ , Div
+ ( "definition-lists"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header 1 ( "" , [] , [] ) [ Str "Definition Lists" ]
+ , Para [ Str "Tight using spaces:" ]
+ , DefinitionList
+ [ ( [ Str "apple" ] , [ [ Para [ Str "red fruit" ] ] ] )
+ , ( [ Str "orange" ] , [ [ Para [ Str "orange fruit" ] ] ] )
+ , ( [ Str "banana" ] , [ [ Para [ Str "yellow fruit" ] ] ] )
+ , ( [ Str "apple" ] , [ [ Para [ Str "red fruit" ] ] ] )
+ , ( [ Str "orange" ] , [ [ Para [ Str "orange fruit" ] ] ] )
+ , ( [ Str "banana" ] , [ [ Para [ Str "yellow fruit" ] ] ] )
+ , ( [ Str "apple" ] , [ [ Para [ Str "red fruit" ] ] ] )
+ , ( [ Str "orange" ] , [ [ Para [ Str "orange fruit" ] ] ] )
+ , ( [ Str "banana" ] , [ [ Para [ Str "yellow fruit" ] ] ] )
+ , ( [ Emph [ Str "apple" ] ]
+ , [ [ Para [ Str "red fruit" ]
+ , Para
+ [ Str "contains seeds, crisp, pleasant to taste" ]
+ ]
+ ]
+ )
+ , ( [ Emph [ Str "orange" ] ]
+ , [ [ Para [ Str "orange fruit" ]
+ , CodeBlock
+ ( "" , [ "" ] , [] ) "{ orange code block }\n"
+ ]
+ ]
+ )
+ ]
+ , BlockQuote [ Para [ Str "orange block quote" ] ]
+ , Para [ Str "Multiple definitions, tight:" ]
+ , DefinitionList
+ [ ( [ Str "apple" ]
+ , [ [ Para [ Str "red fruit" ] , Para [ Str "computer" ] ] ]
+ )
+ , ( [ Str "orange" ]
+ , [ [ Para [ Str "orange fruit" ] , Para [ Str "bank" ] ] ]
+ )
+ , ( [ Str "apple" ]
+ , [ [ Para [ Str "red fruit" ] , Para [ Str "computer" ] ] ]
+ )
+ , ( [ Str "orange" ]
+ , [ [ Para [ Str "orange fruit" ] , Para [ Str "bank" ] ] ]
+ )
+ , ( [ Str "apple" ]
+ , [ [ Para [ Str "red fruit" ] , Para [ Str "computer" ] ] ]
+ )
+ , ( [ Str "orange" ]
+ , [ [ Para [ Str "orange fruit" ]
+ , OrderedList
+ ( 1 , Decimal , Period )
+ [ [ Plain [ Str "sublist" ] ]
+ , [ Plain [ Str "sublist" ] ]
+ ]
+ ]
+ ]
+ )
+ ]
+ ]
+ , Div
+ ( "html-blocks" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "HTML Blocks" ]
+ , Para [ Str "Simple block on one line:" ]
+ , Div ( "" , [] , [] ) [ Para [ Str "foo" ] ]
+ , Para [ Str "And nested without indentation:" ]
+ , Div
+ ( "" , [] , [] )
+ [ Div
+ ( "" , [] , [] )
+ [ Div ( "" , [] , [] ) [ Para [ Str "foo" ] ] ]
+ , Div ( "" , [] , [] ) [ Para [ Str "bar" ] ]
+ ]
+ , Para [ Str "Interpreted markdown in a table:" ]
+ , Para [ Str "This is " , Emph [ Str "emphasized" ] ]
+ , Para [ Str "And this is " , Strong [ Str "strong" ] ]
+ , Para [ Str "Here\8217s a simple block:" ]
+ , Div ( "" , [] , [] ) [ Para [ Str "foo" ] ]
+ , Para [ Str "This should be a code block, though:" ]
+ , CodeBlock ( "" , [ "" ] , [] ) "<div>\n foo\n</div>\n"
+ , Para [ Str "As should this:" ]
+ , CodeBlock ( "" , [ "" ] , [] ) "<div>foo</div>\n"
+ , Para [ Str "Now, nested:" ]
+ , Div
+ ( "" , [] , [] )
+ [ Div
+ ( "" , [] , [] )
+ [ Div ( "" , [] , [] ) [ Para [ Str "foo" ] ] ]
+ ]
+ , Para [ Str "This should just be an HTML comment:" ]
+ , Para [ Str "Multiline:" ]
+ , Para [ Str "Code block:" ]
+ , CodeBlock ( "" , [ "" ] , [] ) "<!-- Comment -->\n"
+ , Para
+ [ Str
+ "Just plain comment, with trailing spaces on the line:"
+ ]
+ , Para [ Str "Code:" ]
+ , CodeBlock ( "" , [ "" ] , [] ) "<hr />\n"
+ , Para [ Str "Hr\8217s:" ]
+ , HorizontalRule
+ ]
+ , Div
+ ( "inline-markup"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header 1 ( "" , [] , [] ) [ Str "Inline Markup" ]
+ , Para
+ [ Str "This is "
+ , Emph [ Str "emphasized" ]
+ , Str ", and so "
+ , Emph [ Str "is this" ]
+ , Str "."
+ ]
+ , Para
+ [ Str "This is "
+ , Strong [ Str "strong" ]
+ , Str ", and so "
+ , Strong [ Str "is this" ]
+ , Str "."
+ ]
+ , Para
+ [ Str "An "
+ , Emph
+ [ Link
+ ( "" , [] , [] )
+ [ Str "emphasized link" ]
+ ( "/url" , "" )
+ ]
+ , Str "."
+ ]
+ , Para [ Strong [ Emph [ Str "This is strong and em." ] ] ]
+ , Para
+ [ Str "So is "
+ , Strong [ Emph [ Str "this" ] ]
+ , Str " word."
+ ]
+ , Para [ Strong [ Emph [ Str "This is strong and em." ] ] ]
+ , Para
+ [ Str "So is "
+ , Strong [ Emph [ Str "this" ] ]
+ , Str " word."
+ ]
+ , Para
+ [ Str "This is code: "
+ , Code ( "" , [] , [] ) ">"
+ , Str ", "
+ , Code ( "" , [] , [] ) "$"
+ , Str ", "
+ , Code ( "" , [] , [] ) "\\`, "
+ , Str "$"
+ , Code ( "" , [] , [] ) ", "
+ , Str "<html>"
+ , Code ( "" , [] , [] ) "."
+ ]
+ , Para
+ [ Span
+ ( "" , [ "deleted" ] , [] )
+ [ Str "This is " , Emph [ Str "strikeout" ] , Str "." ]
+ ]
+ , Para
+ [ Str "Superscripts: a"
+ , Superscript [ Str "bc" ]
+ , Str "d a"
+ , Superscript [ Emph [ Str "hello" ] ]
+ , Str " a"
+ , Superscript [ Str "hello\160there" ]
+ , Str "."
+ ]
+ , Para
+ [ Str "Subscripts: H"
+ , Subscript [ Str "2" ]
+ , Str "O, H"
+ , Subscript [ Str "23" ]
+ , Str "O, H"
+ , Subscript [ Str "many\160of\160them" ]
+ , Str "O."
+ ]
+ , Para
+ [ Str
+ "These should not be superscripts or subscripts, because of the unescaped spaces:"
+ , SoftBreak
+ , Str "a^b c^d, a~b c~d."
+ ]
+ , HorizontalRule
+ ]
+ , Div
+ ( "smart-quotes-ellipses-dashes"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header
+ 1 ( "" , [] , [] ) [ Str "Smart quotes, ellipses, dashes" ]
+ , Para
+ [ Quoted DoubleQuote [ Str "Hello," ]
+ , Str " said the spider. "
+ , Quoted
+ DoubleQuote
+ [ Quoted SingleQuote [ Str "Shelob" ]
+ , Str " is my name."
+ ]
+ ]
+ , Para
+ [ Quoted SingleQuote [ Str "A" ]
+ , Str ", "
+ , Quoted SingleQuote [ Str "B" ]
+ , Str ", and "
+ , Quoted SingleQuote [ Str "C" ]
+ , Str " are letters."
+ ]
+ , Para
+ [ Quoted SingleQuote [ Str "Oak," ]
+ , Str " "
+ , Quoted SingleQuote [ Str "elm," ]
+ , Str " and "
+ , Quoted SingleQuote [ Str "beech" ]
+ , Str " are names of trees. So is "
+ , Quoted SingleQuote [ Str "pine." ]
+ ]
+ , Para
+ [ Quoted
+ SingleQuote
+ [ Str "He said, "
+ , Quoted DoubleQuote [ Str "I want to go." ]
+ ]
+ , Str " Were you alive in the 70\8217s?"
+ ]
+ , Para
+ [ Str "Here is some quoted "
+ , Quoted SingleQuote [ Code ( "" , [] , [] ) "code" ]
+ , Str " and a "
+ , Quoted
+ DoubleQuote
+ [ Link
+ ( "" , [] , [] )
+ [ Str "quoted" , SoftBreak , Str "link" ]
+ ( "http://example.com/?foo=1&bar=2" , "" )
+ ]
+ , Str "."
+ ]
+ , Para
+ [ Str
+ "Some dashes: one\8212two \8212 three\8212four \8212 five."
+ ]
+ , Para
+ [ Str
+ "Dashes between numbers: 5\8211\&7, 255\8211\&66, 1987\8211\&1999."
+ ]
+ , Para [ Str "Ellipses\8230and\8230and\8230." ]
+ , HorizontalRule
+ ]
+ , Div
+ ( "latex" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "LaTeX" ]
+ , BulletList
+ [ []
+ , [ Para [ Math InlineMath "2+2=4" ] ]
+ , [ Para [ Math InlineMath "x \\in y" ] ]
+ , [ Para [ Math InlineMath "\\alpha \\wedge \\omega" ] ]
+ , [ Para [ Math InlineMath "223" ] ]
+ , [ Para [ Math InlineMath "p" , Str "-Tree" ] ]
+ , [ Para
+ [ Str "Here\8217s some display math:"
+ , SoftBreak
+ , Math
+ DisplayMath
+ "\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)-f(x)}{h}"
+ ]
+ ]
+ , [ Para
+ [ Str "Here\8217s one that has a line break in it: "
+ , Math InlineMath "\\alpha + \\omega \\times x^2"
+ , Str "."
+ ]
+ ]
+ , [ Para
+ [ Str "To get the famous equation, write "
+ , Code ( "" , [] , [] ) "$e = mc^2$"
+ , Str "."
+ ]
+ ]
+ , [ Para
+ [ Str "$22,000 is a "
+ , Emph [ Str "lot" ]
+ , Str " of money. So is $34,000. (It worked if "
+ , Quoted DoubleQuote [ Str "lot" ]
+ , Str " is"
+ , SoftBreak
+ , Str "emphasized.)"
+ ]
+ ]
+ , [ Para [ Str "Shoes ($20) and socks ($5)." ] ]
+ , [ Para
+ [ Str "Escaped "
+ , Code ( "" , [] , [] ) "$"
+ , Str ": $73 "
+ , Emph [ Str "this should be emphasized" ]
+ , Str " 23$."
+ ]
+ ]
+ ]
+ , HorizontalRule
+ ]
+ , Div
+ ( "special-characters"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header 1 ( "" , [] , [] ) [ Str "Special Characters" ]
+ , Para [ Str "Here is some unicode:" ]
+ , BulletList
+ [ [ Plain [ Str "I hat: \206" ] ]
+ , [ Plain [ Str "o umlaut: \246" ] ]
+ , [ Plain [ Str "section: \167" ] ]
+ , [ Plain [ Str "set membership: \8712" ] ]
+ , [ Plain [ Str "copyright: \169" ] ]
+ ]
+ , HorizontalRule
+ ]
+ , Div
+ ( "links" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "Links" ]
+ , Div
+ ( "explicit" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 2 ( "" , [] , [] ) [ Str "Explicit" ]
+ , Para
+ [ Str "Just a "
+ , Link ( "" , [] , [] ) [ Str "URL" ] ( "/url/" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Link
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" ) , ( "title" , "title" ) ]
+ )
+ [ Str "URL and title" ]
+ ( "/url/" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Link
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" )
+ , ( "title" , "title preceded by two spaces" )
+ ]
+ )
+ [ Str "URL and title" ]
+ ( "/url/" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Link
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" )
+ , ( "title" , "title preceded by a tab" )
+ ]
+ )
+ [ Str "URL and title" ]
+ ( "/url/" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Link
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" )
+ , ( "title" , "title with \"quotes\" in it" )
+ ]
+ )
+ [ Str "URL and title" ]
+ ( "/url/" , "" )
+ ]
+ , Para
+ [ Link
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" )
+ , ( "title" , "title with single quotes" )
+ ]
+ )
+ [ Str "URL and title" ]
+ ( "/url/" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "with_underscore" ]
+ ( "/url/with_underscore" , "" )
+ ]
+ , Para
+ [ Link
+ ( "" , [] , [] )
+ [ Str "Email link" ]
+ ( "mailto:[email protected]" , "" )
+ ]
+ , Para
+ [ Link ( "" , [] , [] ) [ Str "Empty" ] ( "" , "" )
+ , Str "."
+ ]
+ ]
+ , Div
+ ( "reference" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 2 ( "" , [] , [] ) [ Str "Reference" ]
+ , Para
+ [ Str "Foo "
+ , Link ( "" , [] , [] ) [ Str "bar" ] ( "/url/" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Str "With "
+ , Link
+ ( "" , [] , [] )
+ [ Str "embedded [brackets]" ]
+ ( "/url/" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Link ( "" , [] , [] ) [ Str "b" ] ( "/url/" , "" )
+ , Str " by itself should be a link."
+ ]
+ , Para
+ [ Str "Indented "
+ , Link ( "" , [] , [] ) [ Str "once" ] ( "/url" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Str "Indented "
+ , Link ( "" , [] , [] ) [ Str "twice" ] ( "/url" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Str "Indented "
+ , Link ( "" , [] , [] ) [ Str "thrice" ] ( "/url" , "" )
+ , Str "."
+ ]
+ , Para [ Str "This should [not][] be a link." ]
+ , CodeBlock ( "" , [ "" ] , [] ) "[not]: /url\n"
+ , Para
+ [ Str "Foo "
+ , Link
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" )
+ , ( "title" , "Title with \"quotes\" inside" )
+ ]
+ )
+ [ Str "bar" ]
+ ( "/url/" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Str "Foo "
+ , Link
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" )
+ , ( "title" , "Title with \"quote\" inside" )
+ ]
+ )
+ [ Str "biz" ]
+ ( "/url/" , "" )
+ , Str "."
+ ]
+ ]
+ , Div
+ ( "with-ampersands"
+ , [ "section" ]
+ , [ ( "wrapper" , "1" ) ]
+ )
+ [ Header 2 ( "" , [] , [] ) [ Str "With ampersands" ]
+ , Para
+ [ Str "Here\8217s a "
+ , Link
+ ( "" , [] , [] )
+ [ Str "link with an ampersand in the URL" ]
+ ( "http://example.com/?foo=1&bar=2" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Str
+ "Here\8217s a link with an amersand in the link text:"
+ , SoftBreak
+ , Link
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" ) , ( "title" , "AT&T" ) ]
+ )
+ [ Str "AT&T" ]
+ ( "http://att.com/" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Str "Here\8217s an "
+ , Link
+ ( "" , [] , [] )
+ [ Str "inline link" ]
+ ( "/script?foo=1&bar=2" , "" )
+ , Str "."
+ ]
+ , Para
+ [ Str "Here\8217s an "
+ , Link
+ ( "" , [] , [] )
+ [ Str "inline link in pointy braces" ]
+ ( "/script?foo=1&bar=2" , "" )
+ , Str "."
+ ]
+ ]
+ , Div
+ ( "autolinks" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 2 ( "" , [] , [] ) [ Str "Autolinks" ]
+ , Para
+ [ Str "With an ampersand: "
+ , Link
+ ( "" , [ "uri" ] , [] )
+ [ Str "http://example.com/?foo=1&bar=2" ]
+ ( "http://example.com/?foo=1&bar=2" , "" )
+ ]
+ , BulletList
+ [ [ Plain [ Str "In a list?" ] ]
+ , [ Plain
+ [ Link
+ ( "" , [ "uri" ] , [] )
+ [ Str "http://example.com/" ]
+ ( "http://example.com/" , "" )
+ ]
+ ]
+ , [ Plain [ Str "It should." ] ]
+ ]
+ , BlockQuote
+ [ Para
+ [ Str "Blockquoted: "
+ , Link
+ ( "" , [ "uri" ] , [] )
+ [ Str "http://example.com/" ]
+ ( "http://example.com/" , "" )
+ ]
+ ]
+ , Para
+ [ Str "Auto-links should not occur here: "
+ , Code ( "" , [] , [] ) "<http://example.com/>"
+ ]
+ , CodeBlock
+ ( "" , [ "" ] , [] ) "or here: <http://example.com/>\n"
+ , HorizontalRule
+ ]
+ ]
+ , Div
+ ( "images" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "Images" ]
+ , Para
+ [ Str "From "
+ , Quoted DoubleQuote [ Str "Voyage dans la Lune" ]
+ , Str " by Georges Melies (1902):"
+ ]
+ , Div
+ ( "" , [] , [] )
+ [ Para
+ [ Image
+ ( ""
+ , []
+ , [ ( "wrapper" , "1" )
+ , ( "title" , "Voyage dans la Lune" )
+ ]
+ )
+ [ Str "lalune" ]
+ ( "lalune.jpg" , "" )
+ ]
+ , Div
+ ( "" , [ "caption" ] , [ ( "wrapper" , "1" ) ] )
+ [ Para [ Str "lalune" ] ]
+ ]
+ , Para
+ [ Str "Here is a movie "
+ , Image
+ ( "" , [] , [] ) [ Str "movie" ] ( "movie.jpg" , "" )
+ , Str " icon."
+ ]
+ , HorizontalRule
+ ]
+ , Div
+ ( "footnotes" , [ "section" ] , [ ( "wrapper" , "1" ) ] )
+ [ Header 1 ( "" , [] , [] ) [ Str "Footnotes" ]
+ , Para
+ [ Str "Here is a footnote reference,"
+ , Note
+ [ Para
+ [ Str
+ "Here is the footnote. It can go anywhere after the footnote reference. It"
+ , SoftBreak
+ , Str "need not be placed at the end of the document."
+ ]
+ ]
+ , Str " and another."
+ , Note
+ [ Para
+ [ Str
+ "Here\8217s the long note. This one contains multiple blocks."
+ ]
+ , Para
+ [ Str
+ "Subsequent blocks are indented to show that they belong to the footnote (as"
+ , SoftBreak
+ , Str "with list items)."
+ ]
+ , CodeBlock ( "" , [ "" ] , [] ) "{ <code> }\n"
+ , Para
+ [ Str
+ "If you want, you can indent every line, but you can also be lazy and just"
+ , SoftBreak
+ , Str "indent the first line of each block."
+ ]
+ ]
+ , Str " This should "
+ , Emph [ Str "not" ]
+ , Str " be a"
+ , SoftBreak
+ , Str
+ "footnote reference, because it contains a space.[^my note] Here is an inline"
+ , SoftBreak
+ , Str "note."
+ , Note
+ [ Para
+ [ Str "This is "
+ , Emph [ Str "easier" ]
+ , Str " to type. Inline notes may contain"
+ , SoftBreak
+ , Link
+ ( "" , [] , [] )
+ [ Str "links" ]
+ ( "http://google.com" , "" )
+ , Str " and "
+ , Code ( "" , [] , [] ) "]"
+ , Str " verbatim characters, as well as"
+ , SoftBreak
+ , Str "[bracketed text]."
+ ]
+ ]
+ ]
+ , BlockQuote
+ [ Para
+ [ Str "Notes can go in quotes."
+ , Note [ Para [ Str "In quote." ] ]
+ ]
+ ]
+ , OrderedList
+ ( 1 , Decimal , Period )
+ [ [ Plain
+ [ Str "And in list items."
+ , Note [ Para [ Str "In list." ] ]
+ ]
+ ]
+ ]
+ ]
+ ]
diff --git a/test/tables.djot b/test/tables.djot
new file mode 100644
index 000000000..94963f96e
--- /dev/null
+++ b/test/tables.djot
@@ -0,0 +1,54 @@
+Simple table with caption:
+
+| Right | Left | Center | Default |
+|------:|:-----|:------:|-------|
+| 12 | 12 | 12 | 12 |
+| 123 | 123 | 123 | 123 |
+| 1 | 1 | 1 | 1 |
+
+^ Demonstration of simple table syntax.
+
+Simple table without caption:
+
+| Right | Left | Center | Default |
+|------:|:-----|:------:|-------|
+| 12 | 12 | 12 | 12 |
+| 123 | 123 | 123 | 123 |
+| 1 | 1 | 1 | 1 |
+
+Simple table indented two spaces:
+
+| Right | Left | Center | Default |
+|------:|:-----|:------:|-------|
+| 12 | 12 | 12 | 12 |
+| 123 | 123 | 123 | 123 |
+| 1 | 1 | 1 | 1 |
+
+^ Demonstration of simple table syntax.
+
+Multiline table with caption:
+
+| Centered Header | Left Aligned | Right Aligned | Default aligned |
+|:---------------:|:-------------|--------------:|:------------------------------------------------------|
+| First | row | 12.0 | Example of a row that spans multiple lines. |
+| Second | row | 5.0 | Here's another one. Note the blank line between rows. |
+
+^ Here's the caption. It may span multiple lines.
+
+Multiline table without caption:
+
+| Centered Header | Left Aligned | Right Aligned | Default aligned |
+|:---------------:|:-------------|--------------:|:------------------------------------------------------|
+| First | row | 12.0 | Example of a row that spans multiple lines. |
+| Second | row | 5.0 | Here's another one. Note the blank line between rows. |
+
+Table without column headers:
+
+| 12 | 12 | 12 | 12 |
+| 123 | 123 | 123 | 123 |
+| 1 | 1 | 1 | 1 |
+
+Multiline table without column headers:
+
+| First | row | 12.0 | Example of a row that spans multiple lines. |
+| Second | row | 5.0 | Here's another one. Note the blank line between rows. |
diff --git a/test/writer.djot b/test/writer.djot
new file mode 100644
index 000000000..1faef6d4e
--- /dev/null
+++ b/test/writer.djot
@@ -0,0 +1,749 @@
+# Pandoc Test Suite
+
+John MacFarlane
+Anonymous
+
+July 17, 2006
+
+This is a set of tests for pandoc. Most of them are adapted from John Gruber's
+markdown test suite.
+
+* * * *
+
+{#headers}
+# Headers
+
+{#level-2-with-an-embedded-link}
+## Level 2 with an [embedded link](/url)
+
+{#level-3-with-emphasis}
+### Level 3 with _emphasis_
+
+{#level-4}
+#### Level 4
+
+{#level-5}
+##### Level 5
+
+{#level-1}
+# Level 1
+
+{#level-2-with-emphasis}
+## Level 2 with _emphasis_
+
+{#level-3}
+### Level 3
+
+with no blank line
+
+{#level-2}
+## Level 2
+
+with no blank line
+
+* * * *
+
+{#paragraphs}
+# Paragraphs
+
+Here's a regular paragraph.
+
+In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item.
+Because a hard-wrapped line in the middle of a paragraph looked like a list
+item.
+
+Here's one with a bullet. \* criminey.
+
+There should be a hard line break\
+here.
+
+* * * *
+
+{#block-quotes}
+# Block Quotes
+
+E-mail style:
+
+> This is a block quote. It is pretty short.
+
+> Code in a block quote:
+>
+> ```
+> sub status {
+> print "working";
+> }
+> ```
+>
+> A list:
+>
+> 1. item one
+> 2. item two
+>
+> Nested block quotes:
+>
+> > nested
+>
+> > nested
+
+This should not be a block quote: 2 \> 1.
+
+And a following paragraph.
+
+* * * *
+
+{#code-blocks}
+# Code Blocks
+
+Code:
+
+```
+---- (should be four hyphens)
+
+sub status {
+ print "working";
+}
+
+this code block is indented by one tab
+```
+
+And:
+
+```
+ this code block is indented by two tabs
+
+These should not be escaped: \$ \\ \> \[ \{
+```
+
+* * * *
+
+{#lists}
+# Lists
+
+{#unordered}
+## Unordered
+
+Asterisks tight:
+
+- asterisk 1
+- asterisk 2
+- asterisk 3
+
+Asterisks loose:
+
+- asterisk 1
+
+- asterisk 2
+
+- asterisk 3
+
+Pluses tight:
+
+- Plus 1
+- Plus 2
+- Plus 3
+
+Pluses loose:
+
+- Plus 1
+
+- Plus 2
+
+- Plus 3
+
+Minuses tight:
+
+- Minus 1
+- Minus 2
+- Minus 3
+
+Minuses loose:
+
+- Minus 1
+
+- Minus 2
+
+- Minus 3
+
+{#ordered}
+## Ordered
+
+Tight:
+
+1. First
+2. Second
+3. Third
+
+and:
+
+1. One
+2. Two
+3. Three
+
+Loose using tabs:
+
+1. First
+
+2. Second
+
+3. Third
+
+and using spaces:
+
+1. One
+
+2. Two
+
+3. Three
+
+Multiple paragraphs:
+
+1. Item 1, graf one.
+
+ Item 1. graf two. The quick brown fox jumped over the lazy dog's back.
+
+2. Item 2.
+
+3. Item 3.
+
+{#nested}
+## Nested
+
+- Tab
+
+ - Tab
+
+ - Tab
+
+Here's another:
+
+1. First
+2. Second:
+
+ - Fee
+ - Fie
+ - Foe
+3. Third
+
+Same thing but with paragraphs:
+
+1. First
+
+2. Second:
+
+ - Fee
+ - Fie
+ - Foe
+
+3. Third
+
+{#tabs-and-spaces}
+## Tabs and spaces
+
+- this is a list item indented with tabs
+
+- this is a list item indented with spaces
+
+ - this is an example list item indented with tabs
+
+ - this is an example list item indented with spaces
+
+{#fancy-list-markers}
+## Fancy list markers
+
+(2) begins with 2
+
+(3) and now 3
+
+ with a continuation
+
+ iv. sublist with roman numerals, starting with 4
+ v. more items
+
+ (A) a subsublist
+ (B) a subsublist
+
+Nesting:
+
+A. Upper Alpha
+
+ I. Upper Roman.
+
+ (6) Decimal start with 6
+
+ c) Lower alpha with paren
+
+Autonumbering:
+
+1. Autonumber.
+2. More.
+
+ 1. Nested.
+
+Should not be a list item:
+
+M.A. 2007
+
+B. Williams
+
+* * * *
+
+{#definition-lists}
+# Definition Lists
+
+Tight using spaces:
+
+: apple
+
+ red fruit
+: orange
+
+ orange fruit
+: banana
+
+ yellow fruit
+
+Tight using tabs:
+
+: apple
+
+ red fruit
+: orange
+
+ orange fruit
+: banana
+
+ yellow fruit
+
+Loose:
+
+: apple
+
+ red fruit
+
+: orange
+
+ orange fruit
+
+: banana
+
+ yellow fruit
+
+Multiple blocks with italics:
+
+: _apple_
+
+ red fruit
+
+ contains seeds, crisp, pleasant to taste
+
+: _orange_
+
+ orange fruit
+
+ ```
+ { orange code block }
+ ```
+
+ > orange block quote
+
+Multiple definitions, tight:
+
+: apple
+
+ red fruit
+
+ computer
+: orange
+
+ orange fruit
+
+ bank
+
+Multiple definitions, loose:
+
+: apple
+
+ red fruit
+
+ computer
+
+: orange
+
+ orange fruit
+
+ bank
+
+Blank line after term, indented marker, alternate markers:
+
+: apple
+
+ red fruit
+
+ computer
+
+: orange
+
+ orange fruit
+
+ 1. sublist
+ 2. sublist
+
+{#html-blocks}
+# HTML Blocks
+
+Simple block on one line:
+
+:::
+foo
+
+:::
+
+And nested without indentation:
+
+::::::
+::::
+:::
+foo
+
+:::
+
+::::
+
+:::
+bar
+
+:::
+
+::::::
+
+Interpreted markdown in a table:
+
+This is _emphasized_
+
+And this is *strong*
+
+Here's a simple block:
+
+:::
+foo
+
+:::
+
+This should be a code block, though:
+
+```
+<div>
+ foo
+</div>
+```
+
+As should this:
+
+```
+<div>foo</div>
+```
+
+Now, nested:
+
+:::::
+::::
+:::
+foo
+
+:::
+
+::::
+
+:::::
+
+This should just be an HTML comment:
+
+Multiline:
+
+Code block:
+
+```
+<!-- Comment -->
+```
+
+Just plain comment, with trailing spaces on the line:
+
+Code:
+
+```
+<hr />
+```
+
+Hr's:
+
+* * * *
+
+{#inline-markup}
+# Inline Markup
+
+This is _emphasized_, and so _is this_.
+
+This is *strong*, and so *is this*.
+
+An _[emphasized link](/url)_.
+
+*_This is strong and em._*
+
+So is *_this_* word.
+
+*_This is strong and em._*
+
+So is *_this_* word.
+
+This is code: `>`, `$`, `\`, `\$`, `<html>`.
+
+{-This is _strikeout_.-}
+
+Superscripts: a^bc^d a^_hello_^ a^hello there^.
+
+Subscripts: H~2~O, H~23~O, H~many of them~O.
+
+These should not be superscripts or subscripts, because of the unescaped spaces:
+a\^b c\^d, a\~b c\~d.
+
+* * * *
+
+{#smart-quotes-ellipses-dashes}
+# Smart quotes, ellipses, dashes
+
+"Hello," said the spider. "'Shelob' is my name."
+
+'A', 'B', and 'C' are letters.
+
+'Oak,' 'elm,' and 'beech' are names of trees. So is 'pine.'
+
+'He said, "I want to go."' Were you alive in the 70's?
+
+Here is some quoted '`code`' and a "[quoted
+link](http://example.com/?foo=1&bar=2)".
+
+Some dashes: one---two --- three---four --- five.
+
+Dashes between numbers: 5--7, 255--66, 1987--1999.
+
+Ellipses...and...and....
+
+* * * *
+
+{#latex}
+# LaTeX
+
+-
+- $`2+2=4`
+- $`x \in y`
+- $`\alpha \wedge \omega`
+- $`223`
+- $`p`-Tree
+- Here's some display math:
+ $$`\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}`
+- Here's one that has a line break in it: $`\alpha + \omega \times x^2`.
+
+These shouldn't be math:
+
+- To get the famous equation, write `$e = mc^2$`.
+- $22,000 is a _lot_ of money. So is $34,000. (It worked if "lot" is
+ emphasized.)
+- Shoes ($20) and socks ($5).
+- Escaped `$`\: $73 _this should be emphasized_ 23$.
+
+Here's a LaTeX table:
+
+* * * *
+
+{#special-characters}
+# Special Characters
+
+Here is some unicode:
+
+- I hat: Î
+- o umlaut: ö
+- section: §
+- set membership: ∈
+- copyright: ©
+
+AT&T has an ampersand in their name.
+
+AT&T is another way to write it.
+
+This & that.
+
+4 \< 5.
+
+6 \> 5.
+
+Backslash: \\
+
+Backtick: \`
+
+Asterisk: \*
+
+Underscore: \_
+
+Left brace: \{
+
+Right brace: \}
+
+Left bracket: \[
+
+Right bracket: \]
+
+Left paren: (
+
+Right paren: )
+
+Greater-than: \>
+
+Hash: #
+
+Period: .
+
+Bang: \!
+
+Plus: +
+
+Minus: -
+
+* * * *
+
+{#links}
+# Links
+
+{#explicit}
+## Explicit
+
+Just a [URL](/url/).
+
+[URL and title](/url/){title="title"}.
+
+[URL and title](/url/){title="title preceded by two spaces"}.
+
+[URL and title](/url/){title="title preceded by a tab"}.
+
+[URL and title](/url/){title="title with \"quotes\" in it"}
+
+[URL and title](/url/){title="title with single quotes"}
+
+[with\_underscore](/url/with_underscore)
+
+[Email link](mailto:[email protected])
+
+[Empty]().
+
+{#reference}
+## Reference
+
+Foo [bar](/url/).
+
+With [embedded \[brackets\]](/url/).
+
+[b](/url/) by itself should be a link.
+
+Indented [once](/url).
+
+Indented [twice](/url).
+
+Indented [thrice](/url).
+
+This should \[not\]\[\] be a link.
+
+```
+[not]: /url
+```
+
+Foo [bar](/url/){title="Title with \"quotes\" inside"}.
+
+Foo [biz](/url/){title="Title with \"quote\" inside"}.
+
+{#with-ampersands}
+## With ampersands
+
+Here's a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2).
+
+Here's a link with an amersand in the link text:
+[AT&T](http://att.com/){title="AT&T"}.
+
+Here's an [inline link](/script?foo=1&bar=2).
+
+Here's an [inline link in pointy braces](/script?foo=1&bar=2).
+
+{#autolinks}
+## Autolinks
+
+With an ampersand: <http://example.com/?foo=1&bar=2>
+
+- In a list?
+- <http://example.com/>
+- It should.
+
+An e-mail address: <[email protected]>
+
+> Blockquoted: <http://example.com/>
+
+Auto-links should not occur here: `<http://example.com/>`
+
+```
+or here: <http://example.com/>
+```
+
+* * * *
+
+{#images}
+# Images
+
+From "Voyage dans la Lune" by Georges Melies (1902):
+
+::::
+![lalune](lalune.jpg){title="Voyage dans la Lune"}
+
+{.caption}
+:::
+lalune
+
+:::
+
+::::
+
+Here is a movie ![movie](movie.jpg) icon.
+
+* * * *
+
+{#footnotes}
+# Footnotes
+
+Here is a footnote reference,[^1] and another.[^2] This should _not_ be a
+footnote reference, because it contains a space.\[\^my note\] Here is an inline
+note.[^3]
+
+> Notes can go in quotes.[^4]
+
+1. And in list items.[^5]
+
+This paragraph should not be part of the note, as it is not indented.
+
+[^1]: Here is the footnote. It can go anywhere after the footnote reference. It
+ need not be placed at the end of the document.
+
+[^2]: Here's the long note. This one contains multiple blocks.
+
+ Subsequent blocks are indented to show that they belong to the footnote (as
+ with list items).
+
+ ```
+ { <code> }
+ ```
+
+ If you want, you can indent every line, but you can also be lazy and just
+ indent the first line of each block.
+
+[^3]: This is _easier_ to type. Inline notes may contain
+ [links](http://google.com) and `]` verbatim characters, as well as
+ \[bracketed text\].
+
+[^4]: In quote.
+
+[^5]: In list.