aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/ODT.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/ODT.hs')
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs50
1 files changed, 28 insertions, 22 deletions
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index e41fb7176..e4eb4fd25 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -2,7 +2,7 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Writers.ODT
- Copyright : Copyright (C) 2008-2020 John MacFarlane
+ Copyright : Copyright (C) 2008-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -13,9 +13,10 @@ Conversion of 'Pandoc' documents to ODT.
-}
module Text.Pandoc.Writers.ODT ( writeODT ) where
import Codec.Archive.Zip
-import Control.Monad.Except (catchError)
+import Control.Monad.Except (catchError, throwError)
import Control.Monad.State.Strict
import qualified Data.ByteString.Lazy as B
+import Data.Maybe (fromMaybe)
import Data.Generics (everywhere', mkT)
import Data.List (isPrefixOf)
import qualified Data.Map as Map
@@ -23,10 +24,11 @@ import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.Time
import System.FilePath (takeDirectory, takeExtension, (<.>))
-import Text.Pandoc.BCP47 (Lang (..), getLang, renderLang)
+import Text.Collate.Lang (Lang (..), renderLang)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang)
import qualified Text.Pandoc.Class.PandocMonad as P
import Text.Pandoc.Definition
+import Text.Pandoc.Error (PandocError(..))
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.MIME (extensionFromMimeType, getMimeType)
@@ -34,13 +36,14 @@ import Text.Pandoc.Options (WrapOption (..), WriterOptions (..))
import Text.DocLayout
import Text.Pandoc.Shared (stringify, pandocVersion, tshow)
import Text.Pandoc.Writers.Shared (lookupMetaString, lookupMetaBlocks,
- fixDisplayMath)
-import Text.Pandoc.UTF8 (fromStringLazy, fromTextLazy, toStringLazy)
+ fixDisplayMath, getLang)
+import Text.Pandoc.UTF8 (fromStringLazy, fromTextLazy, toTextLazy)
import Text.Pandoc.Walk
import Text.Pandoc.Writers.OpenDocument (writeOpenDocument)
import Text.Pandoc.XML
+import Text.Pandoc.XML.Light
import Text.TeXMath
-import Text.XML.Light
+import qualified Text.XML.Light as XL
newtype ODTState = ODTState { stEntries :: [Entry]
}
@@ -66,7 +69,7 @@ pandocToODT :: PandocMonad m
pandocToODT opts doc@(Pandoc meta _) = do
let title = docTitle meta
let authors = docAuthors meta
- utctime <- P.getCurrentTime
+ utctime <- P.getTimestamp
lang <- toLang (getLang opts meta)
refArchive <-
case writerReferenceDoc opts of
@@ -172,24 +175,27 @@ updateStyleWithLang :: PandocMonad m => Maybe Lang -> Archive -> O m Archive
updateStyleWithLang Nothing arch = return arch
updateStyleWithLang (Just lang) arch = do
epochtime <- floor `fmap` lift P.getPOSIXTime
- return arch{ zEntries = [if eRelativePath e == "styles.xml"
- then case parseXMLDoc
- (toStringLazy (fromEntry e)) of
- Nothing -> e
- Just d ->
- toEntry "styles.xml" epochtime
- ( fromStringLazy
- . ppTopElement
- . addLang lang $ d )
- else e
- | e <- zEntries arch] }
+ entries <- mapM (\e -> if eRelativePath e == "styles.xml"
+ then case parseXMLElement
+ (toTextLazy (fromEntry e)) of
+ Left msg -> throwError $
+ PandocXMLError "styles.xml" msg
+ Right d -> return $
+ toEntry "styles.xml" epochtime
+ ( fromTextLazy
+ . TL.fromStrict
+ . ppTopElement
+ . addLang lang $ d )
+ else return e) (zEntries arch)
+ return arch{ zEntries = entries }
+-- TODO FIXME avoid this generic traversal!
addLang :: Lang -> Element -> Element
addLang lang = everywhere' (mkT updateLangAttr)
where updateLangAttr (Attr n@(QName "language" _ (Just "fo")) _)
- = Attr n (T.unpack $ langLanguage lang)
+ = Attr n (langLanguage lang)
updateLangAttr (Attr n@(QName "country" _ (Just "fo")) _)
- = Attr n (T.unpack $ langRegion lang)
+ = Attr n (fromMaybe "" $ langRegion lang)
updateLangAttr x = x
-- | transform both Image and Math elements
@@ -235,8 +241,8 @@ transformPicMath _ (Math t math) = do
case writeMathML dt <$> readTeX math of
Left _ -> return $ Math t math
Right r -> do
- let conf = useShortEmptyTags (const False) defaultConfigPP
- let mathml = ppcTopElement conf r
+ let conf = XL.useShortEmptyTags (const False) XL.defaultConfigPP
+ let mathml = XL.ppcTopElement conf r
epochtime <- floor `fmap` lift P.getPOSIXTime
let dirname = "Formula-" ++ show (length entries) ++ "/"
let fname = dirname ++ "content.xml"