@@ -24,7 +24,7 @@ import Control.Monad
2424import Control.Monad.Except (throwError )
2525import Data.Bifunctor (second )
2626import Data.Char (isAlphaNum , isPunctuation , isSpace )
27- import Data.List (transpose , elemIndex , sortOn , foldl' )
27+ import Data.List (transpose , elemIndex , sortOn )
2828import qualified Data.Map as M
2929import Data.Maybe
3030import qualified Data.Set as Set
@@ -486,12 +486,12 @@ addBlockId (id', classes, kvs) st =
486486 Nothing -> (id', classes, kvs)
487487 Just bid -> (if T. null id' then bid else id', classes, kvs)
488488
489- blockTransclusion :: PandocMonad m => MarkdownParser m (F Blocks )
490- blockTransclusion = try $ do
491- guardEnabled Ext_wikilink_block_transclusions
492- char ' !'
493- res <- wikilink B. linkWith
494- return $ B. divWith (" " , [" block-transclusion" ], [] ) . B. para <$> res
489+ -- blockTransclusion :: PandocMonad m => MarkdownParser m (F Blocks)
490+ -- blockTransclusion = try $ do
491+ -- guardEnabled Ext_wikilink_block_transclusions
492+ -- char '!'
493+ -- res <- wikilink B.linkWith
494+ -- return $ B.divWith ("", ["block-transclusion"], []) . B.para <$> res
495495
496496parseBlocks :: PandocMonad m => MarkdownParser m (F Blocks )
497497parseBlocks = mconcat <$> manyTill block eof
@@ -2068,7 +2068,7 @@ wikilinkTransclusion = try $ do
20682068 string " [[" *> notFollowedBy' (char ' [' )
20692069 raw <- many1TillChar anyChar (try $ string " ]]" )
20702070 titleAfter <- (True <$ guardEnabled Ext_wikilinks_title_after_pipe ) <|> pure False
2071- let (title' , target') = case T. break (== ' |' ) raw of
2071+ let (_ , target') = case T. break (== ' |' ) raw of
20722072 (before, " " ) -> (before, before)
20732073 (before, after)
20742074 | titleAfter -> (T. drop 1 after, before)
@@ -2090,9 +2090,9 @@ wikilinkTransclusion = try $ do
20902090 guardEnabled Ext_wikilink_block_transclusions
20912091 currentDir <- takeDirectory . sourceName <$> getPosition
20922092 let filename = T. unpack url <> " .md" -- Assume .md extension for block transclusion
2093- let blockId = T. drop 1 fragmentContent -- Remove the '^' prefix
2093+ let blockIdText = T. drop 1 fragmentContent -- Remove the '^' prefix
20942094 -- Support relative paths like "Folder/File" by using currentDir as base
2095- insertIncludedFile (parseBlockTransclusion blockId ) toSources [currentDir] filename Nothing Nothing
2095+ insertIncludedFile (parseBlockTransclusion blockIdText ) toSources [currentDir] filename Nothing Nothing
20962096 else do
20972097 -- Heading transclusion: ![[File#Heading]]
20982098 guardEnabled Ext_wikilink_heading_transclusions
@@ -2414,19 +2414,19 @@ doubleQuoted = do
24142414extractBlockById :: Text -> Blocks -> Inlines
24152415extractBlockById targetId blocks =
24162416 case findBlockById targetId (B. toList blocks) of
2417- Just block -> blocksToInlines' [block]
2417+ Just (Div _ contents) -> blocksToInlines' contents -- Extract content from Div wrapper
2418+ Just blk -> blocksToInlines' [blk]
24182419 Nothing -> mempty
24192420
24202421-- | Find a block with a specific ID in a list of blocks
24212422findBlockById :: Text -> [Block ] -> Maybe Block
24222423findBlockById targetId = go
24232424 where
24242425 go [] = Nothing
2425- go (block: rest) =
2426- case block of
2427- Div (bid, _, _) [Para _] | bid == targetId -> Just block
2428- Div (bid, _, _) _ | bid == targetId -> Just block
2429- Header _ (bid, _, _) _ | bid == targetId -> Just block
2426+ go (blk: rest) =
2427+ case blk of
2428+ Div (bid, _, _) _ | bid == targetId -> Just blk
2429+ Header _ (bid, _, _) _ | bid == targetId -> Just blk
24302430 _ -> go rest
24312431
24322432-- | Extract content under a specific heading from a list of blocks
@@ -2444,9 +2444,9 @@ parseTranscludedInlines = do
24442444
24452445-- | Parse a file and extract a specific block by ID for transclusion
24462446parseBlockTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines )
2447- parseBlockTransclusion blockId = do
2447+ parseBlockTransclusion blockIdText = do
24482448 blocks <- parseBlocks
2449- return $ fmap (extractBlockById blockId ) blocks
2449+ return $ fmap (extractBlockById blockIdText ) blocks
24502450
24512451-- | Parse a file and extract content under a specific heading for transclusion
24522452parseHeadingTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines )
@@ -2459,24 +2459,24 @@ extractContentUnderHeading :: Text -> [Block] -> [Block]
24592459extractContentUnderHeading targetHeading = go False 0
24602460 where
24612461 go _found _level [] = []
2462- go found level (block : rest) =
2463- case block of
2464- Header lvl _ inlines
2465- | stringify inlines == targetHeading ->
2462+ go found level (blk : rest) =
2463+ case blk of
2464+ Header lvl _ ils
2465+ | stringify ils == targetHeading ->
24662466 -- Found target heading, start collecting content
2467- block : go True lvl rest
2467+ blk : go True lvl rest
24682468 | found && lvl <= level ->
24692469 -- Found heading of same or higher level, stop collecting
24702470 []
24712471 | found ->
24722472 -- Collecting content under target heading
2473- block : go True level rest
2473+ blk : go True level rest
24742474 | otherwise ->
24752475 -- Haven't found target heading yet
24762476 go False level rest
24772477 _ | found ->
24782478 -- Collecting content under target heading
2479- block : go True level rest
2479+ blk : go True level rest
24802480 | otherwise ->
24812481 -- Haven't found target heading yet
24822482 go False level rest
0 commit comments