This way we have uniform separators, whether on Windows or Linux. This should solve a problem where on some Windows versions the data files weren't being found. Closes #2459.
15 lines
572 B
Text
15 lines
572 B
Text
{-# LANGUAGE OverloadedStrings #-}
|
|
-- to be processed using hsb2hs
|
|
module Text.Pandoc.Data (dataFiles) where
|
|
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' = ("README", %blob "README") : %blobs "data"
|