Skip to content

Commit 58ae017

Browse files
committed
OpenDocument writer: make 'Figure' term sensitive to lang in metadata.
We use the new translations API.
1 parent d7263a7 commit 58ae017

File tree

1 file changed

+16
-9
lines changed

1 file changed

+16
-9
lines changed

src/Text/Pandoc/Writers/OpenDocument.hs

Lines changed: 16 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -39,17 +39,20 @@ import Control.Monad.State.Strict hiding (when)
3939
import Data.Char (chr)
4040
import Data.List (sortBy)
4141
import qualified Data.Map as Map
42+
import Data.Maybe (fromMaybe)
4243
import Data.Ord (comparing)
4344
import qualified Data.Set as Set
4445
import Data.Text (Text)
4546
import Text.Pandoc.BCP47 (Lang (..), parseBCP47)
46-
import Text.Pandoc.Class (PandocMonad, report)
47+
import Text.Pandoc.Class (PandocMonad, report, translateTerm,
48+
setTranslations, toLang)
4749
import Text.Pandoc.Definition
4850
import Text.Pandoc.Logging
4951
import Text.Pandoc.Options
5052
import Text.Pandoc.Pretty
5153
import Text.Pandoc.Shared (linesToPara)
5254
import Text.Pandoc.Templates (renderTemplate')
55+
import Text.Pandoc.Translations (Term(Figure))
5356
import Text.Pandoc.Writers.Math
5457
import Text.Pandoc.Writers.Shared
5558
import Text.Pandoc.XML
@@ -223,6 +226,9 @@ handleSpaces s
223226
-- | Convert Pandoc document to string in OpenDocument format.
224227
writeOpenDocument :: PandocMonad m => WriterOptions -> Pandoc -> m Text
225228
writeOpenDocument opts (Pandoc meta blocks) = do
229+
lang <- fromMaybe (Lang "en" "US" "" []) <$>
230+
toLang (metaValueToString <$> lookupMeta "lang" meta)
231+
setTranslations lang
226232
let colwidth = if writerWrapText opts == WrapAuto
227233
then Just $ writerColumns opts
228234
else Nothing
@@ -413,19 +419,20 @@ blockToOpenDocument o bs
413419
| otherwise = do
414420
id' <- gets stImageId
415421
imageDoc <- withParagraphStyle o "FigureWithCaption" [Para [Image attr caption (source,title)]]
416-
captionDoc <- numberedFigureCaption id' <$> inlinesToOpenDocument o caption
422+
captionDoc <- inlinesToOpenDocument o caption >>= numberedFigureCaption id'
417423
return $ imageDoc $$ captionDoc
418424

419-
numberedFigureCaption :: Int -> Doc -> Doc
420-
numberedFigureCaption num caption =
421-
let t = text "Figure "
422-
r = num - 1
423-
s = inTags False "text:sequence" [ ("text:ref-name", "refIllustration" ++ show r),
425+
numberedFigureCaption :: PandocMonad m => Int -> Doc -> OD m Doc
426+
numberedFigureCaption num caption = do
427+
figterm <- translateTerm Figure
428+
let t = text figterm
429+
let r = num - 1
430+
let s = inTags False "text:sequence" [ ("text:ref-name", "refIllustration" ++ show r),
424431
("text:name", "Illustration"),
425432
("text:formula", "ooow:Illustration+1"),
426433
("style:num-format", "1") ] $ text $ show num
427-
c = text ": "
428-
in inParagraphTagsWithStyle "FigureCaption" $ hcat [ t, s, c, caption ]
434+
let c = text ": "
435+
return $ inParagraphTagsWithStyle "FigureCaption" $ hcat [ t, text " ", s, c, caption ]
429436

430437
colHeadsToOpenDocument :: PandocMonad m
431438
=> WriterOptions -> [String] -> [[Block]]

0 commit comments

Comments
 (0)