Skip to content

Commit 1a2ae20

Browse files
committed
don't use commonmark
1 parent a23ffdd commit 1a2ae20

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
@@ -2028,17 +2028,23 @@ rebasePath pos path = do
20282028
image :: PandocMonad m => MarkdownParser m (F Inlines)
20292029
image = try $ do
20302030
char '!'
2031-
wikilinkTransclusion <|>
2032-
do (lab,raw) <- reference
2033-
defaultExt <- getOption readerDefaultImageExtension
2034-
let constructor attr' src
2035-
| "data:" `T.isPrefixOf` src = B.imageWith attr' src -- see #9118
2036-
| otherwise =
2037-
case takeExtension (T.unpack src) of
2038-
"" -> B.imageWith attr' (T.pack $ addExtension (T.unpack src)
2039-
$ T.unpack defaultExt)
2040-
_ -> B.imageWith attr' src
2041-
regLink constructor lab <|> referenceLink constructor (lab, "!" <> raw)
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 <> "]]"))
20422048

20432049
wikilinkTransclusion :: PandocMonad m => MarkdownParser m (F Inlines)
20442050
wikilinkTransclusion = try $ do
@@ -2058,7 +2064,7 @@ wikilinkTransclusion = try $ do
20582064
currentDir <- takeDirectory . sourceName <$> getPosition
20592065
let filename = T.unpack url
20602066
-- Support relative paths like "Folder/File" by using currentDir as base
2061-
insertIncludedFile (fmap B.toInlines <$> parseBlocks) toSources [currentDir] filename Nothing Nothing
2067+
insertIncludedFile parseTranscludedInlines toSources [currentDir] filename Nothing Nothing
20622068
else do
20632069
let fragmentContent = T.drop 1 fragment -- Remove the '#' prefix
20642070
if T.take 1 fragmentContent == "^"
@@ -2069,15 +2075,15 @@ wikilinkTransclusion = try $ do
20692075
let filename = T.unpack url <> ".md" -- Assume .md extension for block transclusion
20702076
let blockId = T.drop 1 fragmentContent -- Remove the '^' prefix
20712077
-- Support relative paths like "Folder/File" by using currentDir as base
2072-
insertIncludedFile (extractBlockById blockId <$> parseBlocks) toSources [currentDir] filename Nothing Nothing
2078+
insertIncludedFile (parseBlockTransclusion blockId) toSources [currentDir] filename Nothing Nothing
20732079
else do
20742080
-- Heading transclusion: ![[File#Heading]]
20752081
guardEnabled Ext_wikilink_heading_transclusions
20762082
currentDir <- takeDirectory . sourceName <$> getPosition
20772083
let filename = T.unpack url <> ".md" -- Assume .md extension for heading transclusion
20782084
let headingText = fragmentContent
20792085
-- Support relative paths like "Folder/File" by using currentDir as base
2080-
insertIncludedFile (extractHeadingById headingText <$> parseBlocks) toSources [currentDir] filename Nothing Nothing
2086+
insertIncludedFile (parseHeadingTransclusion headingText) toSources [currentDir] filename Nothing Nothing
20812087

20822088
note :: PandocMonad m => MarkdownParser m (F Inlines)
20832089
note = try $ do
@@ -2390,7 +2396,7 @@ doubleQuoted = do
23902396
extractBlockById :: Text -> Blocks -> F Inlines
23912397
extractBlockById targetId blocks =
23922398
case findBlockById targetId (B.toList blocks) of
2393-
Just block -> return $ B.toInlines $ B.fromList [block]
2399+
Just block -> return $ blocksToInlines' [block]
23942400
Nothing -> return mempty
23952401

23962402
-- | Find a block with a specific ID in a list of blocks
@@ -2410,7 +2416,25 @@ extractHeadingById :: Text -> Blocks -> F Inlines
24102416
extractHeadingById targetHeading blocks =
24112417
case extractContentUnderHeading targetHeading (B.toList blocks) of
24122418
[] -> return mempty
2413-
content -> return $ B.toInlines $ B.fromList content
2419+
content -> return $ blocksToInlines' content
2420+
2421+
-- | Parse a file and convert all blocks to inlines for transclusion
2422+
parseTranscludedInlines :: PandocMonad m => MarkdownParser m (F Inlines)
2423+
parseTranscludedInlines = do
2424+
blocks <- parseBlocks
2425+
return $ fmap (blocksToInlines' . B.toList) blocks
2426+
2427+
-- | Parse a file and extract a specific block by ID for transclusion
2428+
parseBlockTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines)
2429+
parseBlockTransclusion blockId = do
2430+
blocks <- parseBlocks
2431+
return $ blocks >>= extractBlockById blockId
2432+
2433+
-- | Parse a file and extract content under a specific heading for transclusion
2434+
parseHeadingTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines)
2435+
parseHeadingTransclusion headingText = do
2436+
blocks <- parseBlocks
2437+
return $ blocks >>= extractHeadingById headingText
24142438

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

0 commit comments

Comments
 (0)