diff --git a/MANUAL.txt b/MANUAL.txt index af7a573c3e48..283a25037c2e 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -269,6 +269,7 @@ header when requesting a document from a URL: - `mdoc` ([mdoc] manual page markup) - `muse` ([Muse]) - `native` (native Haskell) + - `obsidian` ([Obsidian-Flavored Markdown]) - `odt` ([OpenDocument text document][ODT]) - `opml` ([OPML]) - `org` ([Emacs Org mode]) @@ -503,6 +504,7 @@ header when requesting a document from a URL: [Jira]: https://jira.atlassian.com/secure/WikiRendererHelpAction.jspa?section=all [txt2tags]: https://txt2tags.org [EPUB]: http://idpf.org/epub +[Obsidian-Flavored Markdown]: https://help.obsidian.md/obsidian-flavored-markdown [OPML]: http://dev.opml.org/spec2.html [OpenDocument XML]: https://www.oasis-open.org/2021/06/16/opendocument-v1-3-oasis-standard-published/ [ODT]: https://en.wikipedia.org/wiki/OpenDocument @@ -6004,11 +6006,18 @@ or image itself, if these differ. ### Extension: `mark` ### -To highlight out a section of text, begin and end it with +To highlight a section of text, begin and end it with with `==`. Thus, for example, This ==is deleted text.== +### Extension: `comments` ### + +To comment out a section of text, begin and end it +with `%%`. Thus, for example, + + This %%is a comment.%% + ### Extension: `attributes` ### Allows attributes to be attached to any inline or block-level @@ -6155,15 +6164,16 @@ simply skipped (as opposed to being parsed as paragraphs). ### Extension: `alerts` ### -Supports [GitHub-style Markdown alerts], like +Supports [GitHub-style Markdown alerts] and [Obsidian callouts], like > [!TIP] > Helpful advice for doing things better or more easily. + [Obsidian callouts]: https://help.obsidian.md/callouts [GitHub-style Markdown alerts]: https://docs.github.com/en/get-started/writing-on-github/getting-started-with-writing-and-formatting-on-github/basic-writing-and-formatting-syntax#alerts Note: This extension currently only works with commonmark: -`commonmark`, `gfm`, `commonmark_x`. +`commonmark`, `gfm`, `commonmark_x`, `obsidian`. ### Extension: `autolink_bare_uris` ### @@ -6213,6 +6223,38 @@ or Oxygen is O~2. +### Extension: `wikilink_transclusions` ### + +Follows [Obsidan-style transclusions] using wikilink syntax to embed one file in another. For example to transclude the file "Title": + + ![[Title]] + +[Obsidan-style transclusions]: https://help.obsidian.md/embeds + +### Extension: `wilikink_heading_transclusions` ### + +Follows the [Obsidan-style heading transclusions] syntax. For example to transclude a heading within the file "Title": + + ![[Title#Heading]] + +[Obsidan-style heading transclusions]: https://help.obsidian.md/links#Link+to+a+heading+in+a+note + +### Extension: `wilikink_block_transclusions` ### + +Follows the [Obsidan-style block transclusions] syntax. For example to transclude block ID ^ref within the file "Title": + + ![[Title#^ref]] + +[Obsidan-style block transclusions]: https://help.obsidian.md/links#Link+to+a+block+in+a+note + +### Extension: `block_ids` ### + +Follows the [Obsidan-style block identifiers] syntax. For example add `^ref` at the end of a paragraph: + + Text ^ref + +[Obsidan-style block identifiers]: https://help.obsidian.md/links#Link+to+a+block+in+a+note + ### Extension: `wikilinks_title_after_pipe` ### Pandoc supports multiple Markdown wikilink syntaxes, regardless of @@ -6240,6 +6282,7 @@ variants are supported: - `markdown_strict` (Markdown.pl) - `commonmark` (CommonMark) - `gfm` (Github-Flavored Markdown) +- `obsidian` (Obsidian-Flavored Markdown) - `commonmark_x` (CommonMark with many pandoc extensions) To see which extensions are supported for a given format, diff --git a/README.md b/README.md index 37a36eb5fea2..09667bd45d4b 100644 --- a/README.md +++ b/README.md @@ -85,6 +85,7 @@ It can convert *from* markup) - `muse` ([Muse](https://amusewiki.org/library/manual)) - `native` (native Haskell) +- `obsidian` ([Obsidian-Flavored Markdown](https://help.obsidian.md/obsidian-flavored-markdown)) - `odt` ([OpenDocument text document](https://en.wikipedia.org/wiki/OpenDocument)) - `opml` ([OPML](http://dev.opml.org/spec2.html)) diff --git a/src/Text.Pandoc/Parsing.hs b/src/Text.Pandoc/Parsing.hs new file mode 100644 index 000000000000..e69de29bb2d1 diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index 6f173da0e12a..711aa2e0f512 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -57,8 +57,10 @@ data Extension = | Ext_backtick_code_blocks -- ^ GitHub style ``` code blocks | Ext_blank_before_blockquote -- ^ Require blank line before a blockquote | Ext_blank_before_header -- ^ Require blank line before a header + | Ext_block_ids -- ^ Block identifiers, used by Obsidian | Ext_bracketed_spans -- ^ Bracketed spans with attributes | Ext_citations -- ^ Pandoc/citeproc citations + | Ext_comments -- ^ Percent wrapped %%comments%% | Ext_definition_lists -- ^ Definition lists as in pandoc, mmd, php | Ext_east_asian_line_breaks -- ^ Newlines in paragraphs are ignored between -- East Asian wide characters. Note: this extension @@ -141,6 +143,9 @@ data Extension = -- [[target|title]] | Ext_wikilinks_title_before_pipe -- ^ Support wikilinks of style -- [[title|target]] + | Ext_wikilink_transclusions -- ^ Wikilink transclusion e.g. ![[title]] + | Ext_wikilink_heading_transclusions -- ^ Wikilink heading transclusion e.g. ![[title#heading]] in Obsidian + | Ext_wikilink_block_transclusions -- ^ Wikilink block transclusions, e.g. ![[title#^id]] in Obsidian | Ext_xrefs_name -- ^ Use xrefs with names | Ext_xrefs_number -- ^ Use xrefs with numbers | Ext_yaml_metadata_block -- ^ YAML metadata block @@ -405,6 +410,26 @@ getDefaultExtensions "gfm" = extensionsFromList , Ext_tex_math_gfm , Ext_alerts ] +getDefaultExtensions "obsidian" = extensionsFromList + [ Ext_alerts + , Ext_autolink_bare_uris + , Ext_block_ids + , Ext_comments + , Ext_footnotes + , Ext_hard_line_breaks + , Ext_mark + , Ext_pipe_tables + , Ext_raw_html + , Ext_rebase_relative_paths + , Ext_strikeout + , Ext_task_lists + , Ext_tex_math_dollars + , Ext_wikilinks_title_after_pipe + , Ext_wikilink_transclusions + , Ext_wikilink_block_transclusions + , Ext_wikilink_heading_transclusions + , Ext_yaml_metadata_block + ] getDefaultExtensions "commonmark" = extensionsFromList [Ext_raw_html] getDefaultExtensions "commonmark_x" = extensionsFromList @@ -525,6 +550,27 @@ getAllExtensions f = universalExtensions <> getAll f getAll "markdown_mmd" = allMarkdownExtensions getAll "markdown_github" = allMarkdownExtensions getAll "markdown" = allMarkdownExtensions + getAll "obsidian" = allMarkdownExtensions <> extensionsFromList + [ Ext_ascii_identifiers + , Ext_alerts + , Ext_autolink_bare_uris + , Ext_block_ids + , Ext_comments + , Ext_footnotes + , Ext_hard_line_breaks + , Ext_mark + , Ext_pipe_tables + , Ext_raw_html + , Ext_rebase_relative_paths + , Ext_strikeout + , Ext_task_lists + , Ext_tex_math_dollars + , Ext_wikilink_block_transclusions + , Ext_wikilink_heading_transclusions + , Ext_wikilink_transclusions + , Ext_wikilinks_title_after_pipe + , Ext_yaml_metadata_block + ] getAll "ipynb" = allMarkdownExtensions <> extensionsFromList [ Ext_raw_markdown ] getAll "docx" = autoIdExtensions <> extensionsFromList diff --git a/src/Text/Pandoc/Parsing/State.hs b/src/Text/Pandoc/Parsing/State.hs index 547ddaabb891..b84f24459d98 100644 --- a/src/Text/Pandoc/Parsing/State.hs +++ b/src/Text/Pandoc/Parsing/State.hs @@ -77,6 +77,7 @@ data ParserState = ParserState , stateContainers :: [Text] -- ^ parent include files , stateLogMessages :: [LogMessage] -- ^ log messages , stateMarkdownAttribute :: Bool -- ^ True if in markdown=1 context + , stateLastBlockId :: Maybe Text } instance Default ParserState where @@ -166,6 +167,7 @@ defaultParserState = ParserState , stateContainers = [] , stateLogMessages = [] , stateMarkdownAttribute = False + , stateLastBlockId = Nothing } type NoteTable = [(Text, Text)] diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs index 12d1c6c95bf1..93edd0b537eb 100644 --- a/src/Text/Pandoc/Readers.hs +++ b/src/Text/Pandoc/Readers.hs @@ -141,6 +141,7 @@ readers = [("native" , TextReader readNative) ,("creole" , TextReader readCreole) ,("dokuwiki" , TextReader readDokuWiki) ,("gfm" , TextReader readCommonMark) + ,("obsidian" , TextReader readMarkdown) ,("rst" , TextReader readRST) ,("mediawiki" , TextReader readMediaWiki) ,("vimwiki" , TextReader readVimwiki) diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 0a17b9a1a1a1..4f1cd4627c7f 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -23,7 +23,7 @@ module Text.Pandoc.Readers.Markdown ( import Control.Monad import Control.Monad.Except (throwError) import Data.Bifunctor (second) -import Data.Char (isAlphaNum, isPunctuation, isSpace) +import Data.Char (isAlphaNum, isPunctuation, isSpace, toLower) import Data.List (transpose, elemIndex, sortOn, foldl') import qualified Data.Map as M import Data.Maybe @@ -46,7 +46,7 @@ import Text.Pandoc.Error import Safe.Foldable (maximumBounded) import Text.Pandoc.Logging import Text.Pandoc.Options -import Text.Pandoc.Walk (walk) +import Text.Pandoc.Walk (walk, query) import Text.Pandoc.Parsing hiding (tableCaption) import Text.Pandoc.Readers.HTML (htmlInBalanced, htmlTag, isBlockTag, isInlineTag, isTextTag) @@ -480,6 +480,12 @@ noteBlock = do -- parsing blocks -- +addBlockId :: Attr -> ParserState -> Attr +addBlockId (id', classes, kvs) st = + case stateLastBlockId st of + Nothing -> (id', classes, kvs) + Just bid -> (if T.null id' then bid else id', classes, kvs) + parseBlocks :: PandocMonad m => MarkdownParser m (F Blocks) parseBlocks = mconcat <$> manyTill block eof @@ -510,8 +516,15 @@ block = do , para , plain ] "block" - trace (T.take 60 $ tshow $ B.toList $ runF res defaultParserState) - return res + st <- getState + let addIdToBlock (Header lvl attr ils) = Header lvl (addBlockId attr st) ils + addIdToBlock (Para ils) = + case stateLastBlockId st of + Nothing -> Para ils + Just bid -> Div (bid, [], []) [Para ils] + addIdToBlock x = x + updateState $ \s -> s{ stateLastBlockId = Nothing } + return $ B.fromList . map addIdToBlock . B.toList <$> res -- -- header blocks @@ -1515,9 +1528,9 @@ inline = do '`' -> code '_' -> strongOrEmph '*' -> strongOrEmph - '^' -> inlineNote <|> superscript + '^' -> inlineNote <|> superscript <|> blockId -- in this order bc ^[link](/foo)^ '[' -> note <|> cite <|> bracketedSpan <|> wikilink B.linkWith <|> link - '!' -> image + '!' -> transclusion <|> image '$' -> math '~' -> strikeout <|> subscript '=' -> mark @@ -1534,6 +1547,7 @@ inline = do '.' -> smart '&' -> return . B.singleton <$> charRef ':' -> emoji + '%' -> comment _ -> mzero) <|> bareURL <|> str @@ -1854,14 +1868,18 @@ wikilink constructor = do try $ do string "[[" *> notFollowedBy' (char '[') raw <- many1TillChar anyChar (try $ string "]]") - let (title, url) = case T.break (== '|') raw of + let (title', target') = case T.break (== '|') raw of (before, "") -> (before, before) (before, after) | titleAfter -> (T.drop 1 after, before) | otherwise -> (before, T.drop 1 after) + let (url, blockRef) = T.break (== '#') target' guard $ T.all (`notElem` ['\n','\r','\f','\t']) url - return . pure . constructor attr url "" $ - B.text $ fromEntities title + let attr' = if T.null blockRef + then attr + else (mempty, ["wikilink"], [("block-ref", T.drop 1 blockRef)]) + return . pure . constructor attr' url "" $ + B.text $ fromEntities title' link :: PandocMonad m => MarkdownParser m (F Inlines) link = try $ do @@ -2017,20 +2035,78 @@ rebasePath pos path = do "." -> path d -> T.pack d <> "/" <> path +transclusion :: PandocMonad m => MarkdownParser m (F Inlines) +transclusion = try $ do + char '!' + string "[[" *> notFollowedBy' (char '[') + raw <- many1TillChar anyChar (try $ string "]]") + titleAfter <- (True <$ guardEnabled Ext_wikilinks_title_after_pipe) <|> pure False + let (_, target') = case T.break (== '|') raw of + (before, "") -> (before, before) + (before, after) + | titleAfter -> (T.drop 1 after, before) + | otherwise -> (before, T.drop 1 after) + let (url, fragment) = T.break (== '#') target' + guard $ T.all (`notElem` ['\n','\r','\f','\t']) url + + let urlStr = T.unpack url + let ext = map toLower $ takeExtension urlStr + let hasExtension = not (null ext) + let isMdFile = ext == ".md" + + -- Check if any transclusion extensions are enabled + hasTransclusions <- (True <$ guardEnabled Ext_wikilink_transclusions) <|> + (True <$ guardEnabled Ext_wikilink_block_transclusions) <|> + (True <$ guardEnabled Ext_wikilink_heading_transclusions) <|> + return False + + if hasTransclusions && (not hasExtension || isMdFile) + then -- Handle as transclusion (no extension or .md extension) + if T.null fragment + then do + guardEnabled Ext_wikilink_transclusions + currentDir <- takeDirectory . sourceName <$> getPosition + -- Only add .md extension if the file doesn't already have an extension + let filename = if null (takeExtension urlStr) + then T.unpack url <> ".md" + else T.unpack url + -- Support relative paths like "Folder/File" by using currentDir as base + insertIncludedFile parseTranscludedInlines toSources [currentDir] filename Nothing Nothing + else do + let fragmentContent = T.drop 1 fragment -- Remove the '#' prefix + if T.take 1 fragmentContent == "^" + then do + -- Block ID transclusion: ![[File#^block-id]] + guardEnabled Ext_wikilink_block_transclusions + currentDir <- takeDirectory . sourceName <$> getPosition + let filename = T.unpack url <> ".md" -- Assume .md extension for block transclusion + let blockIdText = T.drop 1 fragmentContent -- Remove the '^' prefix + -- Support relative paths like "Folder/File" by using currentDir as base + insertIncludedFile (parseBlockTransclusion blockIdText) toSources [currentDir] filename Nothing Nothing + else do + -- Heading transclusion: ![[File#Heading]] + guardEnabled Ext_wikilink_heading_transclusions + currentDir <- takeDirectory . sourceName <$> getPosition + let filename = T.unpack url <> ".md" -- Assume .md extension for heading transclusion + let headingText = fragmentContent + -- Support relative paths like "Folder/File" by using currentDir as base + insertIncludedFile (parseHeadingTransclusion headingText) toSources [currentDir] filename Nothing Nothing + else -- Handle as image/embed (has non-.md extension or transclusions disabled) + return $ return $ B.imageWith ("", ["wikilink"], []) url "" (B.text target') + image :: PandocMonad m => MarkdownParser m (F Inlines) image = try $ do char '!' - wikilink B.imageWith <|> - do (lab,raw) <- reference - defaultExt <- getOption readerDefaultImageExtension - let constructor attr' src - | "data:" `T.isPrefixOf` src = B.imageWith attr' src -- see #9118 - | otherwise = - case takeExtension (T.unpack src) of - "" -> B.imageWith attr' (T.pack $ addExtension (T.unpack src) - $ T.unpack defaultExt) - _ -> B.imageWith attr' src - regLink constructor lab <|> referenceLink constructor (lab, "!" <> raw) + (lab,raw) <- reference + defaultExt <- getOption readerDefaultImageExtension + let constructor attr' src + | "data:" `T.isPrefixOf` src = B.imageWith attr' src -- see #9118 + | otherwise = + case takeExtension (T.unpack src) of + "" -> B.imageWith attr' (T.pack $ addExtension (T.unpack src) + $ T.unpack defaultExt) + _ -> B.imageWith attr' src + regLink constructor lab <|> referenceLink constructor (lab, "!" <> raw) note :: PandocMonad m => MarkdownParser m (F Inlines) note = try $ do @@ -2308,6 +2384,13 @@ citation = try $ do , citationHash = 0 } +comment :: PandocMonad m => MarkdownParser m (F Inlines) +comment = try $ do + guardEnabled Ext_comments + string "%%" + manyTill (anyChar <|> newline) (try (string "%%")) + return mempty + smart :: PandocMonad m => MarkdownParser m (F Inlines) smart = do guardEnabled Ext_smart @@ -2332,3 +2415,118 @@ doubleQuoted = do fmap B.doubleQuoted . trimInlinesF . mconcat <$> many1Till inline doubleQuoteEnd)) <|> (return (return (B.str "\8220"))) + +-- | Extract a block with a specific ID from a list of blocks +extractBlockById :: Text -> Blocks -> Inlines +extractBlockById targetId blocks = + case findBlockById targetId (B.toList blocks) of + Just (Div _ contents) -> blocksToInlines' contents -- Extract content from Div wrapper + Just blk -> blocksToInlines' [blk] + Nothing -> mempty + +-- | Find a block with a specific ID in a list of blocks (including nested blocks) +findBlockById :: Text -> [Block] -> Maybe Block +findBlockById targetId blocks = + case query findBlock blocks of + (blk:_) -> Just blk + [] -> Nothing + where + findBlock :: Block -> [Block] + findBlock blk@(Div (bid, _, _) _) | bid == targetId = [blk] + findBlock blk@(Header _ (bid, _, _) _) | bid == targetId = [blk] + findBlock blk@(Table (bid, _, _) _ _ _ _ _) | bid == targetId = [blk] + findBlock blk@(CodeBlock (bid, _, _) _) | bid == targetId = [blk] + findBlock blk@(Figure (bid, _, _) _ _) | bid == targetId = [blk] + findBlock _ = [] + +-- | Extract content under a specific heading from a list of blocks +extractHeadingById :: Text -> Blocks -> Inlines +extractHeadingById targetHeading blocks = + case extractContentUnderHeading targetHeading (B.toList blocks) of + [] -> mempty + content -> blocksToInlines' content + +-- | Parse a file and convert all blocks to inlines for transclusion +parseTranscludedInlines :: PandocMonad m => MarkdownParser m (F Inlines) +parseTranscludedInlines = do + blocks <- parseBlocks + return $ fmap (blocksToInlines' . B.toList) blocks + +-- | Parse a file and extract a specific block by ID for transclusion +parseBlockTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines) +parseBlockTransclusion blockIdText = do + blocks <- parseBlocks + return $ fmap (extractBlockById blockIdText) blocks + +-- | Parse a file and extract content under a specific heading for transclusion +parseHeadingTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines) +parseHeadingTransclusion headingText = do + blocks <- parseBlocks + return $ fmap (extractHeadingById headingText) blocks + +-- | Extract all content under a heading until the next heading of same or higher level +-- Handles nested headings by using query to find the target heading anywhere in the document +extractContentUnderHeading :: Text -> [Block] -> [Block] +extractContentUnderHeading targetHeading blocks = + -- Check if target heading exists anywhere in the document + case query findTargetHeading blocks of + [] -> [] -- Target heading not found + ((targetLevel, _):_) -> + -- Target heading found, extract content using the traditional approach + -- but with the level information from the nested search + go False targetLevel blocks + where + -- Find the target heading anywhere in the document structure + findTargetHeading :: Block -> [(Int, [Inline])] + findTargetHeading (Header lvl _ ils) + | stringify ils == targetHeading = [(lvl, ils)] + findTargetHeading _ = [] + + -- Extract content after finding the target heading (handles top-level only for now) + go :: Bool -> Int -> [Block] -> [Block] + go _found _level [] = [] + go found level (blk:rest) = + case blk of + Header lvl _ ils + | stringify ils == targetHeading -> + -- Found target heading, start collecting content + blk : go True lvl rest + | found && lvl <= level -> + -- Found heading of same or higher level, stop collecting + [] + | found -> + -- Collecting content under target heading + blk : go True level rest + | otherwise -> + -- Haven't found target heading yet, check if it's nested in this block + case extractFromNestedBlock blk of + [] -> go False level rest + nestedContent -> nestedContent ++ go False level rest + _ | found -> + -- Collecting content under target heading + blk : go True level rest + | otherwise -> + -- Haven't found target heading yet, check if it's nested in this block + case extractFromNestedBlock blk of + [] -> go False level rest + nestedContent -> nestedContent ++ go False level rest + + -- Extract content from blocks that might contain the target heading + extractFromNestedBlock :: Block -> [Block] + extractFromNestedBlock blk = + case blk of + Div _ nestedBlocks -> extractContentUnderHeading targetHeading nestedBlocks + BlockQuote nestedBlocks -> extractContentUnderHeading targetHeading nestedBlocks + BulletList items -> concatMap (extractContentUnderHeading targetHeading) items + OrderedList _ items -> concatMap (extractContentUnderHeading targetHeading) items + DefinitionList items -> concatMap (\(_, defs) -> concatMap (extractContentUnderHeading targetHeading) defs) items + _ -> [] + +blockId :: PandocMonad m => MarkdownParser m (F Inlines) +blockId = try $ do + guardEnabled Ext_block_ids + char '^' + notFollowedBy space + bid <- T.pack <$> many1 (letter <|> digit <|> char '-') + updateState $ \st -> st{ stateLastBlockId = Just bid } + return mempty diff --git a/test/command/8853.md b/test/command/8853.md index bf15b5792d7b..15664a328bf0 100644 --- a/test/command/8853.md +++ b/test/command/8853.md @@ -1,6 +1,6 @@ ``` % pandoc -f markdown+wikilinks_title_after_pipe --wrap=none -[[hi]] and ![[hi]] +[[hi]] and ![[hi.jpg]] ^D -

hi and hi

+

hi and hi.jpg

``` diff --git a/test/command/obsidian.md b/test/command/obsidian.md new file mode 100644 index 000000000000..0fa42b01ab43 --- /dev/null +++ b/test/command/obsidian.md @@ -0,0 +1,611 @@ +obsidian tests: + +``` +% pandoc -f obsidian -t native +%% a comment %% +^D +[ Para [] ] +``` + +``` +% pandoc -f obsidian -t native +A paragraph with a block ID. ^my-id +^D +[ Div + ( "my-id" , [] , [] ) + [ Para + [ Str "A" + , Space + , Str "paragraph" + , Space + , Str "with" + , Space + , Str "a" + , Space + , Str "block" + , Space + , Str "ID." + ] + ] +] +``` + +``` +% pandoc -f obsidian -t native +An embed: ![[command/obsidian/transclusion]] +^D +[ Para + [ Str "An" + , Space + , Str "embed:" + , Space + , Str "This" + , Space + , Str "is" + , Space + , Str "the" + , Space + , Str "content" + , Space + , Str "of" + , Space + , Str "the" + , Space + , Str "Obsidian" + , Space + , Str "transclusion" + , Space + , Str "test" + , Space + , Str "file." + , LineBreak + , Str "Introduction" + , LineBreak + , Str "This" + , Space + , Str "is" + , Space + , Str "the" + , Space + , Str "introduction" + , Space + , Str "section" + , Space + , Str "with" + , Space + , Str "some" + , Space + , Str "content" + , Space + , Str "for" + , Space + , Str "heading" + , Space + , Str "transclusions." + , LineBreak + , Str "A" + , Space + , Str "paragraph" + , Space + , Str "with" + , Space + , Str "a" + , Space + , Str "block" + , Space + , Str "ID" + , Space + , Str "for" + , Space + , Str "testing" + , Space + , Str "block" + , Space + , Str "transclusions." + , LineBreak + , Str "Another" + , Space + , Str "Section" + , LineBreak + , Str "More" + , Space + , Str "content" + , Space + , Str "here." + ] +] +``` + +``` +% pandoc -f obsidian -t native +A block reference embed: ![[command/obsidian/transclusion#^my-id]] +^D +[ Para + [ Str "A" + , Space + , Str "block" + , Space + , Str "reference" + , Space + , Str "embed:" + , Space + , Str "A" + , Space + , Str "paragraph" + , Space + , Str "with" + , Space + , Str "a" + , Space + , Str "block" + , Space + , Str "ID" + , Space + , Str "for" + , Space + , Str "testing" + , Space + , Str "block" + , Space + , Str "transclusions." + ] +] +``` + +``` +% pandoc -f obsidian -t native +A wikilink transclusion: ![[command/obsidian/transclusion]] +^D +[ Para + [ Str "A" + , Space + , Str "wikilink" + , Space + , Str "transclusion:" + , Space + , Str "This" + , Space + , Str "is" + , Space + , Str "the" + , Space + , Str "content" + , Space + , Str "of" + , Space + , Str "the" + , Space + , Str "Obsidian" + , Space + , Str "transclusion" + , Space + , Str "test" + , Space + , Str "file." + , LineBreak + , Str "Introduction" + , LineBreak + , Str "This" + , Space + , Str "is" + , Space + , Str "the" + , Space + , Str "introduction" + , Space + , Str "section" + , Space + , Str "with" + , Space + , Str "some" + , Space + , Str "content" + , Space + , Str "for" + , Space + , Str "heading" + , Space + , Str "transclusions." + , LineBreak + , Str "A" + , Space + , Str "paragraph" + , Space + , Str "with" + , Space + , Str "a" + , Space + , Str "block" + , Space + , Str "ID" + , Space + , Str "for" + , Space + , Str "testing" + , Space + , Str "block" + , Space + , Str "transclusions." + , LineBreak + , Str "Another" + , Space + , Str "Section" + , LineBreak + , Str "More" + , Space + , Str "content" + , Space + , Str "here." + ] +] +``` + +``` +% pandoc -f obsidian -t native +A block transclusion: ![[command/obsidian/transclusion#^my-id]] +^D +[ Para + [ Str "A" + , Space + , Str "block" + , Space + , Str "transclusion:" + , Space + , Str "A" + , Space + , Str "paragraph" + , Space + , Str "with" + , Space + , Str "a" + , Space + , Str "block" + , Space + , Str "ID" + , Space + , Str "for" + , Space + , Str "testing" + , Space + , Str "block" + , Space + , Str "transclusions." + ] +] +``` + +``` +% pandoc -f obsidian -t native +A heading transclusion: ![[command/obsidian/transclusion#Introduction]] +^D +[ Para + [ Str "A" + , Space + , Str "heading" + , Space + , Str "transclusion:" + , Space + , Str "Introduction" + , LineBreak + , Str "This" + , Space + , Str "is" + , Space + , Str "the" + , Space + , Str "introduction" + , Space + , Str "section" + , Space + , Str "with" + , Space + , Str "some" + , Space + , Str "content" + , Space + , Str "for" + , Space + , Str "heading" + , Space + , Str "transclusions." + , LineBreak + , Str "A" + , Space + , Str "paragraph" + , Space + , Str "with" + , Space + , Str "a" + , Space + , Str "block" + , Space + , Str "ID" + , Space + , Str "for" + , Space + , Str "testing" + , Space + , Str "block" + , Space + , Str "transclusions." + ] +] +``` + +``` +% pandoc -f obsidian-wikilink_transclusions -t native +A wikilink transclusion: ![[obsidian/transclusion]] +^D +[ Para + [ Str "A" + , Space + , Str "wikilink" + , Space + , Str "transclusion:" + , Space + , Str "!" + , Link + ( "" , [ "wikilink" ] , [] ) + [ Str "obsidian/transclusion" ] + ( "obsidian/transclusion" , "" ) + ] +] +``` + +``` +% pandoc -f obsidian-wikilink_heading_transclusions -t native +A heading transclusion: ![[obsidian/transclusion#Introduction]] +^D +[ Para + [ Str "A" + , Space + , Str "heading" + , Space + , Str "transclusion:" + , Space + , Str "!" + , Link + ( "" + , [ "wikilink" ] + , [ ( "block-ref" , "Introduction" ) ] + ) + [ Str "obsidian/transclusion#Introduction" ] + ( "obsidian/transclusion" , "" ) + ] +] +``` + +``` +% pandoc -f obsidian-wikilink_block_transclusions -t native +A block transclusion: ![[obsidian/transclusion#^my-id]] +^D +[ Para + [ Str "A" + , Space + , Str "block" + , Space + , Str "transclusion:" + , Space + , Str "!" + , Link + ( "" , [ "wikilink" ] , [ ( "block-ref" , "^my-id" ) ] ) + [ Str "obsidian/transclusion#^my-id" ] + ( "obsidian/transclusion" , "" ) + ] +] +``` + +``` +% pandoc -f obsidian -t native +Text with ==highlighted== content. +^D +[ Para + [ Str "Text" + , Space + , Str "with" + , Space + , Span ( "" , [ "mark" ] , [] ) [ Str "highlighted" ] + , Space + , Str "content." + ] +] +``` + +``` +% pandoc -f obsidian -t native +Nested heading transclusion: ![[command/obsidian/nested-transclusion#Nested Heading in Blockquote]] +^D +[ Para + [ Str "Nested" + , Space + , Str "heading" + , Space + , Str "transclusion:" + , Space + , Str "Nested" + , Space + , Str "Heading" + , Space + , Str "in" + , Space + , Str "Blockquote" + , LineBreak + , Str "This" + , Space + , Str "heading" + , Space + , Str "is" + , Space + , Str "nested" + , Space + , Str "inside" + , Space + , Str "a" + , Space + , Str "blockquote" + , Space + , Str "for" + , Space + , Str "testing" + , Space + , Str "nested" + , Space + , Str "heading" + , Space + , Str "transclusions." + , LineBreak + , Str "Some" + , Space + , Str "content" + , Space + , Str "under" + , Space + , Str "the" + , Space + , Str "nested" + , Space + , Str "heading." + , LineBreak + , Str "A" + , Space + , Str "paragraph" + , Space + , Str "with" + , Space + , Str "a" + , Space + , Str "nested" + , Space + , Str "block" + , Space + , Str "ID." + ] +] +``` + +``` +% pandoc -f obsidian -t native +Nested block transclusion: ![[command/obsidian/nested-transclusion#^nested-block-id]] +^D +[ Para + [ Str "Nested" + , Space + , Str "block" + , Space + , Str "transclusion:" + , Space + , Str "A" + , Space + , Str "paragraph" + , Space + , Str "with" + , Space + , Str "a" + , Space + , Str "nested" + , Space + , Str "block" + , Space + , Str "ID." + ] +] +``` + +``` +% pandoc -f obsidian -t native +List nested heading transclusion: ![[command/obsidian/nested-transclusion#Heading in List Item]] +^D +[ Para + [ Str "List" + , Space + , Str "nested" + , Space + , Str "heading" + , Space + , Str "transclusion:" + , Space + , Str "Heading" + , Space + , Str "in" + , Space + , Str "List" + , Space + , Str "Item" + , LineBreak + , Str "This" + , Space + , Str "heading" + , Space + , Str "is" + , Space + , Str "nested" + , Space + , Str "inside" + , Space + , Str "a" + , Space + , Str "list" + , Space + , Str "item." + , LineBreak + , Str "Content" + , Space + , Str "under" + , Space + , Str "the" + , Space + , Str "list" + , Space + , Str "heading." + , LineBreak + , Str "A" + , Space + , Str "block" + , Space + , Str "with" + , Space + , Str "an" + , Space + , Str "ID" + , Space + , Str "in" + , Space + , Str "a" + , Space + , Str "list." + ] +] +``` + +``` +% pandoc -f obsidian -t native +List nested block transclusion: ![[command/obsidian/nested-transclusion#^list-block-id]] +^D +[ Para + [ Str "List" + , Space + , Str "nested" + , Space + , Str "block" + , Space + , Str "transclusion:" + , Space + , Str "A" + , Space + , Str "block" + , Space + , Str "with" + , Space + , Str "an" + , Space + , Str "ID" + , Space + , Str "in" + , Space + , Str "a" + , Space + , Str "list." + ] +] +``` + diff --git a/test/command/obsidian/nested-transclusion.md b/test/command/obsidian/nested-transclusion.md new file mode 100644 index 000000000000..5e1b656e2632 --- /dev/null +++ b/test/command/obsidian/nested-transclusion.md @@ -0,0 +1,31 @@ +This is a test file for nested transclusions. + +## Main Section + +Content before the nested structure. + +> ### Nested Heading in Blockquote +> +> This heading is nested inside a blockquote for testing nested heading transclusions. +> +> Some content under the nested heading. +> +> A paragraph with a nested block ID. ^nested-block-id + +More content after the blockquote. + +## Middle Section + +Some content in the middle section. + +- ### Heading in List Item + + This heading is nested inside a list item. + + Content under the list heading. + + A block with an ID in a list. ^list-block-id + +## Final Section + +Regular content at the end. diff --git a/test/command/obsidian/transclusion.md b/test/command/obsidian/transclusion.md new file mode 100644 index 000000000000..6d8b0feaaf70 --- /dev/null +++ b/test/command/obsidian/transclusion.md @@ -0,0 +1,11 @@ +This is the content of the Obsidian transclusion test file. + +## Introduction + +This is the introduction section with some content for heading transclusions. + +A paragraph with a block ID for testing block transclusions. ^my-id + +## Another Section + +More content here. \ No newline at end of file