module Text.Pandoc.Writers.ODT ( writeODT ) where
import Data.IORef
import Data.List ( isPrefixOf )
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
import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..) )
import Text.Pandoc.Shared ( stringify, fetchItem', warn,
getDefaultReferenceODT )
import Text.Pandoc.ImageSize
import Text.Pandoc.MIME ( getMimeType, extensionFromMimeType )
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, takeDirectory, (<.>))
writeODT :: WriterOptions
-> Pandoc
-> IO B.ByteString
writeODT opts doc@(Pandoc meta _) = do
let datadir = writerUserDataDir opts
let title = docTitle meta
refArchive <-
case writerReferenceODT opts of
Just f -> liftM toArchive $ B.readFile f
Nothing -> getDefaultReferenceODT datadir
picEntriesRef <- newIORef ([] :: [Entry])
doc' <- walkM (transformPicMath opts picEntriesRef) $ walk fixDisplayMath doc
let newContents = writeOpenDocument opts{writerWrapText = WrapNone} doc'
epochtime <- floor `fmap` getPOSIXTime
let contentEntry = toEntry "content.xml" epochtime
$ fromStringLazy newContents
picEntries <- readIORef picEntriesRef
let archive = foldr addEntryToArchive refArchive
$ contentEntry : picEntries
let toFileEntry fp = case getMimeType fp of
Nothing -> empty
Just m -> selfClosingTag "manifest:file-entry"
[("manifest:media-type", m)
,("manifest:full-path", fp)
,("manifest:version", "1.2")
]
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\"?>"
$$
( inTags True "manifest:manifest"
[("xmlns:manifest","urn:oasis:names:tc:opendocument:xmlns:manifest:1.0")
,("manifest:version","1.2")]
$ ( selfClosingTag "manifest:file-entry"
[("manifest:media-type","application/vnd.oasis.opendocument.text")
,("manifest:full-path","/")]
$$ vcat ( map toFileEntry $ files )
$$ vcat ( map toFileEntry $ formulas )
)
)
let archive' = addEntryToArchive manifestEntry archive
let metaEntry = toEntry "meta.xml" epochtime
$ fromStringLazy $ render Nothing
$ text "<?xml version=\"1.0\" encoding=\"utf-8\"?>"
$$
( inTags True "office:document-meta"
[("xmlns:office","urn:oasis:names:tc:opendocument:xmlns:office:1.0")
,("xmlns:xlink","http://www.w3.org/1999/xlink")
,("xmlns:dc","http://purl.org/dc/elements/1.1/")
,("xmlns:meta","urn:oasis:names:tc:opendocument:xmlns:meta:1.0")
,("xmlns:ooo","http://openoffice.org/2004/office")
,("xmlns:grddl","http://www.w3.org/2003/g/data-view#")
,("office:version","1.2")]
$ ( inTagsSimple "office:meta"
$ ( inTagsSimple "dc:title" (text $ escapeStringForXML (stringify title))
)
)
)
let mimetypeEntry = toEntry "mimetype" epochtime
$ fromStringLazy "application/vnd.oasis.opendocument.text"
let archive'' = addEntryToArchive mimetypeEntry
$ addEntryToArchive metaEntry archive'
return $ fromArchive archive''
transformPicMath :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline
transformPicMath opts entriesRef (Image attr@(id', cls, _) lab (src,t)) = do
res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src
case res of
Left (_ :: E.SomeException) -> do
warn $ "Could not find image `" ++ src ++ "', skipping..."
return $ Emph lab
Right (img, mbMimeType) -> do
(ptX, ptY) <- case imageSize img of
Right s -> return $ sizeInPoints s
Left msg -> do
warn $ "Could not determine image size in `" ++
src ++ "': " ++ msg
return (100, 100)
let dims =
case (getDim Width, getDim Height) of
(Just w, Just h) -> [("width", show w), ("height", show h)]
(Just w@(Percent _), Nothing) -> [("width", show w), ("style:rel-height", "scale")]
(Nothing, Just h@(Percent _)) -> [("style:rel-width", "scale"), ("height", show h)]
(Just w@(Inch i), Nothing) -> [("width", show w), ("height", show (i / ratio) ++ "in")]
(Nothing, Just h@(Inch i)) -> [("width", show (i * ratio) ++ "in"), ("height", show h)]
_ -> [("width", show ptX ++ "pt"), ("height", show ptY ++ "pt")]
where
ratio = ptX / ptY
getDim dir = case (dimension dir attr) of
Just (Percent i) -> Just $ Percent i
Just dim -> Just $ Inch $ inInch opts dim
Nothing -> Nothing
let newattr = (id', cls, dims)
entries <- readIORef entriesRef
let extension = fromMaybe (takeExtension $ takeWhile (/='?') src)
(mbMimeType >>= extensionFromMimeType)
let newsrc = "Pictures/" ++ show (length entries) <.> extension
let toLazy = B.fromChunks . (:[])
epochtime <- floor `fmap` getPOSIXTime
let entry = toEntry newsrc epochtime $ toLazy img
modifyIORef entriesRef (entry:)
return $ Image newattr lab (newsrc, t)
transformPicMath _ entriesRef (Math t math) = do
entries <- readIORef entriesRef
let dt = if t == InlineMath then DisplayInline else DisplayBlock
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
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