{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
#ifdef EMBED_DATA_FILES
{-# LANGUAGE TemplateHaskell #-}
#endif
{- |
Module      : Text.Pandoc.Data
Copyright   : Copyright (C) 2013-2023 John MacFarlane
License     : GNU GPL, version 2 or above

Maintainer  : John MacFarlane <jgm@berkeley@edu>
Stability   : alpha
Portability : portable

Access to pandoc's data files.
-}
module Text.Pandoc.Data ( readDefaultDataFile
                        , readDataFile
                        , getDataFileNames
                        , defaultUserDataDir
                        ) 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 Codec.Archive.Zip
import qualified Data.Text as T
import Control.Monad.Except (throwError)
import Text.Pandoc.Error (PandocError(..))
import System.FilePath
import System.Directory
import qualified Control.Exception as E
#ifdef EMBED_DATA_FILES
import Text.Pandoc.Data.BakedIn (dataFiles)
import Text.Pandoc.Shared (makeCanonical)
#else
import Paths_pandoc (getDataDir)
#endif

-- | Read file from from the default data files.
readDefaultDataFile :: PandocMonad m => FilePath -> m B.ByteString
readDefaultDataFile :: forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readDefaultDataFile FilePath
"reference.docx" =
  [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString)
-> (Archive -> [ByteString]) -> Archive -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
BL.toChunks (ByteString -> [ByteString])
-> (Archive -> ByteString) -> Archive -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Archive -> ByteString
fromArchive (Archive -> ByteString) -> m Archive -> m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Archive
forall (m :: * -> *). PandocMonad m => m Archive
getDefaultReferenceDocx
readDefaultDataFile FilePath
"reference.pptx" =
  [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString)
-> (Archive -> [ByteString]) -> Archive -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
BL.toChunks (ByteString -> [ByteString])
-> (Archive -> ByteString) -> Archive -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Archive -> ByteString
fromArchive (Archive -> ByteString) -> m Archive -> m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Archive
forall (m :: * -> *). PandocMonad m => m Archive
getDefaultReferencePptx
readDefaultDataFile FilePath
"reference.odt" =
  [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString)
-> (Archive -> [ByteString]) -> Archive -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
BL.toChunks (ByteString -> [ByteString])
-> (Archive -> ByteString) -> Archive -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Archive -> ByteString
fromArchive (Archive -> ByteString) -> m Archive -> m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m Archive
forall (m :: * -> *). PandocMonad m => m Archive
getDefaultReferenceODT
readDefaultDataFile FilePath
fname =
#ifdef EMBED_DATA_FILES
  case lookup (makeCanonical fname) dataFiles of
    Nothing       -> throwError $ PandocCouldNotFindDataFileError $ T.pack fname
    Just contents -> return contents
#else
  FilePath -> m FilePath
forall (m :: * -> *). PandocMonad m => FilePath -> m FilePath
getDataFileName FilePath
fname' m FilePath -> (FilePath -> m FilePath) -> m FilePath
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FilePath -> m FilePath
forall (m :: * -> *). PandocMonad m => FilePath -> m FilePath
checkExistence m FilePath -> (FilePath -> m ByteString) -> m ByteString
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readFileStrict
    where fname' :: FilePath
fname' = if FilePath
fname FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"MANUAL.txt" then FilePath
fname else FilePath
"data" FilePath -> FilePath -> FilePath
</> FilePath
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 :: forall (m :: * -> *). PandocMonad m => FilePath -> m FilePath
checkExistence FilePath
fn = do
  Bool
exists <- FilePath -> m Bool
forall (m :: * -> *). PandocMonad m => FilePath -> m Bool
fileExists FilePath
fn
  if Bool
exists
     then FilePath -> m FilePath
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
fn
     else PandocError -> m FilePath
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m FilePath) -> PandocError -> m FilePath
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocCouldNotFindDataFileError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack FilePath
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 :: forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readDataFile FilePath
fname = do
  Maybe FilePath
datadir <- FilePath -> m (Maybe FilePath)
forall (m :: * -> *).
PandocMonad m =>
FilePath -> m (Maybe FilePath)
checkUserDataDir FilePath
fname
  case Maybe FilePath
datadir of
       Maybe FilePath
Nothing -> FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readDefaultDataFile FilePath
fname
       Just FilePath
userDir -> do
         Bool
exists <- FilePath -> m Bool
forall (m :: * -> *). PandocMonad m => FilePath -> m Bool
fileExists (FilePath
userDir FilePath -> FilePath -> FilePath
</> FilePath
fname)
         if Bool
exists
            then FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readFileStrict (FilePath
userDir FilePath -> FilePath -> FilePath
</> FilePath
fname)
            else FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readDefaultDataFile FilePath
fname

-- | Retrieve default reference.docx.
getDefaultReferenceDocx :: PandocMonad m => m Archive
getDefaultReferenceDocx :: forall (m :: * -> *). PandocMonad m => m Archive
getDefaultReferenceDocx = do
  let paths :: [FilePath]
paths = [FilePath
"[Content_Types].xml",
               FilePath
"_rels/.rels",
               FilePath
"docProps/app.xml",
               FilePath
"docProps/core.xml",
               FilePath
"docProps/custom.xml",
               FilePath
"word/document.xml",
               FilePath
"word/fontTable.xml",
               FilePath
"word/footnotes.xml",
               FilePath
"word/comments.xml",
               FilePath
"word/numbering.xml",
               FilePath
"word/settings.xml",
               FilePath
"word/webSettings.xml",
               FilePath
"word/styles.xml",
               FilePath
"word/_rels/document.xml.rels",
               FilePath
"word/_rels/footnotes.xml.rels",
               FilePath
"word/theme/theme1.xml"]
  let toLazy :: ByteString -> ByteString
toLazy = [ByteString] -> ByteString
BL.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[])
  let pathToEntry :: FilePath -> m Entry
pathToEntry FilePath
path = do
        Integer
epochtime <- POSIXTime -> Integer
forall b. Integral b => POSIXTime -> b
forall a b. (RealFrac a, Integral b) => a -> b
floor (POSIXTime -> Integer)
-> (UTCTime -> POSIXTime) -> UTCTime -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> POSIXTime
utcTimeToPOSIXSeconds (UTCTime -> Integer) -> m UTCTime -> m Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m UTCTime
forall (m :: * -> *). PandocMonad m => m UTCTime
getTimestamp
        ByteString
contents <- ByteString -> ByteString
toLazy (ByteString -> ByteString) -> m ByteString -> m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readDataFile (FilePath
"docx/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
path)
        Entry -> m Entry
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Entry -> m Entry) -> Entry -> m Entry
forall a b. (a -> b) -> a -> b
$ FilePath -> Integer -> ByteString -> Entry
toEntry FilePath
path Integer
epochtime ByteString
contents
  Maybe FilePath
datadir <- m (Maybe FilePath)
forall (m :: * -> *). PandocMonad m => m (Maybe FilePath)
getUserDataDir
  Maybe FilePath
mbArchive <- case Maybe FilePath
datadir of
                    Maybe FilePath
Nothing   -> Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
                    Just FilePath
d    -> do
                       Bool
exists <- FilePath -> m Bool
forall (m :: * -> *). PandocMonad m => FilePath -> m Bool
fileExists (FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
"reference.docx")
                       if Bool
exists
                          then Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
"reference.docx"))
                          else Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
  case Maybe FilePath
mbArchive of
     Just FilePath
arch -> ByteString -> Archive
toArchive (ByteString -> Archive) -> m ByteString -> m Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readFileLazy FilePath
arch
     Maybe FilePath
Nothing   -> (Entry -> Archive -> Archive) -> Archive -> [Entry] -> Archive
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Entry -> Archive -> Archive
addEntryToArchive Archive
emptyArchive ([Entry] -> Archive) -> m [Entry] -> m Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                     (FilePath -> m Entry) -> [FilePath] -> m [Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> m Entry
forall {m :: * -> *}. PandocMonad m => FilePath -> m Entry
pathToEntry [FilePath]
paths

-- | Retrieve default reference.odt.
getDefaultReferenceODT :: PandocMonad m => m Archive
getDefaultReferenceODT :: forall (m :: * -> *). PandocMonad m => m Archive
getDefaultReferenceODT = do
  let paths :: [FilePath]
paths = [FilePath
"mimetype",
               FilePath
"manifest.rdf",
               FilePath
"styles.xml",
               FilePath
"content.xml",
               FilePath
"meta.xml",
               FilePath
"META-INF/manifest.xml"]
  let pathToEntry :: FilePath -> m Entry
pathToEntry FilePath
path = do Integer
epochtime <- POSIXTime -> Integer
forall b. Integral b => POSIXTime -> b
forall a b. (RealFrac a, Integral b) => a -> b
floor (POSIXTime -> Integer) -> m POSIXTime -> m Integer
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` m POSIXTime
forall (m :: * -> *). PandocMonad m => m POSIXTime
getPOSIXTime
                            ByteString
contents <- ([ByteString] -> ByteString
BL.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[])) (ByteString -> ByteString) -> m ByteString -> m ByteString
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                                          FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readDataFile (FilePath
"odt/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
path)
                            Entry -> m Entry
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Entry -> m Entry) -> Entry -> m Entry
forall a b. (a -> b) -> a -> b
$ FilePath -> Integer -> ByteString -> Entry
toEntry FilePath
path Integer
epochtime ByteString
contents
  Maybe FilePath
datadir <- m (Maybe FilePath)
forall (m :: * -> *). PandocMonad m => m (Maybe FilePath)
getUserDataDir
  Maybe FilePath
mbArchive <- case Maybe FilePath
datadir of
                    Maybe FilePath
Nothing   -> Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
                    Just FilePath
d    -> do
                       Bool
exists <- FilePath -> m Bool
forall (m :: * -> *). PandocMonad m => FilePath -> m Bool
fileExists (FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
"reference.odt")
                       if Bool
exists
                          then Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
"reference.odt"))
                          else Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
  case Maybe FilePath
mbArchive of
     Just FilePath
arch -> ByteString -> Archive
toArchive (ByteString -> Archive) -> m ByteString -> m Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readFileLazy FilePath
arch
     Maybe FilePath
Nothing   -> (Entry -> Archive -> Archive) -> Archive -> [Entry] -> Archive
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Entry -> Archive -> Archive
addEntryToArchive Archive
emptyArchive ([Entry] -> Archive) -> m [Entry] -> m Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                     (FilePath -> m Entry) -> [FilePath] -> m [Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> m Entry
forall {m :: * -> *}. PandocMonad m => FilePath -> m Entry
pathToEntry [FilePath]
paths

-- | Retrieve default reference.pptx.
getDefaultReferencePptx :: PandocMonad m => m Archive
getDefaultReferencePptx :: forall (m :: * -> *). PandocMonad m => m Archive
getDefaultReferencePptx = do
  -- We're going to narrow this down substantially once we get it
  -- working.
  let paths :: [FilePath]
paths = [ FilePath
"[Content_Types].xml"
              , FilePath
"_rels/.rels"
              , FilePath
"docProps/app.xml"
              , FilePath
"docProps/core.xml"
              , FilePath
"ppt/_rels/presentation.xml.rels"
              , FilePath
"ppt/presProps.xml"
              , FilePath
"ppt/presentation.xml"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout1.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout2.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout3.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout4.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout5.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout6.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout7.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout8.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout9.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout10.xml.rels"
              , FilePath
"ppt/slideLayouts/_rels/slideLayout11.xml.rels"
              , FilePath
"ppt/slideLayouts/slideLayout1.xml"
              , FilePath
"ppt/slideLayouts/slideLayout10.xml"
              , FilePath
"ppt/slideLayouts/slideLayout11.xml"
              , FilePath
"ppt/slideLayouts/slideLayout2.xml"
              , FilePath
"ppt/slideLayouts/slideLayout3.xml"
              , FilePath
"ppt/slideLayouts/slideLayout4.xml"
              , FilePath
"ppt/slideLayouts/slideLayout5.xml"
              , FilePath
"ppt/slideLayouts/slideLayout6.xml"
              , FilePath
"ppt/slideLayouts/slideLayout7.xml"
              , FilePath
"ppt/slideLayouts/slideLayout8.xml"
              , FilePath
"ppt/slideLayouts/slideLayout9.xml"
              , FilePath
"ppt/slideMasters/_rels/slideMaster1.xml.rels"
              , FilePath
"ppt/slideMasters/slideMaster1.xml"
              , FilePath
"ppt/slides/_rels/slide1.xml.rels"
              , FilePath
"ppt/slides/slide1.xml"
              , FilePath
"ppt/slides/_rels/slide2.xml.rels"
              , FilePath
"ppt/slides/slide2.xml"
              , FilePath
"ppt/slides/_rels/slide3.xml.rels"
              , FilePath
"ppt/slides/slide3.xml"
              , FilePath
"ppt/slides/_rels/slide4.xml.rels"
              , FilePath
"ppt/slides/slide4.xml"
              , FilePath
"ppt/tableStyles.xml"
              , FilePath
"ppt/theme/theme1.xml"
              , FilePath
"ppt/viewProps.xml"
              -- These relate to notes slides.
              , FilePath
"ppt/notesMasters/notesMaster1.xml"
              , FilePath
"ppt/notesMasters/_rels/notesMaster1.xml.rels"
              , FilePath
"ppt/notesSlides/notesSlide1.xml"
              , FilePath
"ppt/notesSlides/_rels/notesSlide1.xml.rels"
              , FilePath
"ppt/notesSlides/notesSlide2.xml"
              , FilePath
"ppt/notesSlides/_rels/notesSlide2.xml.rels"
              , FilePath
"ppt/theme/theme2.xml"
              ]
  let toLazy :: ByteString -> ByteString
toLazy = [ByteString] -> ByteString
BL.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[])
  let pathToEntry :: FilePath -> m Entry
pathToEntry FilePath
path = do
        Integer
epochtime <- POSIXTime -> Integer
forall b. Integral b => POSIXTime -> b
forall a b. (RealFrac a, Integral b) => a -> b
floor (POSIXTime -> Integer) -> m POSIXTime -> m Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m POSIXTime
forall (m :: * -> *). PandocMonad m => m POSIXTime
getPOSIXTime
        ByteString
contents <- ByteString -> ByteString
toLazy (ByteString -> ByteString) -> m ByteString -> m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readDataFile (FilePath
"pptx/" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
path)
        Entry -> m Entry
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Entry -> m Entry) -> Entry -> m Entry
forall a b. (a -> b) -> a -> b
$ FilePath -> Integer -> ByteString -> Entry
toEntry FilePath
path Integer
epochtime ByteString
contents
  Maybe FilePath
datadir <- m (Maybe FilePath)
forall (m :: * -> *). PandocMonad m => m (Maybe FilePath)
getUserDataDir
  Maybe FilePath
mbArchive <- case Maybe FilePath
datadir of
                    Maybe FilePath
Nothing   -> Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
                    Just FilePath
d    -> do
                       Bool
exists <- FilePath -> m Bool
forall (m :: * -> *). PandocMonad m => FilePath -> m Bool
fileExists (FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
"reference.pptx")
                       if Bool
exists
                          then Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
"reference.pptx"))
                          else Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
  case Maybe FilePath
mbArchive of
     Just FilePath
arch -> ByteString -> Archive
toArchive (ByteString -> Archive) -> m ByteString -> m Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> m ByteString
forall (m :: * -> *). PandocMonad m => FilePath -> m ByteString
readFileLazy FilePath
arch
     Maybe FilePath
Nothing   -> (Entry -> Archive -> Archive) -> Archive -> [Entry] -> Archive
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Entry -> Archive -> Archive
addEntryToArchive Archive
emptyArchive ([Entry] -> Archive) -> m [Entry] -> m Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                     (FilePath -> m Entry) -> [FilePath] -> m [Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FilePath -> m Entry
forall {m :: * -> *}. PandocMonad m => FilePath -> m Entry
pathToEntry [FilePath]
paths

getDataFileNames :: IO [FilePath]
getDataFileNames :: IO [FilePath]
getDataFileNames = do
#ifdef EMBED_DATA_FILES
  let allDataFiles = map fst dataFiles
#else
  [FilePath]
allDataFiles <- (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (\FilePath
x -> FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
"." Bool -> Bool -> Bool
&& FilePath
x FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
/= FilePath
"..") ([FilePath] -> [FilePath]) -> IO [FilePath] -> IO [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                      (IO FilePath
getDataDir IO FilePath -> (FilePath -> IO [FilePath]) -> IO [FilePath]
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FilePath -> IO [FilePath]
getDirectoryContents)
#endif
  [FilePath] -> IO [FilePath]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
forall a b. (a -> b) -> a -> b
$ FilePath
"reference.docx" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath
"reference.odt" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: FilePath
"reference.pptx" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
allDataFiles

-- | Return appropriate user data directory for platform.  We use
-- XDG_DATA_HOME (or its default value), but for backwards compatibility,
-- we fall back to the legacy user data directory ($HOME/.pandoc on *nix)
-- if the XDG_DATA_HOME is missing and this exists.  If neither directory
-- is present, we return the XDG data directory.  If the XDG data directory
-- is not defined (e.g. because we are in an environment where $HOME is
-- not defined), we return the empty string.
defaultUserDataDir :: IO FilePath
defaultUserDataDir :: IO FilePath
defaultUserDataDir = do
  FilePath
xdgDir <- IO FilePath -> (SomeException -> IO FilePath) -> IO FilePath
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (XdgDirectory -> FilePath -> IO FilePath
getXdgDirectory XdgDirectory
XdgData FilePath
"pandoc")
               (\(SomeException
_ :: E.SomeException) -> FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
forall a. Monoid a => a
mempty)
  Bool
xdgExists <- FilePath -> IO Bool
doesDirectoryExist FilePath
xdgDir
  FilePath
legacyDir <- IO FilePath -> (SomeException -> IO FilePath) -> IO FilePath
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (FilePath -> IO FilePath
getAppUserDataDirectory FilePath
"pandoc")
                (\(SomeException
_ :: E.SomeException) -> FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
forall a. Monoid a => a
mempty)
  Bool
legacyDirExists <- FilePath -> IO Bool
doesDirectoryExist FilePath
legacyDir
  if Bool -> Bool
not Bool
xdgExists Bool -> Bool -> Bool
&& Bool
legacyDirExists
     then FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
legacyDir
     else FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
xdgDir