aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2022-10-03 13:05:38 -0700
committerGitHub <[email protected]>2022-10-03 13:05:38 -0700
commitad0532244adfbd0ca9596a27506ed6161e4bc225 (patch)
tree70cdf0534234805fb650fa349745abea5814d65c /src
parent2d565eda9ec6df702bc0381ccb60fc3cc9699318 (diff)
Separate out T.P.Data, T.P.Translations from T.P.Class. (#8348)
This makes T.P.Class more self-contained, and suitable for extraction into a separate package if desired. [API changes] - T.P.Data is now an exported module, providing `readDataFile`, `readDefaultDataFile` (both formerly provided by T.P.Class), and also `getDataFileNames` (formerly unexported in T.P.App.CommandLineOptions). - T.P.Translations is now an exported module (along with T.P.Translations.Types), providing `readTranslations`, `getTranslations`, `setTranslations`, `translateTerm`, `lookupTerm`, `readTranslations`, `Term(..)`, and `Translations`. - T.P.Class: `readDataFile`, `readDefaultDataFile`, `setTranslations`, and `translateTerm` are no longer exported. `checkUserDataDir` is now exported. - Text.Pandoc now exports Text.Pandoc.Data and `setTranslations` and `translateTerm`.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc.hs9
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs18
-rw-r--r--src/Text/Pandoc/Citeproc.hs3
-rw-r--r--src/Text/Pandoc/Class.hs2
-rw-r--r--src/Text/Pandoc/Class/CommonState.hs2
-rw-r--r--src/Text/Pandoc/Class/PandocMonad.hs264
-rw-r--r--src/Text/Pandoc/Data.hs232
-rw-r--r--src/Text/Pandoc/Data/BakedIn.hs32
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Inline.hs3
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Lang.hs3
-rw-r--r--src/Text/Pandoc/Shared.hs10
-rw-r--r--src/Text/Pandoc/Templates.hs3
-rw-r--r--src/Text/Pandoc/Translations.hs140
-rw-r--r--src/Text/Pandoc/Translations/Types.hs88
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs9
-rw-r--r--src/Text/Pandoc/Writers/Docx/Table.hs3
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs3
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs4
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs3
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs4
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Output.hs5
21 files changed, 453 insertions, 387 deletions
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index 690cdd99d..2f2b396af 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -47,6 +47,8 @@ module Text.Pandoc
, module Text.Pandoc.Logging
-- * Typeclass
, module Text.Pandoc.Class
+ -- * Internal data files
+ , module Text.Pandoc.Data
-- * Error handling
, module Text.Pandoc.Error
-- * Readers: converting /to/ Pandoc format
@@ -55,13 +57,17 @@ module Text.Pandoc
, module Text.Pandoc.Writers
-- * Rendering templates and default templates
, module Text.Pandoc.Templates
- -- * Miscellaneous
+ -- * Localization
+ , setTranslations
+ , translateTerm
+ -- * Version information
, pandocVersion
, pandocVersionText
) where
import Text.Pandoc.Class
import Text.Pandoc.Definition
+import Text.Pandoc.Data
import Text.Pandoc.Error
import Text.Pandoc.Generic
import Text.Pandoc.Logging
@@ -69,4 +75,5 @@ import Text.Pandoc.Options
import Text.Pandoc.Readers
import Text.Pandoc.Shared (pandocVersion, pandocVersionText)
import Text.Pandoc.Templates
+import Text.Pandoc.Translations (setTranslations, translateTerm)
import Text.Pandoc.Writers
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index d2b140eaf..a9afec7f6 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -55,14 +55,6 @@ import Text.Pandoc.Highlighting (highlightingStyles, lookupHighlightingStyle)
import Text.Pandoc.Scripting (ScriptingEngine (engineName))
import Text.Pandoc.Shared (ordNub, elemText, safeStrRead, defaultUserDataDir)
import Text.Printf
-
-#ifdef EMBED_DATA_FILES
-import Text.Pandoc.Data (dataFiles)
-#else
-import Paths_pandoc (getDataDir)
-import System.Directory (getDirectoryContents)
-#endif
-
import qualified Control.Exception as E
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as B
@@ -966,16 +958,6 @@ options scriptingEngine =
"" -- "Show help"
]
-getDataFileNames :: IO [FilePath]
-getDataFileNames = do
-#ifdef EMBED_DATA_FILES
- let allDataFiles = map fst dataFiles
-#else
- allDataFiles <- filter (\x -> x /= "." && x /= "..") <$>
- (getDataDir >>= getDirectoryContents)
-#endif
- return $ "reference.docx" : "reference.odt" : "reference.pptx" : allDataFiles
-
-- Returns usage message
usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String
usageMessage programName = usageInfo (programName ++ " [OPTIONS] [FILES]")
diff --git a/src/Text/Pandoc/Citeproc.hs b/src/Text/Pandoc/Citeproc.hs
index fc453c277..082d79553 100644
--- a/src/Text/Pandoc/Citeproc.hs
+++ b/src/Text/Pandoc/Citeproc.hs
@@ -24,7 +24,8 @@ import Text.Pandoc.Builder (Inlines, Many(..), deleteMeta, setMeta)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Definition as Pandoc
import Text.Pandoc.Class (PandocMonad(..), getResourcePath, getUserDataDir,
- fetchItem, readDataFile, report, setResourcePath)
+ fetchItem, report, setResourcePath)
+import Text.Pandoc.Data (readDataFile)
import Text.Pandoc.Error (PandocError(..))
import Text.Pandoc.Extensions (pandocExtensions)
import Text.Pandoc.Logging (LogMessage(..))
diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs
index 6394df251..a1e51e0cf 100644
--- a/src/Text/Pandoc/Class.hs
+++ b/src/Text/Pandoc/Class.hs
@@ -27,5 +27,5 @@ import Text.Pandoc.Class.CommonState (CommonState (..))
import Text.Pandoc.Class.PandocMonad
import Text.Pandoc.Class.PandocIO
import Text.Pandoc.Class.PandocPure
-import Text.Pandoc.Translations (Translations)
+import Text.Pandoc.Translations.Types (Translations)
import Text.Pandoc.Class.Sandbox
diff --git a/src/Text/Pandoc/Class/CommonState.hs b/src/Text/Pandoc/Class/CommonState.hs
index 796a4afd5..4e04b5add 100644
--- a/src/Text/Pandoc/Class/CommonState.hs
+++ b/src/Text/Pandoc/Class/CommonState.hs
@@ -22,7 +22,7 @@ import Data.Text (Text)
import Text.Collate.Lang (Lang)
import Text.Pandoc.MediaBag (MediaBag)
import Text.Pandoc.Logging (LogMessage, Verbosity (WARNING))
-import Text.Pandoc.Translations (Translations)
+import Text.Pandoc.Translations.Types (Translations)
-- | 'CommonState' represents state that is used by all
-- instances of 'PandocMonad'. Normally users should not
diff --git a/src/Text/Pandoc/Class/PandocMonad.hs b/src/Text/Pandoc/Class/PandocMonad.hs
index e108dd13e..8cffde275 100644
--- a/src/Text/Pandoc/Class/PandocMonad.hs
+++ b/src/Text/Pandoc/Class/PandocMonad.hs
@@ -45,22 +45,17 @@ module Text.Pandoc.Class.PandocMonad
, setOutputFile
, setResourcePath
, getResourcePath
- , readDefaultDataFile
- , readDataFile
, readMetadataFile
, fillMediaBag
, toLang
- , setTranslations
- , translateTerm
, makeCanonical
, findFileWithDataFallback
, getTimestamp
+ , checkUserDataDir
) where
-import Codec.Archive.Zip
import Control.Monad.Except (MonadError (catchError, throwError),
MonadTrans, lift, when)
-import Data.List (foldl')
import Data.Time (UTCTime)
import Data.Time.Clock.POSIX (POSIXTime, utcTimeToPOSIXSeconds,
posixSecondsToUTCTime)
@@ -69,30 +64,24 @@ import Network.URI ( escapeURIString, nonStrictRelativeTo,
unEscapeString, parseURIReference, isAllowedInURI,
parseURI, URI(..) )
import System.FilePath ((</>), takeExtension, dropExtension,
- isRelative, splitDirectories, makeRelative)
+ isRelative, makeRelative)
import System.Random (StdGen)
-import Text.Collate.Lang (Lang(..), parseLang, renderLang)
+import Text.Collate.Lang (Lang(..), parseLang)
import Text.Pandoc.Class.CommonState (CommonState (..))
import Text.Pandoc.Definition
import Text.Pandoc.Error
import Text.Pandoc.Logging
import Text.Pandoc.MIME (MimeType, getMimeType)
import Text.Pandoc.MediaBag (MediaBag, lookupMedia, MediaItem(..))
-import Text.Pandoc.Shared (uriPathToPath, safeRead)
-import Text.Pandoc.Translations (Term(..), Translations, lookupTerm,
- readTranslations)
+import Text.Pandoc.Shared (uriPathToPath, safeRead, makeCanonical)
import Text.Pandoc.Walk (walkM)
import Text.Parsec (ParsecT, getPosition, sourceLine, sourceName)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Debug.Trace
-import qualified System.FilePath.Posix as Posix
import qualified Text.Pandoc.MediaBag as MB
import qualified Text.Pandoc.UTF8 as UTF8
-#ifdef EMBED_DATA_FILES
-import Text.Pandoc.Data (dataFiles)
-#endif
-- | The PandocMonad typeclass contains all the potentially
-- IO-related functions used in pandoc's readers and writers.
@@ -295,62 +284,6 @@ toLang (Just s) =
return Nothing
Right l -> return (Just l)
--- | Select the language to use with 'translateTerm'.
--- Note that this does not read a translation file;
--- that is only done the first time 'translateTerm' is
--- used.
-setTranslations :: PandocMonad m => Lang -> m ()
-setTranslations lang =
- modifyCommonState $ \st -> st{ stTranslations = Just (lang, Nothing) }
-
--- | Load term map.
-getTranslations :: PandocMonad m => m Translations
-getTranslations = do
- mbtrans <- getsCommonState stTranslations
- case mbtrans of
- Nothing -> return mempty -- no language defined
- Just (_, Just t) -> return t
- Just (lang, Nothing) -> do -- read from file
- let translationFile = "translations/" <> renderLang lang <> ".yaml"
- let fallbackFile = "translations/" <> langLanguage lang <> ".yaml"
- let getTrans fp = do
- bs <- readDataFile fp
- case readTranslations (UTF8.toText bs) of
- Left e -> do
- report $ CouldNotLoadTranslations (renderLang lang)
- (T.pack fp <> ": " <> e)
- -- make sure we don't try again...
- modifyCommonState $ \st ->
- st{ stTranslations = Nothing }
- return mempty
- Right t -> do
- modifyCommonState $ \st ->
- st{ stTranslations = Just (lang, Just t) }
- return t
- catchError (getTrans $ T.unpack translationFile)
- (\_ ->
- catchError (getTrans $ T.unpack fallbackFile)
- (\e -> do
- report $ CouldNotLoadTranslations (renderLang lang)
- $ case e of
- PandocCouldNotFindDataFileError _ ->
- "data file " <> fallbackFile <> " not found"
- _ -> ""
- -- make sure we don't try again...
- modifyCommonState $ \st -> st{ stTranslations = Nothing }
- return mempty))
-
--- | Get a translation from the current term map.
--- Issue a warning if the term is not defined.
-translateTerm :: PandocMonad m => Term -> m T.Text
-translateTerm term = do
- translations <- getTranslations
- case lookupTerm term translations of
- Just s -> return s
- Nothing -> do
- report $ NoTranslation $ T.pack $ show term
- return ""
-
-- | Specialized version of parseURIReference that disallows
-- single-letter schemes. Reason: these are usually windows absolute
-- paths.
@@ -436,146 +369,6 @@ downloadOrRead s = do
convertSlash '\\' = '/'
convertSlash x = x
--- | Retrieve default reference.docx.
-getDefaultReferenceDocx :: PandocMonad m => m Archive
-getDefaultReferenceDocx = do
- let paths = ["[Content_Types].xml",
- "_rels/.rels",
- "docProps/app.xml",
- "docProps/core.xml",
- "docProps/custom.xml",
- "word/document.xml",
- "word/fontTable.xml",
- "word/footnotes.xml",
- "word/comments.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 = BL.fromChunks . (:[])
- let pathToEntry path = do
- epochtime <- floor . utcTimeToPOSIXSeconds <$> getTimestamp
- contents <- toLazy <$> readDataFile ("docx/" ++ path)
- return $ toEntry path epochtime contents
- datadir <- getUserDataDir
- mbArchive <- case datadir of
- Nothing -> return Nothing
- Just d -> do
- exists <- fileExists (d </> "reference.docx")
- if exists
- then return (Just (d </> "reference.docx"))
- else return Nothing
- case mbArchive of
- Just arch -> toArchive <$> readFileLazy arch
- Nothing -> foldr addEntryToArchive emptyArchive <$>
- mapM pathToEntry paths
-
--- | Retrieve default reference.odt.
-getDefaultReferenceODT :: PandocMonad m => m Archive
-getDefaultReferenceODT = 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 <- (BL.fromChunks . (:[])) `fmap`
- readDataFile ("odt/" ++ path)
- return $ toEntry path epochtime contents
- datadir <- getUserDataDir
- mbArchive <- case datadir of
- Nothing -> return Nothing
- Just d -> do
- exists <- fileExists (d </> "reference.odt")
- if exists
- then return (Just (d </> "reference.odt"))
- else return Nothing
- case mbArchive of
- Just arch -> toArchive <$> readFileLazy arch
- Nothing -> foldr addEntryToArchive emptyArchive <$>
- mapM pathToEntry paths
-
--- | Retrieve default reference.pptx.
-getDefaultReferencePptx :: PandocMonad m => m Archive
-getDefaultReferencePptx = do
- -- We're going to narrow this down substantially once we get it
- -- working.
- let paths = [ "[Content_Types].xml"
- , "_rels/.rels"
- , "docProps/app.xml"
- , "docProps/core.xml"
- , "ppt/_rels/presentation.xml.rels"
- , "ppt/presProps.xml"
- , "ppt/presentation.xml"
- , "ppt/slideLayouts/_rels/slideLayout1.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout2.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout3.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout4.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout5.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout6.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout7.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout8.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout9.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout10.xml.rels"
- , "ppt/slideLayouts/_rels/slideLayout11.xml.rels"
- , "ppt/slideLayouts/slideLayout1.xml"
- , "ppt/slideLayouts/slideLayout10.xml"
- , "ppt/slideLayouts/slideLayout11.xml"
- , "ppt/slideLayouts/slideLayout2.xml"
- , "ppt/slideLayouts/slideLayout3.xml"
- , "ppt/slideLayouts/slideLayout4.xml"
- , "ppt/slideLayouts/slideLayout5.xml"
- , "ppt/slideLayouts/slideLayout6.xml"
- , "ppt/slideLayouts/slideLayout7.xml"
- , "ppt/slideLayouts/slideLayout8.xml"
- , "ppt/slideLayouts/slideLayout9.xml"
- , "ppt/slideMasters/_rels/slideMaster1.xml.rels"
- , "ppt/slideMasters/slideMaster1.xml"
- , "ppt/slides/_rels/slide1.xml.rels"
- , "ppt/slides/slide1.xml"
- , "ppt/slides/_rels/slide2.xml.rels"
- , "ppt/slides/slide2.xml"
- , "ppt/slides/_rels/slide3.xml.rels"
- , "ppt/slides/slide3.xml"
- , "ppt/slides/_rels/slide4.xml.rels"
- , "ppt/slides/slide4.xml"
- , "ppt/tableStyles.xml"
- , "ppt/theme/theme1.xml"
- , "ppt/viewProps.xml"
- -- These relate to notes slides.
- , "ppt/notesMasters/notesMaster1.xml"
- , "ppt/notesMasters/_rels/notesMaster1.xml.rels"
- , "ppt/notesSlides/notesSlide1.xml"
- , "ppt/notesSlides/_rels/notesSlide1.xml.rels"
- , "ppt/notesSlides/notesSlide2.xml"
- , "ppt/notesSlides/_rels/notesSlide2.xml.rels"
- , "ppt/theme/theme2.xml"
- ]
- let toLazy = BL.fromChunks . (:[])
- let pathToEntry path = do
- epochtime <- floor . utcTimeToPOSIXSeconds <$> getCurrentTime
- contents <- toLazy <$> readDataFile ("pptx/" ++ path)
- return $ toEntry path epochtime contents
- datadir <- getUserDataDir
- mbArchive <- case datadir of
- Nothing -> return Nothing
- Just d -> do
- exists <- fileExists (d </> "reference.pptx")
- if exists
- then return (Just (d </> "reference.pptx"))
- else return Nothing
- case mbArchive of
- Just arch -> toArchive <$> readFileLazy arch
- Nothing -> foldr addEntryToArchive emptyArchive <$>
- mapM pathToEntry paths
-
-- | Checks if the file path is relative to a parent directory.
isRelativeToParentDir :: FilePath -> Bool
isRelativeToParentDir fname =
@@ -590,19 +383,6 @@ checkUserDataDir fname =
then getUserDataDir
else return Nothing
---- | Read file from user data directory or,
---- if not found there, from the default data files.
-readDataFile :: PandocMonad m => FilePath -> m B.ByteString
-readDataFile fname = do
- datadir <- checkUserDataDir fname
- case datadir of
- Nothing -> readDefaultDataFile fname
- Just userDir -> do
- exists <- fileExists (userDir </> fname)
- if exists
- then readFileStrict (userDir </> fname)
- else readDefaultDataFile fname
-
-- | Read metadata file from the working directory or, if not found there, from
-- the metadata subdirectory of the user data directory.
readMetadataFile :: PandocMonad m => FilePath -> m B.ByteString
@@ -610,42 +390,6 @@ readMetadataFile fname = findFileWithDataFallback "metadata" fname >>= \case
Nothing -> throwError $ PandocCouldNotFindMetadataFileError (T.pack fname)
Just metadataFile -> readFileStrict metadataFile
--- | Read file from from the default data files.
-readDefaultDataFile :: PandocMonad m => FilePath -> m B.ByteString
-readDefaultDataFile "reference.docx" =
- B.concat . BL.toChunks . fromArchive <$> getDefaultReferenceDocx
-readDefaultDataFile "reference.pptx" =
- B.concat . BL.toChunks . fromArchive <$> getDefaultReferencePptx
-readDefaultDataFile "reference.odt" =
- B.concat . BL.toChunks . fromArchive <$> getDefaultReferenceODT
-readDefaultDataFile fname =
-#ifdef EMBED_DATA_FILES
- case lookup (makeCanonical fname) dataFiles of
- Nothing -> throwError $ PandocCouldNotFindDataFileError $ T.pack fname
- Just contents -> return contents
-#else
- getDataFileName fname' >>= checkExistence >>= readFileStrict
- where fname' = if fname == "MANUAL.txt" then fname else "data" </> fname
-
--- | Returns the input filename unchanged if the file exits, and throws
--- a `PandocCouldNotFindDataFileError` if it doesn't.
-checkExistence :: PandocMonad m => FilePath -> m FilePath
-checkExistence fn = do
- exists <- fileExists fn
- if exists
- then return fn
- else throwError $ PandocCouldNotFindDataFileError $ T.pack fn
-#endif
-
--- | Canonicalizes a file path by removing redundant @.@ and @..@.
-makeCanonical :: FilePath -> FilePath
-makeCanonical = Posix.joinPath . transformPathParts . splitDirectories
- where transformPathParts = reverse . foldl' go []
- go as "." = as
- go ("..":as) ".." = ["..", ".."] <> as
- go (_:as) ".." = as
- go as x = x : as
-
-- | Tries to run an action on a file: for each directory given, a
-- filepath is created from the given filename, and the action is run on
-- that filepath. Returns the result of the first successful execution
diff --git a/src/Text/Pandoc/Data.hs b/src/Text/Pandoc/Data.hs
index fe543edfa..712b53f8e 100644
--- a/src/Text/Pandoc/Data.hs
+++ b/src/Text/Pandoc/Data.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{- |
Module : Text.Pandoc.Data
@@ -8,25 +9,216 @@ Maintainer : John MacFarlane <jgm@berkeley@edu>
Stability : alpha
Portability : portable
-Provide contents data files as Haskell values.
+Access to pandoc's data files.
-}
-module Text.Pandoc.Data (dataFiles) where
-
+module Text.Pandoc.Data ( readDefaultDataFile
+ , readDataFile
+ , getDataFileNames
+ ) where
+import Text.Pandoc.Class (PandocMonad(..), checkUserDataDir, getTimestamp,
+ getUserDataDir, getPOSIXTime)
+import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)
+import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString as B
-import Data.FileEmbed
-import System.FilePath (splitDirectories)
-import qualified System.FilePath.Posix as Posix
-
--- We ensure that the data files are stored using Posix
--- path separators (/), even on Windows.
-dataFiles :: [(FilePath, B.ByteString)]
-dataFiles = map (\(fp, contents) ->
- (Posix.joinPath (splitDirectories fp), contents)) dataFiles'
-
-dataFiles' :: [(FilePath, B.ByteString)]
-dataFiles' = ("MANUAL.txt", $(embedFile "MANUAL.txt")) :
- -- handle the hidden file separately, since embedDir doesn't
- -- include it:
- ("docx/_rels/.rels", $(embedFile "data/docx/_rels/.rels")) :
- ("pptx/_rels/.rels", $(embedFile "data/pptx/_rels/.rels")) :
- $(embedDir "data")
+import Codec.Archive.Zip
+import qualified Data.Text as T
+import Control.Monad.Except (throwError)
+import Text.Pandoc.Error (PandocError(..))
+import System.FilePath
+#ifdef EMBED_DATA_FILES
+import Text.Pandoc.Data.BakedIn (dataFiles)
+import Text.Pandoc.Shared (makeCanonical)
+#else
+import Paths_pandoc (getDataDir)
+import System.Directory (getDirectoryContents)
+#endif
+
+-- | Read file from from the default data files.
+readDefaultDataFile :: PandocMonad m => FilePath -> m B.ByteString
+readDefaultDataFile "reference.docx" =
+ B.concat . BL.toChunks . fromArchive <$> getDefaultReferenceDocx
+readDefaultDataFile "reference.pptx" =
+ B.concat . BL.toChunks . fromArchive <$> getDefaultReferencePptx
+readDefaultDataFile "reference.odt" =
+ B.concat . BL.toChunks . fromArchive <$> getDefaultReferenceODT
+readDefaultDataFile fname =
+#ifdef EMBED_DATA_FILES
+ case lookup (makeCanonical fname) dataFiles of
+ Nothing -> throwError $ PandocCouldNotFindDataFileError $ T.pack fname
+ Just contents -> return contents
+#else
+ getDataFileName fname' >>= checkExistence >>= readFileStrict
+ where fname' = if fname == "MANUAL.txt" then fname else "data" </> fname
+
+-- | Returns the input filename unchanged if the file exits, and throws
+-- a `PandocCouldNotFindDataFileError` if it doesn't.
+checkExistence :: PandocMonad m => FilePath -> m FilePath
+checkExistence fn = do
+ exists <- fileExists fn
+ if exists
+ then return fn
+ else throwError $ PandocCouldNotFindDataFileError $ T.pack fn
+#endif
+
+--- | Read file from user data directory or,
+--- if not found there, from the default data files.
+readDataFile :: PandocMonad m => FilePath -> m B.ByteString
+readDataFile fname = do
+ datadir <- checkUserDataDir fname
+ case datadir of
+ Nothing -> readDefaultDataFile fname
+ Just userDir -> do
+ exists <- fileExists (userDir </> fname)
+ if exists
+ then readFileStrict (userDir </> fname)
+ else readDefaultDataFile fname
+
+-- | Retrieve default reference.docx.
+getDefaultReferenceDocx :: PandocMonad m => m Archive
+getDefaultReferenceDocx = do
+ let paths = ["[Content_Types].xml",
+ "_rels/.rels",
+ "docProps/app.xml",
+ "docProps/core.xml",
+ "docProps/custom.xml",
+ "word/document.xml",
+ "word/fontTable.xml",
+ "word/footnotes.xml",
+ "word/comments.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 = BL.fromChunks . (:[])
+ let pathToEntry path = do
+ epochtime <- floor . utcTimeToPOSIXSeconds <$> getTimestamp
+ contents <- toLazy <$> readDataFile ("docx/" ++ path)
+ return $ toEntry path epochtime contents
+ datadir <- getUserDataDir
+ mbArchive <- case datadir of
+ Nothing -> return Nothing
+ Just d -> do
+ exists <- fileExists (d </> "reference.docx")
+ if exists
+ then return (Just (d </> "reference.docx"))
+ else return Nothing
+ case mbArchive of
+ Just arch -> toArchive <$> readFileLazy arch
+ Nothing -> foldr addEntryToArchive emptyArchive <$>
+ mapM pathToEntry paths
+
+-- | Retrieve default reference.odt.
+getDefaultReferenceODT :: PandocMonad m => m Archive
+getDefaultReferenceODT = 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 <- (BL.fromChunks . (:[])) `fmap`
+ readDataFile ("odt/" ++ path)
+ return $ toEntry path epochtime contents
+ datadir <- getUserDataDir
+ mbArchive <- case datadir of
+ Nothing -> return Nothing
+ Just d -> do
+ exists <- fileExists (d </> "reference.odt")
+ if exists
+ then return (Just (d </> "reference.odt"))
+ else return Nothing
+ case mbArchive of
+ Just arch -> toArchive <$> readFileLazy arch
+ Nothing -> foldr addEntryToArchive emptyArchive <$>
+ mapM pathToEntry paths
+
+-- | Retrieve default reference.pptx.
+getDefaultReferencePptx :: PandocMonad m => m Archive
+getDefaultReferencePptx = do
+ -- We're going to narrow this down substantially once we get it
+ -- working.
+ let paths = [ "[Content_Types].xml"
+ , "_rels/.rels"
+ , "docProps/app.xml"
+ , "docProps/core.xml"
+ , "ppt/_rels/presentation.xml.rels"
+ , "ppt/presProps.xml"
+ , "ppt/presentation.xml"
+ , "ppt/slideLayouts/_rels/slideLayout1.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout2.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout3.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout4.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout5.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout6.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout7.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout8.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout9.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout10.xml.rels"
+ , "ppt/slideLayouts/_rels/slideLayout11.xml.rels"
+ , "ppt/slideLayouts/slideLayout1.xml"
+ , "ppt/slideLayouts/slideLayout10.xml"
+ , "ppt/slideLayouts/slideLayout11.xml"
+ , "ppt/slideLayouts/slideLayout2.xml"
+ , "ppt/slideLayouts/slideLayout3.xml"
+ , "ppt/slideLayouts/slideLayout4.xml"
+ , "ppt/slideLayouts/slideLayout5.xml"
+ , "ppt/slideLayouts/slideLayout6.xml"
+ , "ppt/slideLayouts/slideLayout7.xml"
+ , "ppt/slideLayouts/slideLayout8.xml"
+ , "ppt/slideLayouts/slideLayout9.xml"
+ , "ppt/slideMasters/_rels/slideMaster1.xml.rels"
+ , "ppt/slideMasters/slideMaster1.xml"
+ , "ppt/slides/_rels/slide1.xml.rels"
+ , "ppt/slides/slide1.xml"
+ , "ppt/slides/_rels/slide2.xml.rels"
+ , "ppt/slides/slide2.xml"
+ , "ppt/slides/_rels/slide3.xml.rels"
+ , "ppt/slides/slide3.xml"
+ , "ppt/slides/_rels/slide4.xml.rels"
+ , "ppt/slides/slide4.xml"
+ , "ppt/tableStyles.xml"
+ , "ppt/theme/theme1.xml"
+ , "ppt/viewProps.xml"
+ -- These relate to notes slides.
+ , "ppt/notesMasters/notesMaster1.xml"
+ , "ppt/notesMasters/_rels/notesMaster1.xml.rels"
+ , "ppt/notesSlides/notesSlide1.xml"
+ , "ppt/notesSlides/_rels/notesSlide1.xml.rels"
+ , "ppt/notesSlides/notesSlide2.xml"
+ , "ppt/notesSlides/_rels/notesSlide2.xml.rels"
+ , "ppt/theme/theme2.xml"
+ ]
+ let toLazy = BL.fromChunks . (:[])
+ let pathToEntry path = do
+ epochtime <- floor . utcTimeToPOSIXSeconds <$> getCurrentTime
+ contents <- toLazy <$> readDataFile ("pptx/" ++ path)
+ return $ toEntry path epochtime contents
+ datadir <- getUserDataDir
+ mbArchive <- case datadir of
+ Nothing -> return Nothing
+ Just d -> do
+ exists <- fileExists (d </> "reference.pptx")
+ if exists
+ then return (Just (d </> "reference.pptx"))
+ else return Nothing
+ case mbArchive of
+ Just arch -> toArchive <$> readFileLazy arch
+ Nothing -> foldr addEntryToArchive emptyArchive <$>
+ mapM pathToEntry paths
+
+getDataFileNames :: IO [FilePath]
+getDataFileNames = do
+#ifdef EMBED_DATA_FILES
+ let allDataFiles = map fst dataFiles
+#else
+ allDataFiles <- filter (\x -> x /= "." && x /= "..") <$>
+ (getDataDir >>= getDirectoryContents)
+#endif
+ return $ "reference.docx" : "reference.odt" : "reference.pptx" : allDataFiles
diff --git a/src/Text/Pandoc/Data/BakedIn.hs b/src/Text/Pandoc/Data/BakedIn.hs
new file mode 100644
index 000000000..801a63181
--- /dev/null
+++ b/src/Text/Pandoc/Data/BakedIn.hs
@@ -0,0 +1,32 @@
+{-# LANGUAGE TemplateHaskell #-}
+{- |
+Module : Text.Pandoc.Data.BakedIn
+Copyright : Copyright (C) 2013-2022 John MacFarlane
+License : GNU GPL, version 2 or above
+
+Maintainer : John MacFarlane <jgm@berkeley@edu>
+Stability : alpha
+Portability : portable
+
+Provide contents data files as Haskell values.
+-}
+module Text.Pandoc.Data.BakedIn (dataFiles) where
+
+import qualified Data.ByteString as B
+import Data.FileEmbed
+import System.FilePath (splitDirectories)
+import qualified System.FilePath.Posix as Posix
+
+-- We ensure that the data files are stored using Posix
+-- path separators (/), even on Windows.
+dataFiles :: [(FilePath, B.ByteString)]
+dataFiles = map (\(fp, contents) ->
+ (Posix.joinPath (splitDirectories fp), contents)) dataFiles'
+
+dataFiles' :: [(FilePath, B.ByteString)]
+dataFiles' = ("MANUAL.txt", $(embedFile "MANUAL.txt")) :
+ -- handle the hidden file separately, since embedDir doesn't
+ -- include it:
+ ("docx/_rels/.rels", $(embedFile "data/docx/_rels/.rels")) :
+ ("pptx/_rels/.rels", $(embedFile "data/pptx/_rels/.rels")) :
+ $(embedDir "data")
diff --git a/src/Text/Pandoc/Readers/LaTeX/Inline.hs b/src/Text/Pandoc/Readers/LaTeX/Inline.hs
index e5d7ccb30..6a4346afd 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Inline.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Inline.hs
@@ -30,7 +30,8 @@ import Text.Pandoc.Shared (toRomanNumeral, safeRead)
import Text.Pandoc.Readers.LaTeX.Types (Tok (..), TokType (..))
import Control.Applicative (optional, (<|>))
import Control.Monad (guard, mzero, mplus, unless)
-import Text.Pandoc.Class.PandocMonad (PandocMonad (..), translateTerm)
+import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
+import Text.Pandoc.Translations (translateTerm)
import Text.Pandoc.Readers.LaTeX.Parsing
import Text.Pandoc.Extensions (extensionEnabled, Extension(..))
import Text.Pandoc.Parsing (getOption, updateState, getState, notFollowedBy,
diff --git a/src/Text/Pandoc/Readers/LaTeX/Lang.hs b/src/Text/Pandoc/Readers/LaTeX/Lang.hs
index 3c24bbd00..b80fc9242 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Lang.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Lang.hs
@@ -24,7 +24,8 @@ import Data.Text (Text)
import qualified Data.Text as T
import Text.Pandoc.Shared (extractSpaces)
import Text.Collate.Lang (Lang(..), renderLang)
-import Text.Pandoc.Class (PandocMonad(..), setTranslations)
+import Text.Pandoc.Class (PandocMonad(..))
+import Text.Pandoc.Translations (setTranslations)
import Text.Pandoc.Readers.LaTeX.Parsing
import Text.Pandoc.Parsing (updateState, option, getState, QuoteContext(..),
withQuoteContext)
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index f2bfea0ae..e266b1c34 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -74,6 +74,7 @@ module Text.Pandoc.Shared (
renderTags',
-- * File handling
inDirectory,
+ makeCanonical,
collapseFilePath,
uriPathToPath,
filteredFilesFromArchive,
@@ -824,6 +825,15 @@ inDirectory path action = E.bracket
setCurrentDirectory
(const $ setCurrentDirectory path >> action)
+-- | Canonicalizes a file path by removing redundant @.@ and @..@.
+makeCanonical :: FilePath -> FilePath
+makeCanonical = Posix.joinPath . transformPathParts . splitDirectories
+ where transformPathParts = reverse . foldl' go []
+ go as "." = as
+ go ("..":as) ".." = ["..", ".."] <> as
+ go (_:as) ".." = as
+ go as x = x : as
+
--
-- Error reporting
--
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index e5684f29d..173df273c 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -27,8 +27,9 @@ module Text.Pandoc.Templates ( Template
import System.FilePath ((<.>), (</>), takeFileName)
import Text.DocTemplates (Template, TemplateMonad(..), compileTemplate, renderTemplate)
import Text.Pandoc.Class.CommonState (CommonState(..))
-import Text.Pandoc.Class.PandocMonad (PandocMonad, readDataFile, fetchItem,
+import Text.Pandoc.Class.PandocMonad (PandocMonad, fetchItem,
getCommonState, modifyCommonState)
+import Text.Pandoc.Data (readDataFile)
import qualified Text.Pandoc.UTF8 as UTF8
import Control.Monad.Except (catchError, throwError)
import Data.Text (Text)
diff --git a/src/Text/Pandoc/Translations.hs b/src/Text/Pandoc/Translations.hs
index 3755285ae..f389e7bd5 100644
--- a/src/Text/Pandoc/Translations.hs
+++ b/src/Text/Pandoc/Translations.hs
@@ -11,88 +11,90 @@
Stability : alpha
Portability : portable
-Data types for localization.
-
-Translations are stored in @data/translations/langname.trans@,
-where langname can be the full BCP47 language specifier, or
-just the language part. File format is:
-
-> # A comment, ignored
-> Figure: Figura
-> Index: Indeksi
-
+Functions for getting localized translations of terms.
-}
module Text.Pandoc.Translations (
- Term(..)
- , Translations
- , lookupTerm
+ module Text.Pandoc.Translations.Types
, readTranslations
+ , getTranslations
+ , setTranslations
+ , translateTerm
)
where
-import Data.Aeson.Types (Value(..), FromJSON(..))
-import qualified Data.Aeson.Types as Aeson
-import qualified Data.Map as M
+import Text.Pandoc.Translations.Types
+import Text.Pandoc.Class (PandocMonad(..), CommonState(..), report)
+import Text.Pandoc.Data (readDataFile)
+import Text.Pandoc.Error (PandocError(..))
+import Text.Pandoc.Logging (LogMessage(..))
+import Control.Monad.Except (catchError)
import qualified Data.Text as T
import qualified Data.Yaml as Yaml
-import GHC.Generics (Generic)
-import Text.Pandoc.Shared (safeRead)
import qualified Text.Pandoc.UTF8 as UTF8
import Data.Yaml (prettyPrintParseException)
+import Text.Collate.Lang (Lang(..), renderLang)
-data Term =
- Abstract
- | Appendix
- | Bibliography
- | Cc
- | Chapter
- | Contents
- | Encl
- | Figure
- | Glossary
- | Index
- | Listing
- | ListOfFigures
- | ListOfTables
- | Page
- | Part
- | Preface
- | Proof
- | References
- | See
- | SeeAlso
- | Table
- | To
- deriving (Show, Eq, Ord, Generic, Enum, Read)
-
-newtype Translations = Translations (M.Map Term T.Text)
- deriving (Show, Generic, Semigroup, Monoid)
-
-instance FromJSON Term where
- parseJSON (String t) = case safeRead t of
- Just t' -> pure t'
- Nothing -> Prelude.fail $ "Invalid Term name " ++
- show t
- parseJSON invalid = Aeson.typeMismatch "Term" invalid
-
-instance FromJSON Translations where
- parseJSON o@(Object{}) = do
- xs <- parseJSON o >>= mapM addItem . M.toList
- return $ Translations (M.fromList xs)
- where addItem (k,v) =
- case safeRead k of
- Nothing -> Prelude.fail $ "Invalid Term name " ++ show k
- Just t ->
- case v of
- (String s) -> return (t, T.strip s)
- inv -> Aeson.typeMismatch "String" inv
- parseJSON invalid = Aeson.typeMismatch "Translations" invalid
-
-lookupTerm :: Term -> Translations -> Maybe T.Text
-lookupTerm t (Translations tm) = M.lookup t tm
-
+-- | Parse YAML translations.
readTranslations :: T.Text -> Either T.Text Translations
readTranslations s =
case Yaml.decodeAllEither' $ UTF8.fromText s of
Left err' -> Left $ T.pack $ prettyPrintParseException err'
Right (t:_) -> Right t
Right [] -> Left "empty YAML document"
+
+-- | Select the language to use with 'translateTerm'.
+-- Note that this does not read a translation file;
+-- that is only done the first time 'translateTerm' is
+-- used.
+setTranslations :: PandocMonad m => Lang -> m ()
+setTranslations lang =
+ modifyCommonState $ \st -> st{ stTranslations = Just (lang, Nothing) }
+
+-- | Load term map.
+getTranslations :: PandocMonad m => m Translations
+getTranslations = do
+ mbtrans <- getsCommonState stTranslations
+ case mbtrans of
+ Nothing -> return mempty -- no language defined
+ Just (_, Just t) -> return t
+ Just (lang, Nothing) -> do -- read from file
+ let translationFile = "translations/" <> renderLang lang <> ".yaml"
+ let fallbackFile = "translations/" <> langLanguage lang <> ".yaml"
+ let getTrans fp = do
+ bs <- readDataFile fp
+ case readTranslations (UTF8.toText bs) of
+ Left e -> do
+ report $ CouldNotLoadTranslations (renderLang lang)
+ (T.pack fp <> ": " <> e)
+ -- make sure we don't try again...
+ modifyCommonState $ \st ->
+ st{ stTranslations = Nothing }
+ return mempty
+ Right t -> do
+ modifyCommonState $ \st ->
+ st{ stTranslations = Just (lang, Just t) }
+ return t
+ catchError (getTrans $ T.unpack translationFile)
+ (\_ ->
+ catchError (getTrans $ T.unpack fallbackFile)
+ (\e -> do
+ report $ CouldNotLoadTranslations (renderLang lang)
+ $ case e of
+ PandocCouldNotFindDataFileError _ ->
+ "data file " <> fallbackFile <> " not found"
+ _ -> ""
+ -- make sure we don't try again...
+ modifyCommonState $ \st -> st{ stTranslations = Nothing }
+ return mempty))
+
+-- | Get a translation from the current term map.
+-- Issue a warning if the term is not defined.
+translateTerm :: PandocMonad m => Term -> m T.Text
+translateTerm term = do
+ translations <- getTranslations
+ case lookupTerm term translations of
+ Just s -> return s
+ Nothing -> do
+ report $ NoTranslation $ T.pack $ show term
+ return ""
+
+
diff --git a/src/Text/Pandoc/Translations/Types.hs b/src/Text/Pandoc/Translations/Types.hs
new file mode 100644
index 000000000..370de9217
--- /dev/null
+++ b/src/Text/Pandoc/Translations/Types.hs
@@ -0,0 +1,88 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE OverloadedStrings #-}
+{- |
+ Module : Text.Pandoc.Translations.Types
+ Copyright : Copyright (C) 2017-2022 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <[email protected]>
+ Stability : alpha
+ Portability : portable
+
+Data types for localization.
+
+Translations are stored in @data/translations/langname.trans@,
+where langname can be the full BCP47 language specifier, or
+just the language part. File format is:
+
+> # A comment, ignored
+> Figure: Figura
+> Index: Indeksi
+
+-}
+module Text.Pandoc.Translations.Types (
+ Term(..)
+ , Translations
+ , lookupTerm
+ )
+where
+import Data.Aeson.Types (Value(..), FromJSON(..))
+import qualified Data.Aeson.Types as Aeson
+import qualified Data.Map as M
+import qualified Data.Text as T
+import GHC.Generics (Generic)
+import Text.Pandoc.Shared (safeRead)
+
+data Term =
+ Abstract
+ | Appendix
+ | Bibliography
+ | Cc
+ | Chapter
+ | Contents
+ | Encl
+ | Figure
+ | Glossary
+ | Index
+ | Listing
+ | ListOfFigures
+ | ListOfTables
+ | Page
+ | Part
+ | Preface
+ | Proof
+ | References
+ | See
+ | SeeAlso
+ | Table
+ | To
+ deriving (Show, Eq, Ord, Generic, Enum, Read)
+
+newtype Translations = Translations (M.Map Term T.Text)
+ deriving (Show, Generic, Semigroup, Monoid)
+
+instance FromJSON Term where
+ parseJSON (String t) = case safeRead t of
+ Just t' -> pure t'
+ Nothing -> Prelude.fail $ "Invalid Term name " ++
+ show t
+ parseJSON invalid = Aeson.typeMismatch "Term" invalid
+
+instance FromJSON Translations where
+ parseJSON o@(Object{}) = do
+ xs <- parseJSON o >>= mapM addItem . M.toList
+ return $ Translations (M.fromList xs)
+ where addItem (k,v) =
+ case safeRead k of
+ Nothing -> Prelude.fail $ "Invalid Term name " ++ show k
+ Just t ->
+ case v of
+ (String s) -> return (t, T.strip s)
+ inv -> Aeson.typeMismatch "String" inv
+ parseJSON invalid = Aeson.typeMismatch "Translations" invalid
+
+-- | Lookup a term in a 'Translations'.
+lookupTerm :: Term -> Translations -> Maybe T.Text
+lookupTerm t (Translations tm) = M.lookup t tm
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 8264ed4bf..5adf1efcb 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -36,11 +36,12 @@ import Data.Time.Clock.POSIX
import Data.Digest.Pure.SHA (sha1, showDigest)
import Skylighting
import Text.Collate.Lang (renderLang)
-import Text.Pandoc.Class (PandocMonad, report, toLang, translateTerm,
- getMediaBag)
+import Text.Pandoc.Class (PandocMonad, report, toLang, getMediaBag)
+import Text.Pandoc.Translations (translateTerm)
import Text.Pandoc.MediaBag (lookupMedia, MediaItem(..))
import qualified Text.Pandoc.Translations as Term
import qualified Text.Pandoc.Class.PandocMonad as P
+import Text.Pandoc.Data (readDataFile, readDefaultDataFile)
import Data.Time
import Text.Pandoc.UTF8 (fromTextLazy)
import Text.Pandoc.Definition
@@ -119,13 +120,13 @@ writeDocx opts doc = do
utctime <- P.getTimestamp
oldUserDataDir <- P.getUserDataDir
P.setUserDataDir Nothing
- res <- P.readDefaultDataFile "reference.docx"
+ res <- readDefaultDataFile "reference.docx"
P.setUserDataDir oldUserDataDir
let distArchive = toArchive $ BL.fromStrict res
refArchive <- case writerReferenceDoc opts of
Just f -> toArchive <$> P.readFileLazy f
Nothing -> toArchive . BL.fromStrict <$>
- P.readDataFile "reference.docx"
+ readDataFile "reference.docx"
parsedDoc <- parseXml refArchive distArchive "word/document.xml"
let wname f qn = qPrefix qn == Just "w" && f (qName qn)
diff --git a/src/Text/Pandoc/Writers/Docx/Table.hs b/src/Text/Pandoc/Writers/Docx/Table.hs
index 9b26c8b44..0c154d443 100644
--- a/src/Text/Pandoc/Writers/Docx/Table.hs
+++ b/src/Text/Pandoc/Writers/Docx/Table.hs
@@ -27,7 +27,8 @@ import Text.Pandoc.Definition
RowSpan(..),
ColSpan(..),
ColWidth(ColWidth) )
-import Text.Pandoc.Class.PandocMonad (PandocMonad, translateTerm)
+import Text.Pandoc.Class.PandocMonad (PandocMonad)
+import Text.Pandoc.Translations (translateTerm)
import Text.Pandoc.Writers.Docx.Types
( WS,
WriterState(stNextTableNum, stInTable),
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index c38844ce0..e303cae0f 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -38,6 +38,7 @@ import Text.Pandoc.Builder (fromList, setMeta)
import Text.Pandoc.Writers.Shared (ensureValidXmlIdentifiers)
import Text.Pandoc.Class (PandocMonad, report)
import qualified Text.Pandoc.Class.PandocPure as P
+import Text.Pandoc.Data (readDataFile)
import qualified Text.Pandoc.Class.PandocMonad as P
import Data.Time
import Text.Pandoc.Definition
@@ -460,7 +461,7 @@ pandocToEPUB version opts doc = do
-- stylesheet
stylesheets <- case epubStylesheets metadata of
[] -> (\x -> [B.fromChunks [x]]) <$>
- P.readDataFile "epub.css"
+ readDataFile "epub.css"
fs -> mapM P.readFileLazy fs
stylesheetEntries <- zipWithM
(\bs n -> mkEntry ("styles/stylesheet" ++ show n ++ ".css") bs)
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 06d8d4e8a..8d293e6a4 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -68,8 +68,8 @@ import System.FilePath (takeBaseName)
import Text.Blaze.Html.Renderer.Text (renderHtml)
import qualified Text.Blaze.XHtml1.Transitional as H
import qualified Text.Blaze.XHtml1.Transitional.Attributes as A
-import Text.Pandoc.Class.PandocMonad (PandocMonad, report,
- translateTerm)
+import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
+import Text.Pandoc.Translations (translateTerm)
import Text.Pandoc.Class.PandocPure (runPure)
import Text.Pandoc.Error
import Text.Pandoc.Logging
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index 2db863591..77289faea 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -27,6 +27,7 @@ import System.FilePath (takeDirectory, takeExtension, (<.>))
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.Data (readDataFile)
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError(..))
import Text.Pandoc.ImageSize
@@ -77,7 +78,7 @@ pandocToODT opts doc@(Pandoc meta _) = do
case writerReferenceDoc opts of
Just f -> liftM toArchive $ lift $ P.readFileLazy f
Nothing -> lift $ toArchive . B.fromStrict <$>
- P.readDataFile "reference.odt"
+ readDataFile "reference.odt"
-- handle formulas and pictures
-- picEntriesRef <- P.newIORef ([] :: [Entry])
doc' <- walkM (transformPicMath opts) $ walk fixDisplayMath doc
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 8af64969b..7cf8b4bd6 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -26,8 +26,8 @@ import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import Text.Collate.Lang (Lang (..), parseLang)
-import Text.Pandoc.Class.PandocMonad (PandocMonad, report, translateTerm,
- setTranslations, toLang)
+import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang)
+import Text.Pandoc.Translations (translateTerm, setTranslations)
import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Logging
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
index 9b14b2311..3b87d8c1d 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
@@ -47,6 +47,7 @@ import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Error (PandocError(..))
import qualified Text.Pandoc.Class.PandocMonad as P
+import Text.Pandoc.Data (readDataFile, readDefaultDataFile)
import Text.Pandoc.Options
import Text.Pandoc.MIME
import qualified Data.ByteString.Lazy as BL
@@ -572,11 +573,11 @@ presentationToArchive :: PandocMonad m
=> WriterOptions -> Meta -> Presentation -> m Archive
presentationToArchive opts meta pres = do
distArchive <- toArchive . BL.fromStrict <$>
- P.readDefaultDataFile "reference.pptx"
+ readDefaultDataFile "reference.pptx"
refArchive <- case writerReferenceDoc opts of
Just f -> toArchive <$> P.readFileLazy f
Nothing -> toArchive . BL.fromStrict <$>
- P.readDataFile "reference.pptx"
+ readDataFile "reference.pptx"
let (referenceLayouts, defaultReferenceLayouts) =
(getLayoutsFromArchive refArchive, getLayoutsFromArchive distArchive)