Use hsb2hs preprocessor instead of TH for embed_data_files.
This should work on Windows, unlike the TH solution with file-embed.
This commit is contained in:
parent
daeb52d4e0
commit
fe337b07f7
4 changed files with 23 additions and 9 deletions
1
INSTALL
1
INSTALL
|
@ -94,6 +94,7 @@ It is possible to compile pandoc such that the data files
|
|||
pandoc uses are embedded in the binary. The resulting binary
|
||||
can be run from any directory and is completely self-contained.
|
||||
|
||||
cabal install hsb2hs # a required build tool
|
||||
cabal install --flags="embed_data_files" citeproc-hs
|
||||
cabal configure --flags="embed_data_files"
|
||||
cabal build
|
||||
|
|
18
Setup.hs
18
Setup.hs
|
@ -1,6 +1,7 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
|
||||
import Distribution.Simple
|
||||
import Distribution.Simple.PreProcess
|
||||
import Distribution.Simple.Setup
|
||||
(copyDest, copyVerbosity, fromFlag, installVerbosity, BuildFlags(..))
|
||||
import Distribution.PackageDescription (PackageDescription(..), Executable(..))
|
||||
|
@ -8,10 +9,11 @@ import Distribution.Simple.LocalBuildInfo
|
|||
(LocalBuildInfo(..), absoluteInstallDirs)
|
||||
import Distribution.Verbosity ( Verbosity, silent )
|
||||
import Distribution.Simple.InstallDirs (mandir, CopyDest (NoCopyDest))
|
||||
import Distribution.Simple.Utils (installOrdinaryFiles)
|
||||
import Distribution.Simple.Utils (installOrdinaryFiles, info)
|
||||
import Prelude hiding (catch)
|
||||
import System.Process ( rawSystem )
|
||||
import System.FilePath ( (</>) )
|
||||
import System.Directory ( findExecutable )
|
||||
import System.Exit
|
||||
|
||||
main :: IO ()
|
||||
|
@ -29,6 +31,7 @@ main = do
|
|||
, instHook = \pkgdescr ->
|
||||
(instHook simpleUserHooks) pkgdescr{ executables =
|
||||
[x | x <- executables pkgdescr, exeName x /= "make-pandoc-man-pages"] }
|
||||
, hookedPreProcessors = [ppBlobSuffixHandler]
|
||||
}
|
||||
exitWith ExitSuccess
|
||||
|
||||
|
@ -53,3 +56,16 @@ installManpages pkg lbi verbosity copy =
|
|||
installOrdinaryFiles verbosity (mandir (absoluteInstallDirs pkg lbi copy))
|
||||
(zip (repeat manDir) manpages)
|
||||
|
||||
ppBlobSuffixHandler :: PPSuffixHandler
|
||||
ppBlobSuffixHandler = ("hsb", \_ _ ->
|
||||
PreProcessor {
|
||||
platformIndependent = True,
|
||||
runPreProcessor = mkSimplePreProcessor $ \infile outfile verbosity ->
|
||||
do info verbosity $ "Preprocessing " ++ infile ++ " to " ++ outfile
|
||||
hsb2hsPath <- findExecutable "hsb2hs"
|
||||
case hsb2hsPath of
|
||||
Just p -> rawSystem p [infile, infile, outfile]
|
||||
Nothing -> error "hsb2hs is needed to build this program: cabal install hsb2hs"
|
||||
return ()
|
||||
|
||||
})
|
||||
|
|
|
@ -246,9 +246,9 @@ Library
|
|||
build-depends:
|
||||
blaze-html >= 0.4.3.0 && < 0.5
|
||||
if flag(embed_data_files)
|
||||
build-depends: file-embed >= 0.0.4.7 && < 0.1,
|
||||
template-haskell >= 2.4 && < 2.9
|
||||
cpp-options: -DEMBED_DATA_FILES
|
||||
-- build-tools: hsb2hs
|
||||
other-modules: Text.Pandoc.Data
|
||||
if impl(ghc >= 7.0.1)
|
||||
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
|
||||
else
|
||||
|
@ -314,9 +314,6 @@ Library
|
|||
Text.Pandoc.Slides,
|
||||
Paths_pandoc
|
||||
|
||||
if flag(embed_data_files)
|
||||
Other-Modules: Text.Pandoc.Data
|
||||
|
||||
Buildable: True
|
||||
|
||||
Executable pandoc
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
-- to be processed using hsb2hs
|
||||
module Text.Pandoc.Data (dataFiles) where
|
||||
import Data.FileEmbed
|
||||
import qualified Data.ByteString as B
|
||||
|
||||
dataFiles :: [(FilePath, B.ByteString)]
|
||||
dataFiles = $(embedDir "data")
|
||||
dataFiles = %blobs "data"
|
Loading…
Add table
Reference in a new issue