@@ -23,7 +23,7 @@ module Text.Pandoc.Readers.Markdown (
2323import Control.Monad
2424import Control.Monad.Except (throwError )
2525import Data.Bifunctor (second )
26- import Data.Char (isAlphaNum , isPunctuation , isSpace )
26+ import Data.Char (isAlphaNum , isPunctuation , isSpace , toLower )
2727import Data.List (transpose , elemIndex , sortOn , foldl' )
2828import qualified Data.Map as M
2929import Data.Maybe
@@ -1518,7 +1518,7 @@ inline = do
15181518 ' *' -> strongOrEmph
15191519 ' ^' -> superscript <|> inlineNote <|> blockId -- in this order bc ^[link](/foo)^
15201520 ' [' -> note <|> cite <|> bracketedSpan <|> wikilink B. linkWith <|> link
1521- ' !' -> image
1521+ ' !' -> transclusion <|> image
15221522 ' $' -> math
15231523 ' ~' -> strikeout <|> subscript
15241524 ' =' -> mark
@@ -2025,29 +2025,9 @@ rebasePath pos path = do
20252025 " ." -> path
20262026 d -> T. pack d <> " /" <> path
20272027
2028- image :: PandocMonad m => MarkdownParser m (F Inlines )
2029- image = try $ do
2028+ transclusion :: PandocMonad m => MarkdownParser m (F Inlines )
2029+ transclusion = try $ do
20302030 char ' !'
2031- -- First try wikilink transclusion
2032- (try wikilinkTransclusion) <|>
2033- -- Then try regular image parsing
2034- (do (lab,raw) <- reference
2035- defaultExt <- getOption readerDefaultImageExtension
2036- let constructor attr' src
2037- | " data:" `T.isPrefixOf` src = B. imageWith attr' src -- see #9118
2038- | otherwise =
2039- case takeExtension (T. unpack src) of
2040- " " -> B. imageWith attr' (T. pack $ addExtension (T. unpack src)
2041- $ T. unpack defaultExt)
2042- _ -> B. imageWith attr' src
2043- regLink constructor lab <|> referenceLink constructor (lab, " !" <> raw)) <|>
2044- -- Fallback: if it looks like ![[...]], create a span with literal text
2045- (do try $ string " [["
2046- content <- many1TillChar anyChar (try $ string " ]]" )
2047- return $ return $ B. spanWith (" " , [] , [] ) (B. str $ " ![[" <> content <> " ]]" ))
2048-
2049- wikilinkTransclusion :: PandocMonad m => MarkdownParser m (F Inlines )
2050- wikilinkTransclusion = try $ do
20512031 string " [[" *> notFollowedBy' (char ' [' )
20522032 raw <- many1TillChar anyChar (try $ string " ]]" )
20532033 titleAfter <- (True <$ guardEnabled Ext_wikilinks_title_after_pipe ) <|> pure False
@@ -2058,32 +2038,65 @@ wikilinkTransclusion = try $ do
20582038 | otherwise -> (before, T. drop 1 after)
20592039 let (url, fragment) = T. break (== ' #' ) target'
20602040 guard $ T. all (`notElem` [' \n ' ,' \r ' ,' \f ' ,' \t ' ]) url
2061- if T. null fragment
2062- then do
2063- guardEnabled Ext_wikilink_transclusions
2064- currentDir <- takeDirectory . sourceName <$> getPosition
2065- let filename = T. unpack url <> " .md" -- Assume .md extension for transclusion
2066- -- Support relative paths like "Folder/File" by using currentDir as base
2067- insertIncludedFile parseTranscludedInlines toSources [currentDir] filename Nothing Nothing
2068- else do
2069- let fragmentContent = T. drop 1 fragment -- Remove the '#' prefix
2070- if T. take 1 fragmentContent == " ^"
2071- then do
2072- -- Block ID transclusion: ![[File#^block-id]]
2073- guardEnabled Ext_wikilink_block_transclusions
2074- currentDir <- takeDirectory . sourceName <$> getPosition
2075- let filename = T. unpack url <> " .md" -- Assume .md extension for block transclusion
2076- let blockIdText = T. drop 1 fragmentContent -- Remove the '^' prefix
2077- -- Support relative paths like "Folder/File" by using currentDir as base
2078- insertIncludedFile (parseBlockTransclusion blockIdText) toSources [currentDir] filename Nothing Nothing
2079- else do
2080- -- Heading transclusion: ![[File#Heading]]
2081- guardEnabled Ext_wikilink_heading_transclusions
2082- currentDir <- takeDirectory . sourceName <$> getPosition
2083- let filename = T. unpack url <> " .md" -- Assume .md extension for heading transclusion
2084- let headingText = fragmentContent
2085- -- Support relative paths like "Folder/File" by using currentDir as base
2086- insertIncludedFile (parseHeadingTransclusion headingText) toSources [currentDir] filename Nothing Nothing
2041+
2042+ let urlStr = T. unpack url
2043+ let ext = map toLower $ takeExtension urlStr
2044+ let hasExtension = not (null ext)
2045+ let isMdFile = ext == " .md"
2046+
2047+ -- Check if any transclusion extensions are enabled
2048+ hasTransclusions <- (True <$ guardEnabled Ext_wikilink_transclusions ) <|>
2049+ (True <$ guardEnabled Ext_wikilink_block_transclusions ) <|>
2050+ (True <$ guardEnabled Ext_wikilink_heading_transclusions ) <|>
2051+ return False
2052+
2053+ if hasTransclusions && (not hasExtension || isMdFile)
2054+ then -- Handle as transclusion (no extension or .md extension)
2055+ if T. null fragment
2056+ then do
2057+ guardEnabled Ext_wikilink_transclusions
2058+ currentDir <- takeDirectory . sourceName <$> getPosition
2059+ -- Only add .md extension if the file doesn't already have an extension
2060+ let filename = if null (takeExtension urlStr)
2061+ then T. unpack url <> " .md"
2062+ else T. unpack url
2063+ -- Support relative paths like "Folder/File" by using currentDir as base
2064+ insertIncludedFile parseTranscludedInlines toSources [currentDir] filename Nothing Nothing
2065+ else do
2066+ let fragmentContent = T. drop 1 fragment -- Remove the '#' prefix
2067+ if T. take 1 fragmentContent == " ^"
2068+ then do
2069+ -- Block ID transclusion: ![[File#^block-id]]
2070+ guardEnabled Ext_wikilink_block_transclusions
2071+ currentDir <- takeDirectory . sourceName <$> getPosition
2072+ let filename = T. unpack url <> " .md" -- Assume .md extension for block transclusion
2073+ let blockIdText = T. drop 1 fragmentContent -- Remove the '^' prefix
2074+ -- Support relative paths like "Folder/File" by using currentDir as base
2075+ insertIncludedFile (parseBlockTransclusion blockIdText) toSources [currentDir] filename Nothing Nothing
2076+ else do
2077+ -- Heading transclusion: ![[File#Heading]]
2078+ guardEnabled Ext_wikilink_heading_transclusions
2079+ currentDir <- takeDirectory . sourceName <$> getPosition
2080+ let filename = T. unpack url <> " .md" -- Assume .md extension for heading transclusion
2081+ let headingText = fragmentContent
2082+ -- Support relative paths like "Folder/File" by using currentDir as base
2083+ insertIncludedFile (parseHeadingTransclusion headingText) toSources [currentDir] filename Nothing Nothing
2084+ else -- Handle as image/embed (has non-.md extension or transclusions disabled)
2085+ return $ return $ B. imageWith (" " , [" wikilink" ], [] ) url " " (B. text target')
2086+
2087+ image :: PandocMonad m => MarkdownParser m (F Inlines )
2088+ image = try $ do
2089+ char ' !'
2090+ (lab,raw) <- reference
2091+ defaultExt <- getOption readerDefaultImageExtension
2092+ let constructor attr' src
2093+ | " data:" `T.isPrefixOf` src = B. imageWith attr' src -- see #9118
2094+ | otherwise =
2095+ case takeExtension (T. unpack src) of
2096+ " " -> B. imageWith attr' (T. pack $ addExtension (T. unpack src)
2097+ $ T. unpack defaultExt)
2098+ _ -> B. imageWith attr' src
2099+ regLink constructor lab <|> referenceLink constructor (lab, " !" <> raw)
20872100
20882101note :: PandocMonad m => MarkdownParser m (F Inlines )
20892102note = try $ do
0 commit comments