diff --git a/src/Text/Pandoc/Parsing/State.hs b/src/Text/Pandoc/Parsing/State.hs index de7bab7d853e..547ddaabb891 100644 --- a/src/Text/Pandoc/Parsing/State.hs +++ b/src/Text/Pandoc/Parsing/State.hs @@ -186,4 +186,4 @@ toKey = Key . T.toLower . T.unwords . T.words . unbracket type KeyTable = M.Map Key (Target, Attr) -type SubstTable = M.Map Key Inlines +type SubstTable = M.Map Key Blocks diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 0b4398ae28aa..e68756e355e2 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -163,10 +163,28 @@ parseRST = do else (blocks, meta) let reversedNotes = stateNotes state updateState $ \s -> s { stateNotes = reverse reversedNotes } - doc <- walkM resolveReferences (Pandoc meta' (blocks' ++ refBlock)) + doc <- walkM resolveReferences =<< + walkM resolveBlockSubstitutions + (Pandoc meta' (blocks' ++ refBlock)) reportLogMessages return doc +resolveBlockSubstitutions :: PandocMonad m => Block -> RSTParser m Block +resolveBlockSubstitutions x@(Para [Link _attr _ (s,_)]) + | Just ref <- T.stripPrefix "##SUBST##" s = do + substTable <- stateSubstitutions <$> getState + let key@(Key key') = toKey $ stripFirstAndLast ref + case M.lookup key substTable of + Nothing -> do + pos <- getPosition + logMessage $ ReferenceNotFound (tshow key') pos + return x + Just target -> case + B.toList target of + [bl] -> return bl + bls -> return $ Div nullAttr bls +resolveBlockSubstitutions x = return x + resolveReferences :: PandocMonad m => Inline -> RSTParser m Inline resolveReferences x@(Link _ ils (s,_)) | Just ref <- T.stripPrefix "##REF##" s = do @@ -218,8 +236,9 @@ resolveReferences x@(Link _ ils (s,_)) return x Just target -> case B.toList target of - [t] -> return t - ts -> return $ Span nullAttr ts + [Para [t]] -> return t + [Para xs] -> return $ Span nullAttr xs + bls -> return $ Span nullAttr $ blocksToInlines bls | otherwise = return x resolveReferences x = return x @@ -1202,17 +1221,16 @@ substKey = try $ do (alt,ref) <- withRaw $ trimInlines . mconcat <$> enclosed (char '|') (char '|') inline res <- B.toList <$> directive' - il <- case res of + bls <- case res of -- use alt unless :alt: attribute on image: [Para [Image attr [Str "image"] (src,tit)]] -> - return $ B.imageWith attr src tit alt + return $ B.para $ B.imageWith attr src tit alt [Para [Link _ [Image attr [Str "image"] (src,tit)] (src',tit')]] -> - return $ B.link src' tit' (B.imageWith attr src tit alt) - [Para ils] -> return $ B.fromList ils - _ -> mzero + return $ B.para $ B.link src' tit' (B.imageWith attr src tit alt) + _ -> return $ B.fromList res let key = toKey $ stripFirstAndLast ref updateState $ \s -> s{ stateSubstitutions = - M.insert key il $ stateSubstitutions s } + M.insert key bls $ stateSubstitutions s } anonymousKey :: PandocMonad m => RSTParser m () anonymousKey = try $ do diff --git a/test/command/rst_block_subst.md b/test/command/rst_block_subst.md new file mode 100644 index 000000000000..cc284b27f951 --- /dev/null +++ b/test/command/rst_block_subst.md @@ -0,0 +1,19 @@ +``` +% pandoc -f rst -t native +|figure05| + +.. |figure05| figure:: img/dummy.png + + capt +[ Figure + ( "" , [] , [] ) + (Caption Nothing [ Plain [ Str "capt" ] ]) + [ Plain + [ Image + ( "" , [] , [] ) + [ Str "img/dummy.png" ] + ( "img/dummy.png" , "" ) + ] + ] +] +```