diff options
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 73 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 24 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ODT.hs | 21 |
3 files changed, 74 insertions, 44 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 7a4753327..bb4dd0688 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -76,6 +76,8 @@ module Text.Pandoc.Shared ( renderTags', -- * File handling inDirectory, + getDefaultReferenceDocx, + getDefaultReferenceODT, readDataFile, readDataFileUTF8, fetchItem, @@ -119,6 +121,7 @@ import Control.Monad (msum, unless, MonadPlus(..)) import Text.Pandoc.Pretty (charWidth) import Text.Pandoc.Compat.Locale (defaultTimeLocale) import Data.Time +import Data.Time.Clock.POSIX import System.IO (stderr) import System.IO.Temp import Text.HTML.TagSoup (renderTagsOptions, RenderOptions(..), Tag(..), @@ -129,7 +132,8 @@ import Text.Pandoc.Compat.Monoid import Data.ByteString.Base64 (decodeLenient) import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr) import qualified Data.Text as T (toUpper, pack, unpack) -import Data.ByteString.Lazy (toChunks) +import Data.ByteString.Lazy (toChunks, fromChunks) +import qualified Data.ByteString.Lazy as BL #ifdef EMBED_DATA_FILES import Text.Pandoc.Data (dataFiles) @@ -145,6 +149,7 @@ import Network.HTTP.Client.TLS (tlsManagerSettings) import System.Environment (getEnv) import Network.HTTP.Types.Header ( hContentType) import Network (withSocketsDo) +import Codec.Archive.Zip #else import Network.URI (parseURI) import Network.HTTP (findHeader, rspBody, @@ -742,7 +747,73 @@ inDirectory path action = E.bracket setCurrentDirectory (const $ setCurrentDirectory path >> action) +getDefaultReferenceDocx :: Maybe FilePath -> IO Archive +getDefaultReferenceDocx datadir = do + let paths = ["[Content_Types].xml", + "_rels/.rels", + "docProps/app.xml", + "docProps/core.xml", + "word/document.xml", + "word/fontTable.xml", + "word/footnotes.xml", + "word/numbering.xml", + "word/settings.xml", + "word/webSettings.xml", + "word/styles.xml", + "word/_rels/document.xml.rels", + "word/_rels/footnotes.xml.rels", + "word/theme/theme1.xml"] + let toLazy = fromChunks . (:[]) + let pathToEntry path = do epochtime <- (floor . utcTimeToPOSIXSeconds) <$> + getCurrentTime + contents <- toLazy <$> readDataFile datadir + ("docx/" ++ path) + return $ toEntry path epochtime contents + mbArchive <- case datadir of + Nothing -> return Nothing + Just d -> do + exists <- doesFileExist (d </> "reference.docx") + if exists + then return (Just (d </> "reference.docx")) + else return Nothing + case mbArchive of + Just arch -> toArchive <$> BL.readFile arch + Nothing -> foldr addEntryToArchive emptyArchive <$> + mapM pathToEntry paths + +getDefaultReferenceODT :: Maybe FilePath -> IO Archive +getDefaultReferenceODT datadir = do + let paths = ["mimetype", + "manifest.rdf", + "styles.xml", + "content.xml", + "meta.xml", + "settings.xml", + "Configurations2/accelerator/current.xml", + "Thumbnails/thumbnail.png", + "META-INF/manifest.xml"] + let pathToEntry path = do epochtime <- floor `fmap` getPOSIXTime + contents <- (fromChunks . (:[])) `fmap` + readDataFile datadir ("odt/" ++ path) + return $ toEntry path epochtime contents + mbArchive <- case datadir of + Nothing -> return Nothing + Just d -> do + exists <- doesFileExist (d </> "reference.odt") + if exists + then return (Just (d </> "reference.odt")) + else return Nothing + case mbArchive of + Just arch -> toArchive <$> BL.readFile arch + Nothing -> foldr addEntryToArchive emptyArchive <$> + mapM pathToEntry paths + + readDefaultDataFile :: FilePath -> IO BS.ByteString +readDefaultDataFile "reference.docx" = + (BS.concat . toChunks . fromArchive) <$> getDefaultReferenceDocx Nothing +readDefaultDataFile "reference.odt" = + (BS.concat . toChunks . fromArchive) <$> getDefaultReferenceODT Nothing readDefaultDataFile fname = #ifdef EMBED_DATA_FILES case lookup (makeCanonical fname) dataFiles of diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 04368e730..8ffae5048 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -1220,27 +1220,3 @@ fitToPage (x, y) pageWidth ((fromIntegral pageWidth) / ((fromIntegral :: Integer -> Double) x)) * (fromIntegral y)) | otherwise = (x, y) -getDefaultReferenceDocx :: Maybe FilePath -> IO Archive -getDefaultReferenceDocx datadir = do - let paths = ["[Content_Types].xml", - "_rels/.rels", - "docProps/app.xml", - "docProps/core.xml", - "word/document.xml", - "word/fontTable.xml", - "word/footnotes.xml", - "word/numbering.xml", - "word/settings.xml", - "word/webSettings.xml", - "word/styles.xml", - "word/_rels/document.xml.rels", - "word/_rels/footnotes.xml.rels", - "word/theme/theme1.xml"] - let pathToEntry path = do epochtime <- (floor . utcTimeToPOSIXSeconds) <$> - getCurrentTime - contents <- toLazy <$> readDataFile datadir - ("docx/" ++ path) - return $ toEntry path epochtime contents - entries <- mapM pathToEntry paths - let archive = foldr addEntryToArchive emptyArchive entries - return archive diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 51e06cea8..0719acc3e 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -39,7 +39,8 @@ import Text.Pandoc.UTF8 ( fromStringLazy ) import Codec.Archive.Zip import Control.Applicative ((<$>)) import Text.Pandoc.Options ( WriterOptions(..) ) -import Text.Pandoc.Shared ( stringify, readDataFile, fetchItem', warn ) +import Text.Pandoc.Shared ( stringify, readDataFile, fetchItem', warn, + getDefaultReferenceODT ) import Text.Pandoc.ImageSize ( imageSize, sizeInPoints ) import Text.Pandoc.MIME ( getMimeType, extensionFromMimeType ) import Text.Pandoc.Definition @@ -177,21 +178,3 @@ transformPicMath _ entriesRef (Math t math) = do , ("xlink:actuate", "onLoad")] transformPicMath _ _ x = return x - -getDefaultReferenceODT :: Maybe FilePath -> IO Archive -getDefaultReferenceODT datadir = do - let paths = ["mimetype", - "manifest.rdf", - "styles.xml", - "content.xml", - "meta.xml", - "settings.xml", - "Configurations2/accelerator/current.xml", - "Thumbnails/thumbnail.png", - "META-INF/manifest.xml"] - let pathToEntry path = do epochtime <- floor `fmap` getPOSIXTime - contents <- (B.fromChunks . (:[])) `fmap` - readDataFile datadir ("odt/" ++ path) - return $ toEntry path epochtime contents - entries <- mapM pathToEntry paths - return $ foldr addEntryToArchive emptyArchive entries |