blob: b8e189440df0eaa30f47cd7faa426338b17192e8 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
|
{-# LANGUAGE TemplateHaskell #-}
module Text.Pandoc.Data (dataFiles) where
import Data.FileEmbed
import qualified Data.ByteString as B
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")) :
$(embedDir "data")
|