@@ -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
@@ -467,12 +467,12 @@ addBlockId (id', classes, kvs) st =
467467 Nothing -> (id', classes, kvs)
468468 Just bid -> (if T. null id' then bid else id', classes, kvs)
469469
470- blockTransclusion :: PandocMonad m => MarkdownParser m (F Blocks )
471- blockTransclusion = try $ do
472- guardEnabled Ext_wikilink_block_transclusions
473- char ' !'
474- res <- wikilink B. linkWith
475- return $ B. divWith (" " , [" block-transclusion" ], [] ) . B. para <$> res
470+ -- blockTransclusion :: PandocMonad m => MarkdownParser m (F Blocks)
471+ -- blockTransclusion = try $ do
472+ -- guardEnabled Ext_wikilink_block_transclusions
473+ -- char '!'
474+ -- res <- wikilink B.linkWith
475+ -- return $ B.divWith ("", ["block-transclusion"], []) . B.para <$> res
476476
477477parseBlocks :: PandocMonad m => MarkdownParser m (F Blocks )
478478parseBlocks = mconcat <$> manyTill block eof
@@ -2051,7 +2051,7 @@ wikilinkTransclusion = try $ do
20512051 string " [[" *> notFollowedBy' (char ' [' )
20522052 raw <- many1TillChar anyChar (try $ string " ]]" )
20532053 titleAfter <- (True <$ guardEnabled Ext_wikilinks_title_after_pipe ) <|> pure False
2054- let (title' , target') = case T. break (== ' |' ) raw of
2054+ let (_ , target') = case T. break (== ' |' ) raw of
20552055 (before, " " ) -> (before, before)
20562056 (before, after)
20572057 | titleAfter -> (T. drop 1 after, before)
@@ -2073,9 +2073,9 @@ wikilinkTransclusion = try $ do
20732073 guardEnabled Ext_wikilink_block_transclusions
20742074 currentDir <- takeDirectory . sourceName <$> getPosition
20752075 let filename = T. unpack url <> " .md" -- Assume .md extension for block transclusion
2076- let blockId = T. drop 1 fragmentContent -- Remove the '^' prefix
2076+ let blockIdText = T. drop 1 fragmentContent -- Remove the '^' prefix
20772077 -- Support relative paths like "Folder/File" by using currentDir as base
2078- insertIncludedFile (parseBlockTransclusion blockId ) toSources [currentDir] filename Nothing Nothing
2078+ insertIncludedFile (parseBlockTransclusion blockIdText ) toSources [currentDir] filename Nothing Nothing
20792079 else do
20802080 -- Heading transclusion: ![[File#Heading]]
20812081 guardEnabled Ext_wikilink_heading_transclusions
@@ -2396,19 +2396,19 @@ doubleQuoted = do
23962396extractBlockById :: Text -> Blocks -> Inlines
23972397extractBlockById targetId blocks =
23982398 case findBlockById targetId (B. toList blocks) of
2399- Just block -> blocksToInlines' [block]
2399+ Just (Div _ contents) -> blocksToInlines' contents -- Extract content from Div wrapper
2400+ Just blk -> blocksToInlines' [blk]
24002401 Nothing -> mempty
24012402
24022403-- | Find a block with a specific ID in a list of blocks
24032404findBlockById :: Text -> [Block ] -> Maybe Block
24042405findBlockById targetId = go
24052406 where
24062407 go [] = Nothing
2407- go (block: rest) =
2408- case block of
2409- Div (bid, _, _) [Para _] | bid == targetId -> Just block
2410- Div (bid, _, _) _ | bid == targetId -> Just block
2411- Header _ (bid, _, _) _ | bid == targetId -> Just block
2408+ go (blk: rest) =
2409+ case blk of
2410+ Div (bid, _, _) _ | bid == targetId -> Just blk
2411+ Header _ (bid, _, _) _ | bid == targetId -> Just blk
24122412 _ -> go rest
24132413
24142414-- | Extract content under a specific heading from a list of blocks
@@ -2426,9 +2426,9 @@ parseTranscludedInlines = do
24262426
24272427-- | Parse a file and extract a specific block by ID for transclusion
24282428parseBlockTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines )
2429- parseBlockTransclusion blockId = do
2429+ parseBlockTransclusion blockIdText = do
24302430 blocks <- parseBlocks
2431- return $ fmap (extractBlockById blockId ) blocks
2431+ return $ fmap (extractBlockById blockIdText ) blocks
24322432
24332433-- | Parse a file and extract content under a specific heading for transclusion
24342434parseHeadingTransclusion :: PandocMonad m => Text -> MarkdownParser m (F Inlines )
@@ -2441,24 +2441,24 @@ extractContentUnderHeading :: Text -> [Block] -> [Block]
24412441extractContentUnderHeading targetHeading = go False 0
24422442 where
24432443 go _found _level [] = []
2444- go found level (block : rest) =
2445- case block of
2446- Header lvl _ inlines
2447- | stringify inlines == targetHeading ->
2444+ go found level (blk : rest) =
2445+ case blk of
2446+ Header lvl _ ils
2447+ | stringify ils == targetHeading ->
24482448 -- Found target heading, start collecting content
2449- block : go True lvl rest
2449+ blk : go True lvl rest
24502450 | found && lvl <= level ->
24512451 -- Found heading of same or higher level, stop collecting
24522452 []
24532453 | found ->
24542454 -- Collecting content under target heading
2455- block : go True level rest
2455+ blk : go True level rest
24562456 | otherwise ->
24572457 -- Haven't found target heading yet
24582458 go False level rest
24592459 _ | found ->
24602460 -- Collecting content under target heading
2461- block : go True level rest
2461+ blk : go True level rest
24622462 | otherwise ->
24632463 -- Haven't found target heading yet
24642464 go False level rest
0 commit comments