2013-01-11 15:45:19 -08:00
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
2010-07-02 20:12:14 -07:00
|
|
|
{-
|
2015-04-26 10:18:29 -07:00
|
|
|
Copyright (C) 2008-2015 John MacFarlane <jgm@berkeley.edu>
|
2010-07-02 20:12:14 -07:00
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
-}
|
|
|
|
|
|
|
|
{- |
|
|
|
|
Module : Text.Pandoc.Writers.ODT
|
2015-04-26 10:18:29 -07:00
|
|
|
Copyright : Copyright (C) 2008-2015 John MacFarlane
|
2010-07-02 20:12:14 -07:00
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Conversion of 'Pandoc' documents to ODT.
|
|
|
|
-}
|
|
|
|
module Text.Pandoc.Writers.ODT ( writeODT ) where
|
|
|
|
import Data.IORef
|
2014-08-17 20:42:30 +04:00
|
|
|
import Data.List ( isPrefixOf )
|
2013-12-19 21:07:09 -05:00
|
|
|
import Data.Maybe ( fromMaybe )
|
2014-01-02 15:23:40 -08:00
|
|
|
import Text.XML.Light.Output
|
|
|
|
import Text.TeXMath
|
2010-07-02 20:12:14 -07:00
|
|
|
import qualified Data.ByteString.Lazy as B
|
2012-09-25 19:54:21 -07:00
|
|
|
import Text.Pandoc.UTF8 ( fromStringLazy )
|
2010-07-02 20:12:14 -07:00
|
|
|
import Codec.Archive.Zip
|
2012-07-26 22:59:56 -07:00
|
|
|
import Text.Pandoc.Options ( WriterOptions(..) )
|
2015-06-28 23:59:10 -07:00
|
|
|
import Text.Pandoc.Shared ( stringify, fetchItem', warn,
|
2015-06-28 22:30:21 -07:00
|
|
|
getDefaultReferenceODT )
|
2013-01-11 15:45:19 -08:00
|
|
|
import Text.Pandoc.ImageSize ( imageSize, sizeInPoints )
|
2014-10-30 15:54:04 -07:00
|
|
|
import Text.Pandoc.MIME ( getMimeType, extensionFromMimeType )
|
2010-07-02 20:12:14 -07:00
|
|
|
import Text.Pandoc.Definition
|
2013-08-10 18:45:00 -07:00
|
|
|
import Text.Pandoc.Walk
|
2014-01-02 15:23:40 -08:00
|
|
|
import Text.Pandoc.Writers.Shared ( fixDisplayMath )
|
2010-07-02 20:12:14 -07:00
|
|
|
import Text.Pandoc.Writers.OpenDocument ( writeOpenDocument )
|
|
|
|
import Control.Monad (liftM)
|
2011-07-17 23:21:59 -07:00
|
|
|
import Text.Pandoc.XML
|
|
|
|
import Text.Pandoc.Pretty
|
2012-07-24 19:28:51 -07:00
|
|
|
import qualified Control.Exception as E
|
2013-01-11 15:45:19 -08:00
|
|
|
import Data.Time.Clock.POSIX ( getPOSIXTime )
|
2014-10-30 15:54:04 -07:00
|
|
|
import System.FilePath ( takeExtension, takeDirectory, (<.>))
|
2010-07-02 20:12:14 -07:00
|
|
|
|
|
|
|
-- | Produce an ODT file from a Pandoc document.
|
2012-07-24 09:56:00 -07:00
|
|
|
writeODT :: WriterOptions -- ^ Writer options
|
2010-07-02 20:12:14 -07:00
|
|
|
-> Pandoc -- ^ Document to convert
|
|
|
|
-> IO B.ByteString
|
2013-05-10 22:53:35 -07:00
|
|
|
writeODT opts doc@(Pandoc meta _) = do
|
2010-07-08 17:31:55 -07:00
|
|
|
let datadir = writerUserDataDir opts
|
2013-05-10 22:53:35 -07:00
|
|
|
let title = docTitle meta
|
2015-05-28 18:15:01 -07:00
|
|
|
refArchive <-
|
2012-07-24 09:56:00 -07:00
|
|
|
case writerReferenceODT opts of
|
2015-05-28 18:15:01 -07:00
|
|
|
Just f -> liftM toArchive $ B.readFile f
|
|
|
|
Nothing -> getDefaultReferenceODT datadir
|
2014-01-02 15:23:40 -08:00
|
|
|
-- handle formulas and pictures
|
2010-07-02 20:12:14 -07:00
|
|
|
picEntriesRef <- newIORef ([] :: [Entry])
|
2014-01-02 15:23:40 -08:00
|
|
|
doc' <- walkM (transformPicMath opts picEntriesRef) $ walk fixDisplayMath doc
|
2010-12-22 14:55:59 -08:00
|
|
|
let newContents = writeOpenDocument opts{writerWrapText = False} doc'
|
2012-01-28 16:04:35 -08:00
|
|
|
epochtime <- floor `fmap` getPOSIXTime
|
2013-08-11 17:13:46 -07:00
|
|
|
let contentEntry = toEntry "content.xml" epochtime
|
|
|
|
$ fromStringLazy newContents
|
2010-07-02 20:12:14 -07:00
|
|
|
picEntries <- readIORef picEntriesRef
|
2013-08-11 17:13:46 -07:00
|
|
|
let archive = foldr addEntryToArchive refArchive
|
|
|
|
$ contentEntry : picEntries
|
2011-07-17 23:21:59 -07:00
|
|
|
-- construct META-INF/manifest.xml based on archive
|
|
|
|
let toFileEntry fp = case getMimeType fp of
|
2014-08-17 20:42:30 +04:00
|
|
|
Nothing -> empty
|
2011-07-17 23:21:59 -07:00
|
|
|
Just m -> selfClosingTag "manifest:file-entry"
|
|
|
|
[("manifest:media-type", m)
|
|
|
|
,("manifest:full-path", fp)
|
2013-08-11 17:13:46 -07:00
|
|
|
,("manifest:version", "1.2")
|
2011-07-17 23:21:59 -07:00
|
|
|
]
|
2013-08-11 17:13:46 -07:00
|
|
|
let files = [ ent | ent <- filesInArchive archive,
|
|
|
|
not ("META-INF" `isPrefixOf` ent) ]
|
2014-01-02 15:23:40 -08:00
|
|
|
let formulas = [ takeDirectory ent ++ "/" | ent <- filesInArchive archive,
|
|
|
|
"Formula-" `isPrefixOf` ent, takeExtension ent == ".xml" ]
|
2011-07-17 23:21:59 -07:00
|
|
|
let manifestEntry = toEntry "META-INF/manifest.xml" epochtime
|
2013-03-15 15:20:52 -07:00
|
|
|
$ fromStringLazy $ render Nothing
|
2011-07-17 23:21:59 -07:00
|
|
|
$ text "<?xml version=\"1.0\" encoding=\"utf-8\"?>"
|
|
|
|
$$
|
|
|
|
( inTags True "manifest:manifest"
|
2013-08-11 17:13:46 -07:00
|
|
|
[("xmlns:manifest","urn:oasis:names:tc:opendocument:xmlns:manifest:1.0")
|
|
|
|
,("manifest:version","1.2")]
|
2011-07-17 23:21:59 -07:00
|
|
|
$ ( selfClosingTag "manifest:file-entry"
|
|
|
|
[("manifest:media-type","application/vnd.oasis.opendocument.text")
|
|
|
|
,("manifest:full-path","/")]
|
|
|
|
$$ vcat ( map toFileEntry $ files )
|
2014-01-02 15:23:40 -08:00
|
|
|
$$ vcat ( map toFileEntry $ formulas )
|
2011-07-17 23:21:59 -07:00
|
|
|
)
|
|
|
|
)
|
|
|
|
let archive' = addEntryToArchive manifestEntry archive
|
2012-07-13 15:19:39 -06:00
|
|
|
let metaEntry = toEntry "meta.xml" epochtime
|
2013-03-15 15:20:52 -07:00
|
|
|
$ fromStringLazy $ render Nothing
|
2012-07-13 15:19:39 -06:00
|
|
|
$ 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))
|
|
|
|
)
|
|
|
|
)
|
|
|
|
)
|
2013-08-11 17:13:46 -07:00
|
|
|
-- make sure mimetype is first
|
|
|
|
let mimetypeEntry = toEntry "mimetype" epochtime
|
|
|
|
$ fromStringLazy "application/vnd.oasis.opendocument.text"
|
|
|
|
let archive'' = addEntryToArchive mimetypeEntry
|
|
|
|
$ addEntryToArchive metaEntry archive'
|
2012-07-13 15:19:39 -06:00
|
|
|
return $ fromArchive archive''
|
2010-07-02 20:12:14 -07:00
|
|
|
|
2014-01-02 15:23:40 -08:00
|
|
|
transformPicMath :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline
|
2015-04-12 00:34:03 +03:00
|
|
|
transformPicMath opts entriesRef (Image lab (src,t)) = do
|
2014-07-30 14:07:31 -07:00
|
|
|
res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src
|
2013-01-11 15:45:19 -08:00
|
|
|
case res of
|
|
|
|
Left (_ :: E.SomeException) -> do
|
2013-07-18 20:58:14 -07:00
|
|
|
warn $ "Could not find image `" ++ src ++ "', skipping..."
|
2013-01-11 15:45:19 -08:00
|
|
|
return $ Emph lab
|
2014-10-30 15:54:04 -07:00
|
|
|
Right (img, mbMimeType) -> do
|
2015-05-09 21:32:31 -07:00
|
|
|
(w,h) <- case imageSize img of
|
|
|
|
Right size -> return $ sizeInPoints size
|
2015-05-09 23:56:18 -07:00
|
|
|
Left msg -> do
|
|
|
|
warn $ "Could not determine image size in `" ++
|
|
|
|
src ++ "': " ++ msg
|
|
|
|
return (0,0)
|
2013-01-11 15:45:19 -08:00
|
|
|
let tit' = show w ++ "x" ++ show h
|
|
|
|
entries <- readIORef entriesRef
|
2014-10-30 15:54:04 -07:00
|
|
|
let extension = fromMaybe (takeExtension $ takeWhile (/='?') src)
|
|
|
|
(mbMimeType >>= extensionFromMimeType)
|
|
|
|
let newsrc = "Pictures/" ++ show (length entries) <.> extension
|
2013-01-11 15:45:19 -08:00
|
|
|
let toLazy = B.fromChunks . (:[])
|
|
|
|
epochtime <- floor `fmap` getPOSIXTime
|
|
|
|
let entry = toEntry newsrc epochtime $ toLazy img
|
|
|
|
modifyIORef entriesRef (entry:)
|
2015-04-12 00:34:03 +03:00
|
|
|
let fig | "fig:" `isPrefixOf` t = "fig:"
|
|
|
|
| otherwise = ""
|
|
|
|
return $ Image lab (newsrc, fig++tit')
|
2014-01-02 15:23:40 -08:00
|
|
|
transformPicMath _ entriesRef (Math t math) = do
|
|
|
|
entries <- readIORef entriesRef
|
|
|
|
let dt = if t == InlineMath then DisplayInline else DisplayBlock
|
2014-08-04 11:13:09 -07:00
|
|
|
case writeMathML dt <$> readTeX math of
|
2014-01-02 15:23:40 -08:00
|
|
|
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")]
|
2010-07-02 20:12:14 -07:00
|
|
|
|
2014-01-02 15:23:40 -08:00
|
|
|
transformPicMath _ _ x = return x
|