@@ -32,6 +32,7 @@ import Data.Maybe (fromMaybe, maybeToList)
32
32
import qualified Data.Set as Set
33
33
import Data.Text (Text )
34
34
import qualified Data.Text as T
35
+ import Data.Either (partitionEithers )
35
36
import Skylighting (defaultSyntaxMap )
36
37
import System.FilePath (addExtension , replaceExtension , takeExtension )
37
38
import Text.Collate.Lang (renderLang )
@@ -935,8 +936,8 @@ environments = M.union (tableEnvironments blocks inline) $
935
936
, (" letter" , env " letter" letterContents)
936
937
, (" minipage" , env " minipage" $
937
938
skipopts *> spaces *> optional braced *> spaces *> blocks)
938
- , (" figure" , env " figure" $ skipopts *> figure)
939
- , (" subfigure" , env " subfigure" $ skipopts *> tok *> figure)
939
+ , (" figure" , env " figure" $ skipopts *> Text.Pandoc.Readers.LaTeX. figure)
940
+ , (" subfigure" , env " subfigure" $ skipopts *> tok *> Text.Pandoc.Readers.LaTeX. figure)
940
941
, (" center" , divWith (" " , [" center" ], [] ) <$> env " center" blocks)
941
942
, (" quote" , blockQuote <$> env " quote" blocks)
942
943
, (" quotation" , blockQuote <$> env " quotation" blocks)
@@ -1088,30 +1089,55 @@ letterContents = do
1088
1089
return $ addr <> bs -- sig added by \closing
1089
1090
1090
1091
figure :: PandocMonad m => LP m Blocks
1091
- figure = try $ do
1092
+ figure = do
1093
+ has_native_figures <-
1094
+ extensionEnabled Ext_native_figures <$> getOption readerExtensions
1095
+ if has_native_figures
1096
+ then nativeFigure
1097
+ else try $ do
1098
+ resetCaption
1099
+ blocks >>= addImageCaption
1100
+
1101
+ nativeFigure :: PandocMonad m => LP m Blocks
1102
+ nativeFigure = try $ do
1092
1103
resetCaption
1093
- blocks >>= addImageCaption
1104
+ innerContent <- many $ try (Left <$> label) <|> (Right <$> block)
1105
+ let content = walk go $ mconcat $ snd $ partitionEithers innerContent
1106
+ labelResult <- sLastLabel <$> getState
1107
+ let attr = case labelResult of
1108
+ Just lab -> (lab, [] , [] )
1109
+ _ -> nullAttr
1110
+ captResult <- sCaption <$> getState
1111
+ case captResult of
1112
+ Nothing -> return $ B. figureWith attr (Caption Nothing [] ) content
1113
+ Just capt -> return $ B. figureWith attr (B. caption Nothing $ B. plain capt) content
1114
+
1115
+ where
1116
+ -- Remove the `Image` caption b.c. it's on the `Figure`
1117
+ go (Para [Image attr _ target]) = Plain [Image attr [] target]
1118
+ go x = x
1094
1119
1095
1120
addImageCaption :: PandocMonad m => Blocks -> LP m Blocks
1096
1121
addImageCaption = walkM go
1097
- where go ( Image attr@ (_, cls, kvs) alt (src,tit))
1122
+ where go p @ ( Para [ Image attr@ (_, cls, kvs) _ (src, tit)] )
1098
1123
| not (" fig:" `T.isPrefixOf` tit) = do
1099
1124
st <- getState
1100
- let (alt', tit') = case sCaption st of
1101
- Just ils -> (toList ils, " fig:" <> tit)
1102
- Nothing -> (alt, tit)
1103
- attr' = case sLastLabel st of
1104
- Just lab -> (lab, cls, kvs)
1105
- Nothing -> attr
1106
- case attr' of
1107
- (" " , _, _) -> return ()
1108
- (ident, _, _) -> do
1109
- num <- getNextNumber sLastFigureNum
1110
- setState
1111
- st{ sLastFigureNum = num
1112
- , sLabels = M. insert ident
1113
- [Str (renderDottedNum num)] (sLabels st) }
1114
- return $ Image attr' alt' (src, tit')
1125
+ case sCaption st of
1126
+ Nothing -> return p
1127
+ Just figureCaption -> do
1128
+ let attr' = case sLastLabel st of
1129
+ Just lab -> (lab, cls, kvs)
1130
+ Nothing -> attr
1131
+ case attr' of
1132
+ (" " , _, _) -> return ()
1133
+ (ident, _, _) -> do
1134
+ num <- getNextNumber sLastFigureNum
1135
+ setState
1136
+ st{ sLastFigureNum = num
1137
+ , sLabels = M. insert ident
1138
+ [Str (renderDottedNum num)] (sLabels st) }
1139
+
1140
+ return $ SimpleFigure attr' (B. toList figureCaption) (src, tit)
1115
1141
go x = return x
1116
1142
1117
1143
coloredBlock :: PandocMonad m => Text -> LP m Blocks
0 commit comments