diff --git a/benchmark/benchmark-pandoc.hs b/benchmark/benchmark-pandoc.hs index 728e45b56..015d0135a 100644 --- a/benchmark/benchmark-pandoc.hs +++ b/benchmark/benchmark-pandoc.hs @@ -1,5 +1,5 @@ import Text.Pandoc -import Text.Pandoc.Shared (readDataFile, normalize) +import Text.Pandoc.Shared (readDataFileUTF8, normalize) import Criterion.Main import Criterion.Config import Text.JSON.Generic @@ -35,8 +35,8 @@ main :: IO () main = do args <- getArgs (conf,_) <- parseArgs defaultConfig{ cfgSamples = Last $ Just 20 } defaultOptions args - inp <- readDataFile (Just ".") "README" - inp2 <- readDataFile (Just ".") "tests/testsuite.txt" + inp <- readDataFileUTF8 (Just ".") "README" + inp2 <- readDataFileUTF8 (Just ".") "tests/testsuite.txt" let opts = def{ readerSmart = True } let doc = readMarkdown opts $ inp ++ unlines (drop 3 $ lines inp2) let readerBs = map (readerBench doc) readers diff --git a/pandoc.cabal b/pandoc.cabal index 40d76be3f..8b40344cf 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -187,6 +187,9 @@ Source-repository head Flag blaze_html_0_5 Description: Use blaze-html 0.5 and blaze-markup 0.5 Default: True +Flag embed_data_files + Description: Embed data files in binary for relocatable executable. + Default: False Library Build-Depends: base >= 4.2 && <5, @@ -224,6 +227,10 @@ Library else build-depends: blaze-html >= 0.4.3.0 && < 0.5 + if flag(embed_data_files) + build-depends: file-embed >= 0.0.4 && < 0.1, + template-haskell >= 2.4 && < 2.9 + cpp-options: -DEMBED_DATA_FILES if impl(ghc >= 7.0.1) Ghc-Options: -O2 -rtsopts -Wall -fno-warn-unused-do-bind -dno-debug-output else diff --git a/pandoc.hs b/pandoc.hs index 7268f57f8..2300076c2 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -33,7 +33,7 @@ module Main where import Text.Pandoc import Text.Pandoc.PDF (tex2pdf) import Text.Pandoc.Readers.LaTeX (handleIncludes) -import Text.Pandoc.Shared ( tabFilter, readDataFile, safeRead, +import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8, safeRead, headerShift, normalize, err, warn ) import Text.Pandoc.XML ( toEntities, fromEntities ) import Text.Pandoc.SelfContained ( makeSelfContained ) @@ -889,24 +889,27 @@ main = do E.catch (UTF8.readFile tp') (\e -> if isDoesNotExistError e then E.catch - (readDataFile datadir $ - "templates" tp') + (readDataFileUTF8 datadir + ("templates" tp')) (\e' -> let _ = (e' :: E.SomeException) in throwIO e') else throwIO e) variables' <- case mathMethod of LaTeXMathML Nothing -> do - s <- readDataFile datadir $ "data" "LaTeXMathML.js" + s <- readDataFileUTF8 datadir + ("data" "LaTeXMathML.js") return $ ("mathml-script", s) : variables MathML Nothing -> do - s <- readDataFile datadir $ "data""MathMLinHTML.js" + s <- readDataFileUTF8 datadir + ("data""MathMLinHTML.js") return $ ("mathml-script", s) : variables _ -> return variables variables'' <- if "dzslides" `isPrefixOf` writerName' then do - dztempl <- readDataFile datadir $ "dzslides" "template.html" + dztempl <- readDataFileUTF8 datadir + ("dzslides" "template.html") let dzcore = unlines $ dropWhile (not . isPrefixOf "