aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorreptee <[email protected]>2025-09-15 12:45:28 +0200
committerGitHub <[email protected]>2025-09-15 12:45:28 +0200
commita0cfb3fd31bc3729266cc3a7aaac1416df183445 (patch)
tree188945541576851557ac34e3b19c01cd45bd0197
parent0ce85b0cfa8e5d3155dddc77b1408b4d7d7890fa (diff)
Vimdoc writer (#11132)
Support for vimdoc, documentation format used by vim in its help pages. Relies heavily on definition lists and precise text alignment to generate tags.
-rw-r--r--MANUAL.txt2
-rw-r--r--data/templates/default.vimdoc16
-rw-r--r--pandoc.cabal7
-rw-r--r--src/Text/Pandoc/Writers.hs3
-rw-r--r--src/Text/Pandoc/Writers/Vimdoc.hs615
-rw-r--r--test/Tests/Old.hs18
-rw-r--r--test/tables.vimdoc65
-rw-r--r--test/vimdoc/definition-lists.markdown70
-rw-r--r--test/vimdoc/definition-lists.vimdoc71
-rw-r--r--test/vimdoc/headers-numbered.vimdoc108
-rw-r--r--test/vimdoc/headers.markdown45
-rw-r--r--test/vimdoc/headers.vimdoc94
-rw-r--r--test/vimdoc/vim-online-doc.markdown42
-rw-r--r--test/vimdoc/vim-online-doc.vimdoc53
-rw-r--r--test/writer.vimdoc669
15 files changed, 1877 insertions, 1 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index 2b621cd85..7d1af9e01 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -361,6 +361,7 @@ header when requesting a document from a URL:
- `s5` ([S5] HTML and JavaScript slide show)
- `tei` ([TEI Simple])
- `typst` ([typst])
+ - `vimdoc` ([Vimdoc])
- `xml` (XML version of native AST)
- `xwiki` ([XWiki markup])
- `zimwiki` ([ZimWiki markup])
@@ -511,6 +512,7 @@ header when requesting a document from a URL:
[DokuWiki markup]: https://www.dokuwiki.org/dokuwiki
[ZimWiki markup]: https://zim-wiki.org/manual/Help/Wiki_Syntax.html
[XWiki markup]: https://www.xwiki.org/xwiki/bin/view/Documentation/UserGuide/Features/XWikiSyntax/
+[Vimdoc]: https://vimhelp.org/helphelp.txt.html#help-writing
[TWiki markup]: https://twiki.org/cgi-bin/view/TWiki/TextFormattingRules
[TikiWiki markup]: https://doc.tiki.org/Wiki-Syntax-Text#The_Markup_Language_Wiki-Syntax
[Haddock markup]: https://www.haskell.org/haddock/doc/html/ch03s08.html
diff --git a/data/templates/default.vimdoc b/data/templates/default.vimdoc
new file mode 100644
index 000000000..1bf80e2d1
--- /dev/null
+++ b/data/templates/default.vimdoc
@@ -0,0 +1,16 @@
+$if(filename)$*${filename}* $endif$$if(abstract)$${abstract}$endif$$if(filename)$
+
+
+$endif$$if(combined-title)$${combined-title}
+
+
+$endif$$toc-reminder$
+
+$if(toc)$
+$toc$
+
+$endif$
+
+$body$
+
+ $modeline$
diff --git a/pandoc.cabal b/pandoc.cabal
index 378d2ef1a..4dcd15ab4 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -23,7 +23,7 @@ description: Pandoc is a Haskell library for converting from one markup
txt2tags, djot)
- HTML formats (HTML 4 and 5)
- Ebook formats (EPUB v2 and v3, FB2)
- - Documentation formats (GNU TexInfo, Haddock)
+ - Documentation formats (GNU TexInfo, Haddock, Vimdoc)
- Roff formats (man, ms)
- TeX formats (LaTeX, ConTeXt)
- Typst
@@ -110,6 +110,7 @@ data-files:
data/templates/fonts.latex
data/templates/font-settings.latex
data/templates/after-header-includes.latex
+ data/templates/default.vimdoc
-- translations
data/translations/*.yaml
@@ -386,6 +387,7 @@ extra-source-files:
test/writer.zimwiki
test/writer.xwiki
test/writer.muse
+ test/writer.vimdoc
test/ansi-test.ansi
test/writers-lang-and-dir.latex
test/writers-lang-and-dir.context
@@ -433,6 +435,8 @@ extra-source-files:
test/odt/markdown/*.md
test/odt/native/*.native
test/pod-reader.pod
+ test/vimdoc/*.markdown
+ test/vimdoc/*.vimdoc
source-repository head
type: git
location: https://github.com/jgm/pandoc.git
@@ -660,6 +664,7 @@ library
Text.Pandoc.Writers.AnnotatedTable,
Text.Pandoc.Writers.BibTeX,
Text.Pandoc.Writers.ANSI,
+ Text.Pandoc.Writers.Vimdoc,
Text.Pandoc.PDF,
Text.Pandoc.UTF8,
Text.Pandoc.Scripting,
diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs
index 164bf6d0f..556ff5ddf 100644
--- a/src/Text/Pandoc/Writers.hs
+++ b/src/Text/Pandoc/Writers.hs
@@ -79,6 +79,7 @@ module Text.Pandoc.Writers
, writeXML
, writeXWiki
, writeZimWiki
+ , writeVimdoc
, getWriter
) where
@@ -132,6 +133,7 @@ import Text.Pandoc.Writers.Typst
import Text.Pandoc.Writers.XML
import Text.Pandoc.Writers.XWiki
import Text.Pandoc.Writers.ZimWiki
+import Text.Pandoc.Writers.Vimdoc
data Writer m = TextWriter (WriterOptions -> Pandoc -> m Text)
| ByteStringWriter (WriterOptions -> Pandoc -> m BL.ByteString)
@@ -206,6 +208,7 @@ writers = [
,("djot" , TextWriter writeDjot)
,("ansi" , TextWriter writeANSI)
,("xml" , TextWriter writeXML)
+ ,("vimdoc" , TextWriter writeVimdoc)
]
-- | Retrieve writer, extensions based on formatSpec (format+extensions).
diff --git a/src/Text/Pandoc/Writers/Vimdoc.hs b/src/Text/Pandoc/Writers/Vimdoc.hs
new file mode 100644
index 000000000..f20b99b6c
--- /dev/null
+++ b/src/Text/Pandoc/Writers/Vimdoc.hs
@@ -0,0 +1,615 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE Strict #-}
+
+module Text.Pandoc.Writers.Vimdoc (writeVimdoc) where
+
+import Control.Applicative (optional, (<|>))
+import Control.Monad (forM)
+import Control.Monad.Reader (MonadReader (..), ReaderT (..), asks)
+import Control.Monad.State (MonadState (..), StateT, evalStateT, gets, modify)
+import Data.Default (Default (..))
+import Data.List (intercalate, intersperse, transpose)
+import Data.List.NonEmpty (NonEmpty (..), nonEmpty)
+import Data.Maybe (fromMaybe)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Text.DocLayout hiding (char, link, text)
+import Text.Pandoc.Class.PandocMonad ( report, PandocMonad )
+import Text.Pandoc.Definition
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Logging (LogMessage (..))
+import Text.Pandoc.Options (WrapOption (..), WriterOptions (..))
+import Text.Pandoc.Parsing.General (many1Till, many1TillChar, readWith)
+import Text.Pandoc.Shared (capitalize, onlySimpleTableCells, orderedListMarkers, isTightList, makeSections, removeFormatting, tshow)
+import Text.Pandoc.Templates (renderTemplate)
+import Text.Pandoc.URI (escapeURI, isURI)
+import Text.Pandoc.Writers.Shared (defField, metaToContext, toLegacyTable)
+import Text.Parsec (anyChar, char, eof, string, try)
+import Text.Read (readMaybe)
+import Text.Pandoc.Chunks (toTOCTree, SecInfo (..))
+import Data.Tree (Tree(..))
+import Data.Functor ((<&>))
+import Data.Sequence (Seq, (|>), (<|))
+import qualified Data.Sequence as Seq
+import Data.Foldable (toList)
+
+data WriterState = WriterState
+ { indentLevel :: Int -- How much to indent the block. Inlines shouldn't
+ -- be concerned with indent level (I guess?)
+ , shiftWidth :: Int -- spaces per indentation level
+ , writerOptions :: WriterOptions
+ , vimdocPrefix :: Maybe Text
+ }
+
+instance Default WriterState where
+ def =
+ WriterState
+ { indentLevel = 0
+ , shiftWidth = 4
+ , writerOptions = def
+ , vimdocPrefix = Nothing
+ }
+
+indent :: (Monad m) => Int -> (VW m a) -> (VW m a)
+indent n = local (\s -> s{indentLevel = indentLevel s + n})
+
+type VW m = StateT (Seq (Doc Text)) (ReaderT WriterState m)
+
+runRR :: (Monad m) => Seq (Doc Text) -> WriterState -> VW m a -> m a
+runRR footnotes opts action = runReaderT (evalStateT action footnotes) opts
+
+docShiftWidth :: Meta -> Maybe Int
+docShiftWidth meta = case lookupMeta "shiftwidth" meta of
+ Just (MetaInlines [Str sw]) -> readMaybe (T.unpack sw)
+ Just (MetaString sw) -> readMaybe (T.unpack sw)
+ _ -> Nothing
+
+docVimdocPrefix :: Meta -> Maybe Text
+docVimdocPrefix meta = case lookupMeta "vimdoc-prefix" meta of
+ Just (MetaInlines [Str pref]) -> Just pref
+ Just (MetaString pref) -> Just pref
+ _ -> Nothing
+
+{- | Build a vim modeline
+>>> makeModeLine def
+"vim:tw=72:sw=4:ts=4:ft=help:norl:et:"
+-}
+makeModeLine :: WriterState -> Text
+makeModeLine ws =
+ T.pack . intercalate ":" $
+ [ "vim"
+ , "tw=" <> show tw
+ , "sw=" <> show sw
+ , "ts=" <> show sw
+ , "ft=help"
+ , "norl" -- left-to-right text
+ , "et:" -- expandtab and finishing ":"
+ ]
+ where
+ tw = writerColumns . writerOptions $ ws
+ sw = shiftWidth ws
+
+-- | Build a single formatted TOC line
+tocEntryToLine :: (PandocMonad m) => SecInfo -> VW m Text
+tocEntryToLine secinfo = do
+ rightRef <- mkVimdocRef (secId secinfo)
+ let numberStr = case secNumber secinfo of
+ Nothing -> ""
+ Just x | '.' `T.elem` x -> x <> " "
+ Just x -> x <> ". "
+ title <- inlineListToVimdoc $ removeFormatting (secTitle secinfo)
+ let titlePlain = render Nothing (title <> " ")
+
+ -- length sub 2 because vertical bars are concealed
+ let rightRefLen = max 0 (T.length rightRef - 2)
+ let numberLen = T.length numberStr
+ let leftLen = numberLen + T.length titlePlain
+ let padForRight = 1
+ textWidth <- asks (writerColumns . writerOptions)
+ il <- asks indentLevel
+
+ -- positive when we lack space (i.e. content is too long)
+ let lack = (il + leftLen + padForRight + rightRefLen) - textWidth
+
+ -- when lacking, truncate title reserving 3+ chars for ellipsis
+ let finalTitle =
+ if lack >= 0
+ then
+ let trunc = T.dropEnd (lack + 3) titlePlain
+ stripped = T.stripEnd trunc
+ ellipsis =
+ T.replicate (3 + T.length trunc - T.length stripped) "."
+ in stripped <> ellipsis
+ else titlePlain
+
+ -- Negative lack means we have an excess of space, so we fill it with dots
+ let dots = T.replicate (negate lack) "."
+
+ pure . T.concat $ [numberStr, finalTitle, dots, " ", rightRef]
+
+vimdocTOC :: (PandocMonad m) => WriterState -> [Block] -> VW m (Doc Text)
+vimdocTOC (WriterState{writerOptions = opts}) blocks = do
+ let (Node _ subtrees) =
+ toTOCTree $ makeSections (writerNumberSections opts) Nothing blocks
+ let tocDepth = writerTOCDepth opts
+ let isBelowTocDepth (Node sec _) = secLevel sec <= tocDepth
+
+ let makeItem :: (PandocMonad m) => Tree SecInfo -> VW m (Doc Text)
+ makeItem (Node secinfo xs) = do
+ line <- tocEntryToLine secinfo
+ -- When unnumbered, indent constantly by two,
+ -- otherwise indent by (length of marker + 1)
+ let markerLen = 1 + maybe 1 T.length (secNumber secinfo)
+ childItems <-
+ indent markerLen $
+ traverse makeItem (filter isBelowTocDepth xs)
+ pure (literal line $$ nest markerLen (vcat childItems))
+
+ items <- traverse makeItem (filter isBelowTocDepth subtrees)
+ pure $ vcat items
+
+writeVimdoc :: (PandocMonad m) => WriterOptions -> Pandoc -> m Text
+writeVimdoc opts document@(Pandoc meta _) =
+ let
+ sw = fromMaybe (shiftWidth def) $ docShiftWidth meta
+ vp = docVimdocPrefix meta
+ footnotes = Seq.empty
+ initialEnv = def{shiftWidth = sw, writerOptions = opts, vimdocPrefix = vp}
+ in
+ runRR footnotes initialEnv $ pandocToVimdoc document
+
+pandocToVimdoc :: (PandocMonad m) => Pandoc -> VW m Text
+pandocToVimdoc (Pandoc meta body) = do
+ st <- ask
+ let opts = writerOptions st
+
+ metadata <- metaToContext opts blockListToVimdoc inlineListToVimdoc meta
+ main <- do
+ body' <- blockListToVimdoc body
+ footnotes <- get
+ rule <- blockToVimdoc HorizontalRule
+ let footnotes' = if Seq.null footnotes
+ then Empty
+ else vsep (toList $ rule <| footnotes)
+ pure $ body' <> blankline <> footnotes'
+
+ title <- inlineListToVimdoc $ docTitle meta
+ authors <- traverse inlineListToVimdoc $ docAuthors meta
+ let authors' = mconcat $ intersperse ("," <> space) (fmap nowrap authors)
+ let tw = writerColumns . writerOptions $ st
+
+ let combinedTitle =
+ render (Just tw) . cblock tw $
+ (title <> space)
+ <> (if null authors' then "" else "by" <> space <> authors')
+
+ -- This is placed here because I couldn't find a way to right-align text
+ -- inside template to the width specified by a variable
+ let toc_reminder =
+ render Nothing . rblock tw $
+ ("Type |gO| to see the table of contents." :: Doc Text)
+
+ toc <- render (Just tw) <$> vimdocTOC st body
+
+ let modeline = makeModeLine st
+ let context =
+ defField "body" main
+ . defField "toc" (if writerTableOfContents opts then toc else "")
+ . defField "modeline" modeline
+ . defField "combined-title" combinedTitle
+ . defField "toc-reminder" toc_reminder
+ $ metadata
+
+ pure $
+ case writerTemplate opts of
+ Just tpl -> render (Just tw) $ renderTemplate tpl context
+ Nothing -> render (Just tw) main
+
+blockListToVimdoc :: (PandocMonad m) => [Block] -> VW m (Doc Text)
+blockListToVimdoc blocks = vcat <$> mapM blockToVimdoc blocks
+
+blockToVimdoc :: (PandocMonad m) => Block -> VW m (Doc Text)
+
+blockToVimdoc (Plain inlines) = inlineListToVimdoc inlines
+
+blockToVimdoc (Para inlines) = do
+ contents <- inlineListToVimdoc inlines
+ pure $ contents <> blankline
+
+blockToVimdoc (LineBlock inliness) = vcat <$> mapM inlineListToVimdoc inliness
+
+blockToVimdoc (CodeBlock (_, cls, _) code) = do
+ sw <- asks shiftWidth
+ let lang = case cls of
+ (lang' : _) -> lang'
+ _ -> ""
+ -- NOTE: No blankline after the codeblock because closing `<` is concealed
+ pure . vcat $
+ [ ">" <> literal lang
+ , nest sw (literal code)
+ , flush "<"
+ ]
+
+blockToVimdoc block@(RawBlock format raw) = case format of
+ "vimdoc" -> pure $ literal raw
+ _ -> "" <$ report (BlockNotRendered block)
+
+blockToVimdoc (BlockQuote blocks) = do
+ content <- blockListToVimdoc blocks
+ pure $ nest 2 content <> blankline
+
+blockToVimdoc (OrderedList listAttr items) = do
+ let itemSpacer = if isTightList items then empty else blankline
+ let itemsWithMarkers = zip (orderedListMarkers listAttr) items
+ items' <- forM itemsWithMarkers $ \(marker, blocks) -> do
+ let markerLen = T.length marker
+
+ item' <- indent (markerLen + 1) $ blockListToVimdoc blocks
+ pure $ literal marker <> space <> nest (markerLen + 1) item' <> itemSpacer
+ pure $ vcat items' <> blankline
+
+blockToVimdoc (BulletList items) = do
+ let itemSpacer = if isTightList items then empty else blankline
+ items' <- forM items $ \blocks -> do
+ let marker = "-"
+ item <- indent 2 $ blockListToVimdoc blocks
+ pure $ marker <> " " <> nest 2 item <> itemSpacer
+ pure $ vcat items' <> blankline
+
+blockToVimdoc (DefinitionList items) = do
+ sw <- asks shiftWidth
+ let sepAll = if all (isTightList . snd) items then vcat else vsep
+ items' <- forM items $ \(term, definitions) -> do
+ let sepCur = if isTightList definitions then vcat else vsep
+ labeledTerm <- mkVimdocDefinitionTerm term
+ definitions' <- indent sw $ traverse blockListToVimdoc definitions
+ pure $ labeledTerm <> cr <> nest sw (sepCur definitions')
+ pure $ sepAll items' <> blankline
+
+blockToVimdoc (Header level (ref, _, _) inlines) = do
+ tw <- asks (writerColumns . writerOptions)
+ let rule = case level of
+ 1 -> T.replicate tw "="
+ 2 -> T.replicate tw "-"
+ _ -> ""
+ title <- fmap (render Nothing) . inlineListToVimdoc $ case level of
+ 3 -> capitalize inlines
+ _ -> inlines
+
+ label <- mkVimdocTag ref
+ -- One manual space that ensures that even if spaceLeft is 0, title and ref
+ -- don't touch each other
+ let label' = " " <> label
+ -- (+ 2) due to stars concealment
+ let spaceLeft = tw - T.length title + 2
+
+ pure $ vcat
+ [ blankline
+ , literal rule
+ , literal $ title <> T.justifyRight spaceLeft ' ' label'
+ , blankline
+ ]
+
+blockToVimdoc HorizontalRule = do
+ tw <- asks (writerColumns . writerOptions)
+ pure $ literal (T.replicate (tw `div` 2) " *") <> blankline
+
+-- Based on blockToMarkdown' from Text.Pandoc.Writers.Markdown
+blockToVimdoc t@(Table (_, _, _) blkCapt specs thead tbody tfoot) = do
+ let isColRowSpans (Cell _ _ rs cs _) = rs > 1 || cs > 1
+ let rowHasColRowSpans (Row _ cs) = any isColRowSpans cs
+ let tbodyHasColRowSpans (TableBody _ _ rhs rs) =
+ any rowHasColRowSpans rhs || any rowHasColRowSpans rs
+ let theadHasColRowSpans (TableHead _ rs) = any rowHasColRowSpans rs
+ let tfootHasColRowSpans (TableFoot _ rs) = any rowHasColRowSpans rs
+ let hasColRowSpans =
+ theadHasColRowSpans thead
+ || any tbodyHasColRowSpans tbody
+ || tfootHasColRowSpans tfoot
+ let (caption, aligns, widths, headers, rows) =
+ toLegacyTable blkCapt specs thead tbody tfoot
+ let numcols =
+ maximum $
+ length aligns :| length widths : map length (headers : rows)
+ caption' <- inlineListToVimdoc caption
+ let caption''
+ | null caption = blankline
+ | otherwise = blankline $$ caption' $$ blankline
+ let hasSimpleCells = onlySimpleTableCells $ headers : rows
+ let isSimple = hasSimpleCells && all (== 0) widths && not hasColRowSpans
+ let isPlainBlock (Plain _) = True
+ isPlainBlock _ = False
+ let hasBlocks = not (all (all (all isPlainBlock)) $ headers : rows)
+ let padRow r = r ++ replicate x empty
+ where
+ x = numcols - length r
+ let aligns' = aligns ++ replicate x AlignDefault
+ where
+ x = numcols - length aligns
+ let widths' = widths ++ replicate x 0.0
+ where
+ x = numcols - length widths
+ sw <- asks shiftWidth
+ rawHeaders <- padRow <$> mapM blockListToVimdoc headers
+ rawRows <- mapM (fmap padRow . mapM blockListToVimdoc) rows
+ let hasHeader = all null headers
+ if
+ | isSimple -> do
+ -- Simple table
+ tbl <-
+ indent sw $
+ vimdocTable False hasHeader aligns' widths' rawHeaders rawRows
+ pure $ nest sw (tbl $$ caption'') $$ blankline
+ | not (hasBlocks || hasColRowSpans) -> do
+ -- Multiline table
+ tbl <-
+ indent sw $
+ vimdocTable True hasHeader aligns' widths' rawHeaders rawRows
+ pure $ nest sw (tbl $$ caption'') $$ blankline
+ | otherwise -> ("[TABLE]" $$ caption'') <$ report (BlockNotRendered t)
+
+blockToVimdoc (Figure _ _ blocks) = blockListToVimdoc blocks
+
+blockToVimdoc (Div _ blocks) = blockListToVimdoc blocks
+
+{- | Create a vimdoc tag. Tag is prefixed with "$vimdocPrefix-" if vimdocPrefix
+is a Just value.
+>>> runReader (mkVimdocTag "abc") def
+"*abc*"
+>>> runReader (mkVimdocTag "abc") (def{vimdocPrefix = Just "myCoolProject"})
+"*myCoolProject-abc*"
+-}
+mkVimdocTag :: (Monad m) => Text -> VW m Text
+mkVimdocTag tag = do
+ asks vimdocPrefix <&> \case
+ _ | T.null tag -> ""
+ Nothing -> "*" <> tag <> "*"
+ Just pref' -> "*" <> pref' <> "-" <> tag <> "*"
+
+{- | Create a hotlink for a tag, ie. a followable vimdoc link. Tag is prefixed
+ - with "$vimdocPrefix-" if vimdocPrefix is a Just value
+>>> runReader (mkVimdocRef "abc") def
+"|abc|"
+>>> runReader (mkVimdocRef "abc") (def{vimdocPrefix = Just "myCoolProject"})
+"|myCoolProject-abc|"
+-}
+mkVimdocRef :: (Monad m) => Text -> VW m Text
+mkVimdocRef ref =
+ asks vimdocPrefix <&> \case
+ _ | T.null ref -> ""
+ Nothing -> "|" <> ref <> "|"
+ Just pref' -> "|" <> pref' <> "-" <> ref <> "|"
+
+mkVimdocDefinitionTerm ::
+ (PandocMonad m) =>
+ [Inline] ->
+ VW m (Doc Text)
+mkVimdocDefinitionTerm inlines = do
+ il <- asks indentLevel
+ tw <- asks (writerColumns . writerOptions)
+ label <- case inlines of
+ -- NOTE: commands in vim are unique, so they get no prefix
+ [Code (ref, _, _) code]
+ | T.isPrefixOf ":" code ->
+ pure . Just $ "*" <> ref <> "*"
+ [Code (ref, _, _) _] | not (T.null ref) -> Just <$> mkVimdocTag ref
+ [Span (ref, _, _) _] | not (T.null ref) -> Just <$> mkVimdocTag ref
+ _ -> pure Nothing
+
+ term <- case inlines of
+ [Code _ code] | T.isPrefixOf ":" code -> pure $ literal code
+ _ -> inlineListToVimdoc inlines
+ let termLen = offset term
+ let labelLen = maybe 0 T.length label
+
+ if il + termLen + labelLen > tw
+ then
+ pure . mconcat $
+ [ case label of
+ Nothing -> empty
+ -- (+2) due to stars concealment
+ Just l -> flush (rblock (tw + 2) $ literal l) <> cr
+ , term
+ ]
+ else
+ pure . mconcat $
+ [ -- Since we calculated that label fits on the same line as
+ -- term and since label actually must exceed textwidth to align
+ -- properly, we disable wrapping.
+ -- vvvvvvvv
+ nowrap term
+ , case label of
+ Nothing -> empty
+ -- (+2) due to stars concealment
+ Just l -> rblock (tw - termLen - il + 2) (literal l)
+ ]
+
+-- | Write a vimdoc table
+vimdocTable ::
+ (Monad m) =>
+ -- | whether this is a multiline table
+ Bool ->
+ -- | whether the table has a header
+ Bool ->
+ -- | column alignments
+ [Alignment] ->
+ -- | column widths
+ [Double] ->
+ -- | table header cells
+ [Doc Text] ->
+ -- | table body rows
+ [[Doc Text]] ->
+ VW m (Doc Text)
+vimdocTable multiline headless aligns widths rawHeaders rawRows = do
+ let isSimple = all (== 0) widths
+ let alignHeader alignment = case alignment of
+ AlignLeft -> lblock
+ AlignCenter -> cblock
+ AlignRight -> rblock
+ AlignDefault -> lblock
+ -- Number of characters per column necessary to output every cell
+ -- without requiring a line break.
+ -- The @+2@ is needed for specifying the alignment.
+ let numChars = (+ 2) . maybe 0 maximum . nonEmpty . map offset
+ -- Number of characters per column necessary to output every cell
+ -- without requiring a line break *inside a word*.
+ -- The @+2@ is needed for specifying the alignment.
+ let minNumChars = (+ 2) . maybe 0 maximum . nonEmpty . map minOffset
+ let columns = transpose (rawHeaders : rawRows)
+
+ il <- asks indentLevel
+
+ -- x = (2 * length columns) -- spaces for specifying the alignment
+ -- y = (length columns - 1) -- spaces between the columns
+ -- x + y = (3 * length columns - 1) -- total needed correction
+ tw <- asks (writerColumns . writerOptions)
+ let tw' = tw - il - 3 * length columns + 1
+ wrap <- asks (writerWrapText . writerOptions)
+
+ -- minimal column width without wrapping a single word
+ let relWidth w col =
+ max
+ (floor $ fromIntegral (tw' - 1) * w)
+ ( if wrap == WrapAuto
+ then minNumChars col
+ else numChars col
+ )
+ let widthsInChars
+ | isSimple = map numChars columns
+ | otherwise = zipWith relWidth widths columns
+ let makeRow =
+ hcat
+ . intersperse (lblock 1 (literal " "))
+ . zipWith3 alignHeader aligns widthsInChars
+ let rows' = map makeRow rawRows
+ -- TODO: reduce tw in case head is not empty
+ let head' = makeRow rawHeaders <> " ~"
+ let head'' =
+ if headless
+ then empty
+ else head'
+ let body =
+ if multiline
+ then
+ vsep rows'
+ $$ if length rows' < 2
+ then blankline
+ else empty
+ else vcat rows'
+ return $
+ blankline
+ $$ head''
+ $$ (if multiline then blankline else empty)
+ $$ body
+
+-- | Replace Unicode characters with their ASCII representation
+replaceSpecialStrings :: Text -> Text
+replaceSpecialStrings =
+ let expand c = case c of
+ '\x00ad' -> ""
+ '\x2013' -> "--"
+ '\x2014' -> "---"
+ '\x2019' -> "'"
+ '\x2026' -> "..."
+ _ -> T.singleton c
+ in T.concatMap expand
+
+inlineListToVimdoc :: (PandocMonad m) => [Inline] -> VW m (Doc Text)
+inlineListToVimdoc inlines = hcat <$> mapM inlineToVimdoc inlines
+
+inlineToVimdoc :: (PandocMonad m) => Inline -> VW m (Doc Text)
+
+inlineToVimdoc (Str str) = pure . literal $ replaceSpecialStrings str
+
+-- Neither `:h help-writing`, nor neovim's grammar.js for vimdoc and
+-- highlights.scm say anything about styling text, so we strip all the
+-- formatting
+inlineToVimdoc (Emph inlines) = inlineListToVimdoc inlines
+inlineToVimdoc (Underline inlines) = inlineListToVimdoc inlines
+inlineToVimdoc (Strong inlines) = inlineListToVimdoc inlines
+inlineToVimdoc (Strikeout inlines) = inlineListToVimdoc inlines
+inlineToVimdoc (Superscript inlines) = inlineListToVimdoc inlines
+inlineToVimdoc (Subscript inlines) = inlineListToVimdoc inlines
+inlineToVimdoc (SmallCaps inlines) = inlineListToVimdoc inlines
+
+inlineToVimdoc (Quoted typ inlines) =
+ let quote = case typ of SingleQuote -> "'"; DoubleQuote -> "\""
+ in inlineListToVimdoc inlines >>= \text -> pure (quote <> text <> quote)
+
+inlineToVimdoc (Cite _citations inlines) = inlineListToVimdoc inlines
+
+inlineToVimdoc (Code (_, cls, _) code) = do
+ let hasNoLang = null cls
+ pure . literal $ case T.words code of
+ [":help", ref] | hasNoLang -> "|" <> ref <> "|"
+ [":h", ref] | hasNoLang -> "|" <> ref <> "|"
+ _ -> "`" <> code <> "`"
+
+inlineToVimdoc Space = pure space
+inlineToVimdoc SoftBreak =
+ asks (writerWrapText . writerOptions) >>= \case
+ WrapAuto -> pure space
+ WrapNone -> pure " "
+ WrapPreserve -> pure "\n"
+
+inlineToVimdoc LineBreak = pure "\n"
+
+inlineToVimdoc (Math _ math) = pure . literal $ "`$" <> math <> "$`"
+
+inlineToVimdoc inline@(RawInline (Format format) text) = case format of
+ "vimdoc" -> pure $ literal text
+ _ -> "" <$ report (InlineNotRendered inline)
+
+inlineToVimdoc (Link _ txt (src, _)) = do
+ let srcSuffix = fromMaybe src (T.stripPrefix "mailto:" src)
+ linkText <- render Nothing <$> inlineListToVimdoc txt
+
+ let isAutolink = case txt of
+ [Str x] | escapeURI x `elem` [src, srcSuffix] -> True
+ _ -> False
+
+ pure $ case refdocLinkToLink src of
+ Right link | isAutolink -> "|" <> literal link <> "|"
+ Right link ->
+ literal (T.stripEnd linkText) <> space <> "|" <> literal link <> "|"
+ Left _ | isURI src, isAutolink -> literal srcSuffix
+ Left _ -> literal (T.stripEnd linkText) <> space <> literal srcSuffix
+
+inlineToVimdoc (Image {}) = pure ""
+
+inlineToVimdoc (Note blocks) = do
+ newN <- gets (succ . Seq.length)
+ contents <- blockListToVimdoc blocks
+ tag <- mkVimdocTag ("footnote" <> tshow newN)
+ tw <- asks (writerColumns . writerOptions)
+
+ -- (+2) due to concealment of stars
+ -- vvvvvvvv
+ let taggedContents = rblock (tw + 2) (literal tag) $$ contents
+ modify (|> taggedContents)
+
+ ref <- mkVimdocRef ("footnote" <> tshow newN)
+ pure $ space <> literal ref
+
+inlineToVimdoc (Span _ inlines) = inlineListToVimdoc inlines
+
+
+refdocLinkToLink :: Text -> Either PandocError Text
+refdocLinkToLink x = (\parser -> readWith parser Nothing x) $ do
+ string "http" >> optional (char 's') >> string "://"
+
+ let vimhelpP = do
+ try (string "vimhelp.org/") <|> string "neo.vimhelp.org/"
+
+ try (many1Till anyChar (char '#') >> many1TillChar anyChar eof)
+ <|> many1TillChar anyChar (try $ string ".html" >> eof)
+
+ let neovimP = do
+ string "neovim.io/doc/user/"
+ try (many1Till anyChar (char '#') >> many1TillChar anyChar eof)
+ <|> do base <- many1TillChar anyChar (try $ string ".html" >> eof)
+ pure $ base <> ".txt"
+
+ try vimhelpP <|> neovimP
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index d74fa3d36..2dcccf013 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -257,6 +257,24 @@ tests pandocPath =
[ test' "pod" ["-f", "pod", "-t", "native"]
"pod-reader.pod" "pod-reader.native"
]
+ , testGroup "vimdoc" [ testGroup "writer" $
+ writerTests' "vimdoc" ++
+ [ test' "vimdoc-specific definition lists"
+ ["-s", "-r", "markdown", "-w", "vimdoc", "--toc", "--columns=78"]
+ "vimdoc/definition-lists.markdown" "vimdoc/definition-lists.vimdoc"
+ , test' "linking to docs"
+ ["-s", "-r", "markdown", "-w", "vimdoc", "--toc", "--columns=78"]
+ "vimdoc/vim-online-doc.markdown" "vimdoc/vim-online-doc.vimdoc"
+ , test' "unnumbered TOC up to level 2 headers"
+ ["-s", "-r", "markdown", "-w", "vimdoc", "--toc", "--columns=78",
+ "--toc-depth=2"]
+ "vimdoc/headers.markdown" "vimdoc/headers.vimdoc"
+ , test' "numbered TOC"
+ ["-s", "-r", "markdown", "-w", "vimdoc", "--toc", "--columns=78",
+ "-N"]
+ "vimdoc/headers.markdown" "vimdoc/headers-numbered.vimdoc"
+ ]
+ ]
]
where
test' = test pandocPath
diff --git a/test/tables.vimdoc b/test/tables.vimdoc
new file mode 100644
index 000000000..0f0492095
--- /dev/null
+++ b/test/tables.vimdoc
@@ -0,0 +1,65 @@
+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 Left Right Default aligned
+ Header Aligned 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 Left Right Default aligned
+ Header Aligned 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/vimdoc/definition-lists.markdown b/test/vimdoc/definition-lists.markdown
new file mode 100644
index 000000000..a075d5125
--- /dev/null
+++ b/test/vimdoc/definition-lists.markdown
@@ -0,0 +1,70 @@
+---
+vimdoc-prefix: pandoc
+abstract: "A short description"
+filename: "definition-lists.txt"
+author: Author
+title: Title
+---
+
+## Basic
+
+Term 1
+: Definition I
+
+Term 2
+: Definition II
+
+Term 3
+: Definition III
+
+## Code
+
+<!-- Source: <https://github.com/ggandor/leap.nvim/blob/c4a215acef90749851d85ddba08bc282867b50eb/doc/leap.txt#L283-L294> -->
+
+`leap.opts.keys.next_target`
+: Jump to the next available target (use the previous search pattern if no input
+ has been given). `:h leap-repeat`
+
+`leap.opts.keys.prev_target`
+: Jump to the previous target (revert `next_target`).
+
+`leap.opts.keys.next_group`
+: Shift to the next group of labeled targets.
+
+`leap.opts.keys.prev_group`
+: Shift to the previous group of labeled targets (revert `next_group`).
+
+## Span
+
+[Important concept]{#important-concept}
+: Definition
+
+[I am too long to fit on the same line as a reference, so reference is put above me!]{#i-am-too-long}
+: Lorem ipsum dolor sit amet, consectetur adipisicing elit, sed do eiusmod
+ tempor incididunt ut labore et dolore magna aliqua.
+
+## Commands
+
+In markdown vim commands are represented as inline code starting with colon (ie.
+`:MyCommand`), but writer strips the backticks
+
+`:FnlCompileBuffer`{#:FnlCompileBuffer}
+
+: Compiles current active fennel buffer
+
+`:FnlCompile[!]`{#:FnlCompile}
+
+: Diff compiles all indexed fennel files
+ If bang! is present then forcefully compiles all `source` files
+
+`:[range]Fnl {expr}`{#:Fnl}
+
+: Evaluates {expr} or range
+
+ ```
+ :'<,'>Fnl
+
+ :Fnl (print "Hello World")
+
+ :Fnl (values some_var)
+ ```
diff --git a/test/vimdoc/definition-lists.vimdoc b/test/vimdoc/definition-lists.vimdoc
new file mode 100644
index 000000000..3061de6be
--- /dev/null
+++ b/test/vimdoc/definition-lists.vimdoc
@@ -0,0 +1,71 @@
+*definition-lists.txt* A short description
+
+ Title by Author
+
+
+ Type |gO| to see the table of contents.
+
+Basic ........................................................... |pandoc-basic|
+Code ............................................................. |pandoc-code|
+Span ............................................................. |pandoc-span|
+Commands ..................................................... |pandoc-commands|
+
+------------------------------------------------------------------------------
+Basic *pandoc-basic*
+
+Term 1
+ Definition I
+Term 2
+ Definition II
+Term 3
+ Definition III
+
+------------------------------------------------------------------------------
+Code *pandoc-code*
+
+`leap.opts.keys.next_target`
+ Jump to the next available target (use the previous search pattern if no
+ input has been given). |leap-repeat|
+`leap.opts.keys.prev_target`
+ Jump to the previous target (revert `next_target`).
+`leap.opts.keys.next_group`
+ Shift to the next group of labeled targets.
+`leap.opts.keys.prev_group`
+ Shift to the previous group of labeled targets (revert `next_group`).
+
+------------------------------------------------------------------------------
+Span *pandoc-span*
+
+Important concept *pandoc-important-concept*
+ Definition
+ *pandoc-i-am-too-long*
+I am too long to fit on the same line as a reference, so reference is put
+above me!
+ Lorem ipsum dolor sit amet, consectetur adipisicing elit, sed do eiusmod
+ tempor incididunt ut labore et dolore magna aliqua.
+
+------------------------------------------------------------------------------
+Commands *pandoc-commands*
+
+In markdown vim commands are represented as inline code starting with colon
+(ie. `:MyCommand`), but writer strips the backticks
+
+:FnlCompileBuffer *:FnlCompileBuffer*
+ Compiles current active fennel buffer
+
+:FnlCompile[!] *:FnlCompile*
+ Diff compiles all indexed fennel files If bang! is present then forcefully
+ compiles all `source` files
+
+:[range]Fnl {expr} *:Fnl*
+ Evaluates {expr} or range
+
+ >
+ :'<,'>Fnl
+
+ :Fnl (print "Hello World")
+
+ :Fnl (values some_var)
+<
+
+ vim:tw=78:sw=4:ts=4:ft=help:norl:et:
diff --git a/test/vimdoc/headers-numbered.vimdoc b/test/vimdoc/headers-numbered.vimdoc
new file mode 100644
index 000000000..4bbb48107
--- /dev/null
+++ b/test/vimdoc/headers-numbered.vimdoc
@@ -0,0 +1,108 @@
+ Type |gO| to see the table of contents.
+
+1. unremarkable header 1 ............................... |unremarkable-header-1|
+ 1.1 unremarkable header 2 ............................ |unremarkable-header-2|
+ 1.1.1 unremarkable header 3 ...................... |unremarkable-header-3|
+ 1.1.2 unremarkable header 3 .................... |unremarkable-header-3-1|
+ unremarkable header 2 .............................. |unremarkable-header-2-1|
+ unremarkable header 3 ............................ |unremarkable-header-3-2|
+ unremarkable header 3 ............................ |unremarkable-header-3-3|
+2. bold italic underline strikethrough ............................... |short11|
+ 2.1 superscript2 subscript3 ........................................ |short21|
+ 2.1.1 smallcaps code inline math display math .................. |short31|
+ 2.1.2 link image ............................................... |short32|
+3. Long header 1 long header 1 long header 1 long header 1 long heade... |long1|
+ 3.1 Long header 2 long header 2 long header 2 long header 2 long h... |long21|
+ 3.1.1 Long header 3 long header 3 long header 3 long header 3.... |long31|
+ 3.1.2 Long header 3 long header 3 long header 3 long header 3.... |long32|
+ 3.2 Long header 2 long header 2 long header 2 long header 2 long h... |long22|
+ 3.2.1 Long header 3 long header 3 long header 3 long header 3.... |long33|
+ 3.2.2 Long header 3 long header 3 long header 3 long header 3.... |long34|
+4. ... |long-header-1-long-header-1-long-header-1-long-header-1-long-header-1-long-header-1-long-header-1|
+ 4.1 ... |long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2|
+ 4.1.1 ... |long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3|
+ 4.1.2 ... |long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-1|
+ 4.2 ... |long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-1|
+ 4.2.1 ... |long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-2|
+ 4.2.2 ... |long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-3|
+
+
+Headers with a short title and implicit ref. Last 3 headers are unnumbered.
+
+==============================================================================
+unremarkable header 1 *unremarkable-header-1*
+
+------------------------------------------------------------------------------
+unremarkable header 2 *unremarkable-header-2*
+
+UNREMARKABLE HEADER 3 *unremarkable-header-3*
+
+UNREMARKABLE HEADER 3 *unremarkable-header-3-1*
+
+------------------------------------------------------------------------------
+unremarkable header 2 *unremarkable-header-2-1*
+
+UNREMARKABLE HEADER 3 *unremarkable-header-3-2*
+
+UNREMARKABLE HEADER 3 *unremarkable-header-3-3*
+
+ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+
+Headers with various inline elements
+
+==============================================================================
+bold italic underline strikethrough *short11*
+
+------------------------------------------------------------------------------
+superscript2 subscript3 *short21*
+
+SMALLCAPS `code` `$inline math$` `$display math$` *short31*
+
+LINK example.com *short32*
+
+ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+
+Headers with a long name and explicit short ref
+
+==============================================================================
+Long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 *long1*
+
+------------------------------------------------------------------------------
+Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 *long21*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long31*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long32*
+
+------------------------------------------------------------------------------
+Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 *long22*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long33*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long34*
+
+ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+
+Headers with a long name and implicit ref.
+
+Since implicit ref is very lengthy, there is no way to fit it. Therefore title
+is not rendered and the references exceed the columns (textwidth) limit
+
+==============================================================================
+Long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 *long-header-1-long-header-1-long-header-1-long-header-1-long-header-1-long-header-1-long-header-1*
+
+------------------------------------------------------------------------------
+Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 *long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-1*
+
+------------------------------------------------------------------------------
+Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 *long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-1*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-2*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-3*
+
+ vim:tw=78:sw=4:ts=4:ft=help:norl:et:
diff --git a/test/vimdoc/headers.markdown b/test/vimdoc/headers.markdown
new file mode 100644
index 000000000..fa285c8b1
--- /dev/null
+++ b/test/vimdoc/headers.markdown
@@ -0,0 +1,45 @@
+Headers with a short title and implicit ref. Last 3 headers are unnumbered.
+
+# unremarkable header 1
+## unremarkable header 2
+### unremarkable header 3
+### unremarkable header 3
+## unremarkable header 2 {.unnumbered}
+### unremarkable header 3 {.unnumbered}
+### unremarkable header 3 {.unnumbered}
+
+---
+
+Headers with various inline elements
+
+# **bold** *italic* [underline]{.underline} ~strikethrough~ {#short11}
+## superscript^2^ subscript~3~ {#short21}
+### [smallcaps]{.smallcaps} `code` $inline math$ $$display math$$ {#short31}
+### [link](example.com) ![image](https://duckduckgo.com/favicon.ico) {#short32}
+
+---
+
+Headers with a long name and explicit short ref
+
+# Long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 {#long1}
+## Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 {#long21}
+### Long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 {#long31}
+### Long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 {#long32}
+## Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 {#long22}
+### Long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 {#long33}
+### Long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 {#long34}
+
+---
+
+Headers with a long name and implicit ref.
+
+Since implicit ref is very lengthy, there is no way to fit it. Therefore title
+is not rendered and the references exceed the columns (textwidth) limit
+
+# Long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 long header 1
+## Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2
+### Long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 long header 3
+### Long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 long header 3
+## Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2
+### Long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 long header 3
+### Long header 3 long header 3 long header 3 long header 3 long header 3 long header 3 long header 3
diff --git a/test/vimdoc/headers.vimdoc b/test/vimdoc/headers.vimdoc
new file mode 100644
index 000000000..a73e69770
--- /dev/null
+++ b/test/vimdoc/headers.vimdoc
@@ -0,0 +1,94 @@
+ Type |gO| to see the table of contents.
+
+unremarkable header 1 .................................. |unremarkable-header-1|
+ unremarkable header 2 ................................ |unremarkable-header-2|
+ unremarkable header 2 .............................. |unremarkable-header-2-1|
+bold italic underline strikethrough .................................. |short11|
+ superscript2 subscript3 ............................................ |short21|
+Long header 1 long header 1 long header 1 long header 1 long header 1... |long1|
+ Long header 2 long header 2 long header 2 long header 2 long heade... |long21|
+ Long header 2 long header 2 long header 2 long header 2 long heade... |long22|
+... |long-header-1-long-header-1-long-header-1-long-header-1-long-header-1-long-header-1-long-header-1|
+ ... |long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2|
+ ... |long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-1|
+
+
+Headers with a short title and implicit ref. Last 3 headers are unnumbered.
+
+==============================================================================
+unremarkable header 1 *unremarkable-header-1*
+
+------------------------------------------------------------------------------
+unremarkable header 2 *unremarkable-header-2*
+
+UNREMARKABLE HEADER 3 *unremarkable-header-3*
+
+UNREMARKABLE HEADER 3 *unremarkable-header-3-1*
+
+------------------------------------------------------------------------------
+unremarkable header 2 *unremarkable-header-2-1*
+
+UNREMARKABLE HEADER 3 *unremarkable-header-3-2*
+
+UNREMARKABLE HEADER 3 *unremarkable-header-3-3*
+
+ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+
+Headers with various inline elements
+
+==============================================================================
+bold italic underline strikethrough *short11*
+
+------------------------------------------------------------------------------
+superscript2 subscript3 *short21*
+
+SMALLCAPS `code` `$inline math$` `$display math$` *short31*
+
+LINK example.com *short32*
+
+ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+
+Headers with a long name and explicit short ref
+
+==============================================================================
+Long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 *long1*
+
+------------------------------------------------------------------------------
+Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 *long21*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long31*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long32*
+
+------------------------------------------------------------------------------
+Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 *long22*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long33*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long34*
+
+ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+
+Headers with a long name and implicit ref.
+
+Since implicit ref is very lengthy, there is no way to fit it. Therefore title
+is not rendered and the references exceed the columns (textwidth) limit
+
+==============================================================================
+Long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 long header 1 *long-header-1-long-header-1-long-header-1-long-header-1-long-header-1-long-header-1-long-header-1*
+
+------------------------------------------------------------------------------
+Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 *long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-1*
+
+------------------------------------------------------------------------------
+Long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 long header 2 *long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-long-header-2-1*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-2*
+
+LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 LONG HEADER 3 *long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-long-header-3-3*
+
+ vim:tw=78:sw=4:ts=4:ft=help:norl:et:
diff --git a/test/vimdoc/vim-online-doc.markdown b/test/vimdoc/vim-online-doc.markdown
new file mode 100644
index 000000000..ecc80b400
--- /dev/null
+++ b/test/vimdoc/vim-online-doc.markdown
@@ -0,0 +1,42 @@
+# Online vim documentation
+
+While vim documentation can be accessed with `:help`, it may be beneficial to
+link to the websites inside readme/markdown docs. Two most common websites are:
+
+- <https://vimhelp.org/> and
+- <https://neovim.io/doc/user>
+
+Also it is not uncommon to reference documentation as `:h <topic>`
+
+## Links to vimhelp.org {#vimhelp-links}
+
+For introduction to writing help files see
+<https://vimhelp.org/helphelp.txt.html#help-writing>
+
+Named link: [vimhelp link](https://vimhelp.org/helphelp.txt.html#help-writing)
+
+## Links to neo.vimhelp.org {#neo-vimhelp-links}
+
+For introduction to writing help files see
+<https://neo.vimhelp.org/helphelp.txt.html#help-writing>
+
+Named link: [vimhelp link](https://neo.vimhelp.org/helphelp.txt.html#help-writing)
+
+## Links to neovim.io {#neovim-io-links}
+
+For introduction to writing help files see
+<https://neovim.io/doc/user/helphelp.html#help-writing>
+
+Named link: [neovim.io link](https://neovim.io/doc/user/helphelp.html#help-writing)
+
+You can also reference whole files with topic omitted:
+<https://neovim.io/doc/user/vim_diff.html>
+
+## :h-style documentation {#colon-h-docs}
+
+For introduction to writing help files see
+`:h help-writing`
+
+Long name for `:help` is also supported: `:help help-writing`
+
+This is malformed: `:help help-writing `, but this is not: `:help help-writing`
diff --git a/test/vimdoc/vim-online-doc.vimdoc b/test/vimdoc/vim-online-doc.vimdoc
new file mode 100644
index 000000000..179454f91
--- /dev/null
+++ b/test/vimdoc/vim-online-doc.vimdoc
@@ -0,0 +1,53 @@
+ Type |gO| to see the table of contents.
+
+Online vim documentation ............................ |online-vim-documentation|
+ Links to vimhelp.org ......................................... |vimhelp-links|
+ Links to neo.vimhelp.org ................................. |neo-vimhelp-links|
+ Links to neovim.io ......................................... |neovim-io-links|
+ :h-style documentation ........................................ |colon-h-docs|
+
+==============================================================================
+Online vim documentation *online-vim-documentation*
+
+While vim documentation can be accessed with `:help`, it may be beneficial to
+link to the websites inside readme/markdown docs. Two most common websites
+are:
+
+- https://vimhelp.org/ and
+- https://neovim.io/doc/user
+
+Also it is not uncommon to reference documentation as |<topic>|
+
+------------------------------------------------------------------------------
+Links to vimhelp.org *vimhelp-links*
+
+For introduction to writing help files see |help-writing|
+
+Named link: vimhelp link |help-writing|
+
+------------------------------------------------------------------------------
+Links to neo.vimhelp.org *neo-vimhelp-links*
+
+For introduction to writing help files see |help-writing|
+
+Named link: vimhelp link |help-writing|
+
+------------------------------------------------------------------------------
+Links to neovim.io *neovim-io-links*
+
+For introduction to writing help files see |help-writing|
+
+Named link: neovim.io link |help-writing|
+
+You can also reference whole files with topic omitted: |vim_diff.txt|
+
+------------------------------------------------------------------------------
+:h-style documentation *colon-h-docs*
+
+For introduction to writing help files see |help-writing|
+
+Long name for `:help` is also supported: |help-writing|
+
+This is malformed: |help-writing|, but this is not: |help-writing|
+
+ vim:tw=78:sw=4:ts=4:ft=help:norl:et:
diff --git a/test/writer.vimdoc b/test/writer.vimdoc
new file mode 100644
index 000000000..daacdae02
--- /dev/null
+++ b/test/writer.vimdoc
@@ -0,0 +1,669 @@
+ Pandoc Test Suite by John MacFarlane, Anonymous
+
+
+ Type |gO| to see the table of contents.
+
+
+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 /url *level-2-with-an-embedded-link*
+
+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: abcd ahello ahello there.
+
+Subscripts: H2O, H23O, Hmany of themO.
+
+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/.
+
+URL and title /url/.
+
+URL and title /url/.
+
+URL and title /url/
+
+URL and title /url/
+
+with_underscore /url/with_underscore
+
+Email link [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/.
+
+Foo biz /url/.
+
+--------------------------------------------------------------------------------
+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/.
+
+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):
+
+Here is a movie icon.
+
+ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+
+================================================================================
+Footnotes *footnotes*
+
+Here is a footnote reference, |footnote1| and another. |footnote2| This should
+not be a footnote reference, because it contains a space.[^my note] Here is an
+inline note. |footnote3|
+
+ Notes can go in quotes. |footnote4|
+
+1. And in list items. |footnote5|
+
+This paragraph should not be part of the note, as it is not indented.
+
+ * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+
+ *footnote1*
+Here is the footnote. It can go anywhere after the footnote reference. It need
+not be placed at the end of the document.
+
+ *footnote2*
+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.
+
+ *footnote3*
+This is easier to type. Inline notes may contain links http://google.com and `]`
+verbatim characters, as well as [bracketed text].
+
+ *footnote4*
+In quote.
+
+ *footnote5*
+In list.
+
+ vim:tw=80:sw=4:ts=4:ft=help:norl:et: