Skip to content

Commit 3e881d0

Browse files
committed
don't use commonmark
1 parent f063ff3 commit 3e881d0

File tree

3 files changed

+42
-18
lines changed

3 files changed

+42
-18
lines changed

src/Text/Pandoc/Extensions.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -550,7 +550,7 @@ getAllExtensions f = universalExtensions <> getAll f
550550
getAll "markdown_mmd" = allMarkdownExtensions
551551
getAll "markdown_github" = allMarkdownExtensions
552552
getAll "markdown" = allMarkdownExtensions
553-
getAll "obsidian" = getAll "commonmark" <> extensionsFromList
553+
getAll "obsidian" = allMarkdownExtensions <> extensionsFromList
554554
[ Ext_ascii_identifiers
555555
, Ext_alerts
556556
, Ext_autolink_bare_uris

src/Text/Pandoc/Readers.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -141,7 +141,7 @@ readers = [("native" , TextReader readNative)
141141
,("creole" , TextReader readCreole)
142142
,("dokuwiki" , TextReader readDokuWiki)
143143
,("gfm" , TextReader readCommonMark)
144-
,("obsidian" , TextReader readCommonMark)
144+
,("obsidian" , TextReader readMarkdown)
145145
,("rst" , TextReader readRST)
146146
,("mediawiki" , TextReader readMediaWiki)
147147
,("vimwiki" , TextReader readVimwiki)

src/Text/Pandoc/Readers/Markdown.hs

Lines changed: 40 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -2045,17 +2045,23 @@ rebasePath pos path = do
20452045
image :: PandocMonad m => MarkdownParser m (F Inlines)
20462046
image = try $ do
20472047
char '!'
2048-
wikilinkTransclusion <|>
2049-
do (lab,raw) <- reference
2050-
defaultExt <- getOption readerDefaultImageExtension
2051-
let constructor attr' src
2052-
| "data:" `T.isPrefixOf` src = B.imageWith attr' src -- see #9118
2053-
| otherwise =
2054-
case takeExtension (T.unpack src) of
2055-
"" -> B.imageWith attr' (T.pack $ addExtension (T.unpack src)
2056-
$ T.unpack defaultExt)
2057-
_ -> B.imageWith attr' src
2058-
regLink constructor lab <|> referenceLink constructor (lab, "!" <> raw)
2048+
-- First try wikilink transclusion
2049+
(try wikilinkTransclusion) <|>
2050+
-- Then try regular image parsing
2051+
(do (lab,raw) <- reference
2052+
defaultExt <- getOption readerDefaultImageExtension
2053+
let constructor attr' src
2054+
| "data:" `T.isPrefixOf` src = B.imageWith attr' src -- see #9118
2055+
| otherwise =
2056+
case takeExtension (T.unpack src) of
2057+
"" -> B.imageWith attr' (T.pack $ addExtension (T.unpack src)
2058+
$ T.unpack defaultExt)
2059+
_ -> B.imageWith attr' src
2060+
regLink constructor lab <|> referenceLink constructor (lab, "!" <> raw)) <|>
2061+
-- Fallback: if it looks like ![[...]], create a span with literal text
2062+
(do try $ string "[["
2063+
content <- many1TillChar anyChar (try $ string "]]")
2064+
return $ return $ B.spanWith ("", [], []) (B.str $ "![[" <> content <> "]]"))
20592065

20602066
wikilinkTransclusion :: PandocMonad m => MarkdownParser m (F Inlines)
20612067
wikilinkTransclusion = try $ do
@@ -2075,7 +2081,7 @@ wikilinkTransclusion = try $ do
20752081
currentDir <- takeDirectory . sourceName <$> getPosition
20762082
let filename = T.unpack url
20772083
-- Support relative paths like "Folder/File" by using currentDir as base
2078-
insertIncludedFile (fmap B.toInlines <$> parseBlocks) toSources [currentDir] filename Nothing Nothing
2084+
insertIncludedFile parseTranscludedInlines toSources [currentDir] filename Nothing Nothing
20792085
else do
20802086
let fragmentContent = T.drop 1 fragment -- Remove the '#' prefix
20812087
if T.take 1 fragmentContent == "^"
@@ -2086,15 +2092,15 @@ wikilinkTransclusion = try $ do
20862092
let filename = T.unpack url <> ".md" -- Assume .md extension for block transclusion
20872093
let blockId = T.drop 1 fragmentContent -- Remove the '^' prefix
20882094
-- Support relative paths like "Folder/File" by using currentDir as base
2089-
insertIncludedFile (extractBlockById blockId <$> parseBlocks) toSources [currentDir] filename Nothing Nothing
2095+
insertIncludedFile (parseBlockTransclusion blockId) toSources [currentDir] filename Nothing Nothing
20902096
else do
20912097
-- Heading transclusion: ![[File#Heading]]
20922098
guardEnabled Ext_wikilink_heading_transclusions
20932099
currentDir <- takeDirectory . sourceName <$> getPosition
20942100
let filename = T.unpack url <> ".md" -- Assume .md extension for heading transclusion
20952101
let headingText = fragmentContent
20962102
-- Support relative paths like "Folder/File" by using currentDir as base
2097-
insertIncludedFile (extractHeadingById headingText <$> parseBlocks) toSources [currentDir] filename Nothing Nothing
2103+
insertIncludedFile (parseHeadingTransclusion headingText) toSources [currentDir] filename Nothing Nothing
20982104

20992105
note :: PandocMonad m => MarkdownParser m (F Inlines)
21002106
note = try $ do
@@ -2408,7 +2414,7 @@ doubleQuoted = do
24082414
extractBlockById :: Text -> Blocks -> F Inlines
24092415
extractBlockById targetId blocks =
24102416
case findBlockById targetId (B.toList blocks) of
2411-
Just block -> return $ B.toInlines $ B.fromList [block]
2417+
Just block -> return $ blocksToInlines' [block]
24122418
Nothing -> return mempty
24132419

24142420
-- | Find a block with a specific ID in a list of blocks
@@ -2428,7 +2434,25 @@ extractHeadingById :: Text -> Blocks -> F Inlines
24282434
extractHeadingById targetHeading blocks =
24292435
case extractContentUnderHeading targetHeading (B.toList blocks) of
24302436
[] -> return mempty
2431-
content -> return $ B.toInlines $ B.fromList content
2437+
content -> return $ blocksToInlines' content
2438+
2439+
-- | Parse a file and convert all blocks to inlines for transclusion
2440+
parseTranscludedInlines :: PandocMonad m => MarkdownParser m (F Inlines)
2441+
parseTranscludedInlines = do
2442+
blocks <- parseBlocks
2443+
return $ fmap (blocksToInlines' . B.toList) blocks
2444+
2445+
-- | Parse a file and extract a specific block by ID for transclusion
2446+
parseBlockTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines)
2447+
parseBlockTransclusion blockId = do
2448+
blocks <- parseBlocks
2449+
return $ blocks >>= extractBlockById blockId
2450+
2451+
-- | Parse a file and extract content under a specific heading for transclusion
2452+
parseHeadingTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines)
2453+
parseHeadingTransclusion headingText = do
2454+
blocks <- parseBlocks
2455+
return $ blocks >>= extractHeadingById headingText
24322456

24332457
-- | Extract all content under a heading until the next heading of same or higher level
24342458
extractContentUnderHeading :: Text -> [Block] -> [Block]

0 commit comments

Comments
 (0)