Setup.hs: rewrite so as not to use process, directory, filepath.
Using anything outside base is dangerous, since older versions of ghc will link against two different versions. See e.g. - https://groups.google.com/forum/#!topic/pandoc-discuss/0r9Hhl730LY - https://www.reddit.com/r/haskell/comments/3634x2/cabal_is_giving_a_weird_error_when_attempting_to/ - jaspervdj/hakyll#356
This commit is contained in:
parent
59193d81fb
commit
d62b1cf180
1 changed files with 10 additions and 25 deletions
35
Setup.hs
35
Setup.hs
|
@ -20,17 +20,14 @@ import Distribution.Simple
|
|||
import Distribution.Simple.PreProcess
|
||||
import Distribution.Simple.Setup (ConfigFlags(..))
|
||||
import Distribution.PackageDescription (PackageDescription(..), FlagName(..))
|
||||
import System.Process ( rawSystem )
|
||||
import System.FilePath ( (</>) )
|
||||
import System.Directory ( findExecutable )
|
||||
import Distribution.Simple.Utils ( rawSystemExitCode, findProgramVersion )
|
||||
import System.Exit
|
||||
import Distribution.Verbosity ( Verbosity )
|
||||
import Distribution.Simple.Utils (info, notice, installOrdinaryFiles)
|
||||
import Distribution.Simple.Setup
|
||||
import Distribution.Simple.Program (simpleProgram, Program(..))
|
||||
import Distribution.Simple.LocalBuildInfo
|
||||
import Data.Version
|
||||
import System.Process (readProcess)
|
||||
import Text.ParserCombinators.ReadP (readP_to_S, skipSpaces, eof)
|
||||
import Control.Monad (when)
|
||||
import qualified Control.Exception as E
|
||||
|
||||
|
@ -39,23 +36,11 @@ main = defaultMainWithHooks $ simpleUserHooks {
|
|||
-- enable hsb2hs preprocessor for .hsb files
|
||||
hookedPreProcessors = [ppBlobSuffixHandler]
|
||||
, hookedPrograms = [(simpleProgram "hsb2hs"){
|
||||
programFindVersion = findHsb2hsVersion }]
|
||||
programFindVersion = \verbosity fp ->
|
||||
findProgramVersion "--version" id verbosity fp }]
|
||||
, postCopy = installManPage
|
||||
}
|
||||
|
||||
findHsb2hsVersion :: Verbosity -> FilePath -> IO (Maybe Version)
|
||||
findHsb2hsVersion verb fp = do
|
||||
let handleExitFailure :: IOError -> IO (Maybe Version)
|
||||
handleExitFailure _ = return Nothing
|
||||
E.handle handleExitFailure $ do
|
||||
outp <- readProcess fp ["--version"] ""
|
||||
case readP_to_S (do v <- parseVersion
|
||||
skipSpaces
|
||||
eof
|
||||
return v) outp of
|
||||
((v,""):_) -> return (Just v)
|
||||
_ -> return Nothing
|
||||
|
||||
ppBlobSuffixHandler :: PPSuffixHandler
|
||||
ppBlobSuffixHandler = ("hsb", \_ lbi ->
|
||||
PreProcessor {
|
||||
|
@ -67,11 +52,11 @@ ppBlobSuffixHandler = ("hsb", \_ lbi ->
|
|||
_ -> False
|
||||
when embedData $
|
||||
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 ()
|
||||
ec <- rawSystemExitCode verbosity "hsb2hs"
|
||||
[infile, infile, outfile]
|
||||
case ec of
|
||||
ExitSuccess -> return ()
|
||||
ExitFailure _ -> error "hsb2hs is needed to build this program"
|
||||
})
|
||||
|
||||
installManPage :: Args -> CopyFlags
|
||||
|
@ -80,6 +65,6 @@ installManPage _ flags pkg lbi = do
|
|||
let verbosity = fromFlag (copyVerbosity flags)
|
||||
let copydest = fromFlag (copyDest flags)
|
||||
let mandest = mandir (absoluteInstallDirs pkg lbi copydest)
|
||||
</> "man1"
|
||||
++ "/man1"
|
||||
notice verbosity $ "Copying man page to " ++ mandest
|
||||
installOrdinaryFiles verbosity mandest [("man", "pandoc.1")]
|
||||
|
|
Loading…
Reference in a new issue