aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2014-01-02 15:23:40 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2014-01-02 15:23:40 -0800
commit33955fd2efd640becfddb262c4443509521cb6cc (patch)
tree9177841c52b29808a52ee63709e7340a85baeacb /src/Text/Pandoc/Writers
parentac100f27249e4c572e687d027330ca2cc53cb1ed (diff)
downloadpandoc-33955fd2efd640becfddb262c4443509521cb6cc.tar.gz
ODT writer: Use mathml for proper rendering of formulas.
Note: LibreOffice's support for this seems a bit buggy. But it should be better than what we had before.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs50
1 files changed, 42 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index 25cd5ae13..c3652d65d 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -30,8 +30,10 @@ Conversion of 'Pandoc' documents to ODT.
-}
module Text.Pandoc.Writers.ODT ( writeODT ) where
import Data.IORef
-import Data.List ( isPrefixOf )
+import Data.List ( isPrefixOf, isSuffixOf )
import Data.Maybe ( fromMaybe )
+import Text.XML.Light.Output
+import Text.TeXMath
import qualified Data.ByteString.Lazy as B
import Text.Pandoc.UTF8 ( fromStringLazy )
import Codec.Archive.Zip
@@ -41,13 +43,14 @@ import Text.Pandoc.ImageSize ( imageSize, sizeInPoints )
import Text.Pandoc.MIME ( getMimeType )
import Text.Pandoc.Definition
import Text.Pandoc.Walk
+import Text.Pandoc.Writers.Shared ( fixDisplayMath )
import Text.Pandoc.Writers.OpenDocument ( writeOpenDocument )
import Control.Monad (liftM)
import Text.Pandoc.XML
import Text.Pandoc.Pretty
import qualified Control.Exception as E
import Data.Time.Clock.POSIX ( getPOSIXTime )
-import System.FilePath ( takeExtension )
+import System.FilePath ( takeExtension, takeDirectory )
-- | Produce an ODT file from a Pandoc document.
writeODT :: WriterOptions -- ^ Writer options
@@ -61,9 +64,9 @@ writeODT opts doc@(Pandoc meta _) = do
Just f -> B.readFile f
Nothing -> (B.fromChunks . (:[])) `fmap`
readDataFile datadir "reference.odt"
- -- handle pictures
+ -- handle formulas and pictures
picEntriesRef <- newIORef ([] :: [Entry])
- doc' <- walkM (transformPic opts picEntriesRef) doc
+ doc' <- walkM (transformPicMath opts picEntriesRef) $ walk fixDisplayMath doc
let newContents = writeOpenDocument opts{writerWrapText = False} doc'
epochtime <- floor `fmap` getPOSIXTime
let contentEntry = toEntry "content.xml" epochtime
@@ -73,7 +76,11 @@ writeODT opts doc@(Pandoc meta _) = do
$ contentEntry : picEntries
-- construct META-INF/manifest.xml based on archive
let toFileEntry fp = case getMimeType fp of
- Nothing -> empty
+ Nothing -> if "Formula-" `isPrefixOf` fp && "/" `isSuffixOf` fp
+ then selfClosingTag "manifest:file-entry"
+ [("manifest:media-type","application/vnd.oasis.opendocument.formula")
+ ,("manifest:full-path",fp)]
+ else empty
Just m -> selfClosingTag "manifest:file-entry"
[("manifest:media-type", m)
,("manifest:full-path", fp)
@@ -81,6 +88,8 @@ writeODT opts doc@(Pandoc meta _) = do
]
let files = [ ent | ent <- filesInArchive archive,
not ("META-INF" `isPrefixOf` ent) ]
+ let formulas = [ takeDirectory ent ++ "/" | ent <- filesInArchive archive,
+ "Formula-" `isPrefixOf` ent, takeExtension ent == ".xml" ]
let manifestEntry = toEntry "META-INF/manifest.xml" epochtime
$ fromStringLazy $ render Nothing
$ text "<?xml version=\"1.0\" encoding=\"utf-8\"?>"
@@ -92,6 +101,7 @@ writeODT opts doc@(Pandoc meta _) = do
[("manifest:media-type","application/vnd.oasis.opendocument.text")
,("manifest:full-path","/")]
$$ vcat ( map toFileEntry $ files )
+ $$ vcat ( map toFileEntry $ formulas )
)
)
let archive' = addEntryToArchive manifestEntry archive
@@ -119,8 +129,8 @@ writeODT opts doc@(Pandoc meta _) = do
$ addEntryToArchive metaEntry archive'
return $ fromArchive archive''
-transformPic :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline
-transformPic opts entriesRef (Image lab (src,_)) = do
+transformPicMath :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline
+transformPicMath opts entriesRef (Image lab (src,_)) = do
res <- fetchItem (writerSourceURL opts) src
case res of
Left (_ :: E.SomeException) -> do
@@ -137,5 +147,29 @@ transformPic opts entriesRef (Image lab (src,_)) = do
let entry = toEntry newsrc epochtime $ toLazy img
modifyIORef entriesRef (entry:)
return $ Image lab (newsrc, tit')
-transformPic _ _ x = return x
+transformPicMath _ entriesRef (Math t math) = do
+ entries <- readIORef entriesRef
+ let dt = if t == InlineMath then DisplayInline else DisplayBlock
+ case texMathToMathML dt math of
+ Left _ -> return $ Math t math
+ Right r -> do
+ let conf = useShortEmptyTags (const False) defaultConfigPP
+ let mathml = ppcTopElement conf r
+ epochtime <- floor `fmap` getPOSIXTime
+ let dirname = "Formula-" ++ show (length entries) ++ "/"
+ let fname = dirname ++ "content.xml"
+ let entry = toEntry fname epochtime (fromStringLazy mathml)
+ modifyIORef entriesRef (entry:)
+ return $ RawInline (Format "opendocument") $ render Nothing $
+ inTags False "draw:frame" [("text:anchor-type",
+ if t == DisplayMath
+ then "paragraph"
+ else "as-char")
+ ,("style:vertical-pos", "middle")
+ ,("style:vertical-rel", "text")] $
+ selfClosingTag "draw:object" [("xlink:href", dirname)
+ , ("xlink:type", "simple")
+ , ("xlink:show", "embed")
+ , ("xlink:actuate", "onLoad")]
+transformPicMath _ _ x = return x