Simplified Setup.hs.
It no longer builds and installs man pages. All it does is hook the hsb preprocessor. This should make the build process more robust over Cabal API changes. We'll add a Makefile to generate man pages.
This commit is contained in:
parent
1d6e1cf9f3
commit
fa71a08ed3
1 changed files with 3 additions and 51 deletions
54
Setup.hs
54
Setup.hs
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
{-
|
||||
Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -19,60 +18,14 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
|
||||
import Distribution.Simple
|
||||
import Distribution.Simple.PreProcess
|
||||
import Distribution.Simple.Setup
|
||||
(copyDest, copyVerbosity, fromFlag, installVerbosity, BuildFlags(..),
|
||||
TestFlags(..))
|
||||
import Distribution.PackageDescription (PackageDescription(..), Executable(..))
|
||||
import Distribution.Simple.LocalBuildInfo
|
||||
(LocalBuildInfo(..), absoluteInstallDirs)
|
||||
import Distribution.Verbosity ( Verbosity, silent )
|
||||
import Distribution.Simple.InstallDirs (mandir, CopyDest (NoCopyDest), toPathTemplate)
|
||||
import Distribution.Simple.Utils (installOrdinaryFiles, info)
|
||||
import Distribution.Simple.Test (test)
|
||||
import System.Process ( rawSystem )
|
||||
import System.FilePath ( (</>) )
|
||||
import System.Directory ( findExecutable )
|
||||
import System.Exit
|
||||
import Distribution.Simple.Utils (info)
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
defaultMainWithHooks $ simpleUserHooks {
|
||||
postBuild = makeManPages
|
||||
, postCopy = \ _ flags pkg lbi ->
|
||||
installManpages pkg lbi (fromFlag $ copyVerbosity flags)
|
||||
(fromFlag $ copyDest flags)
|
||||
, postInst = \ _ flags pkg lbi ->
|
||||
installManpages pkg lbi (fromFlag $ installVerbosity flags) NoCopyDest
|
||||
, copyHook = \pkgdescr ->
|
||||
(copyHook simpleUserHooks) pkgdescr{ executables =
|
||||
[x | x <- executables pkgdescr, exeName x /= "make-pandoc-man-pages"] }
|
||||
, instHook = \pkgdescr ->
|
||||
(instHook simpleUserHooks) pkgdescr{ executables =
|
||||
[x | x <- executables pkgdescr, exeName x /= "make-pandoc-man-pages"] }
|
||||
, hookedPreProcessors = [ppBlobSuffixHandler]
|
||||
}
|
||||
exitWith ExitSuccess
|
||||
|
||||
-- | Build man pages from markdown sources in man/
|
||||
makeManPages :: Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
|
||||
makeManPages _ flags _ lbi = do
|
||||
let verbosity = fromFlag $ buildVerbosity flags
|
||||
let args = ["--verbose" | verbosity /= silent]
|
||||
rawSystem (buildDir lbi </> "make-pandoc-man-pages" </> "make-pandoc-man-pages")
|
||||
args >>= exitWith
|
||||
|
||||
manpages :: [FilePath]
|
||||
manpages = ["man1" </> "pandoc.1"
|
||||
,"man5" </> "pandoc_markdown.5"]
|
||||
|
||||
manDir :: FilePath
|
||||
manDir = "man"
|
||||
|
||||
installManpages :: PackageDescription -> LocalBuildInfo
|
||||
-> Verbosity -> CopyDest -> IO ()
|
||||
installManpages pkg lbi verbosity copy =
|
||||
installOrdinaryFiles verbosity (mandir (absoluteInstallDirs pkg lbi copy))
|
||||
(zip (repeat manDir) manpages)
|
||||
main = defaultMainWithHooks $ simpleUserHooks {
|
||||
hookedPreProcessors = [ppBlobSuffixHandler] }
|
||||
|
||||
ppBlobSuffixHandler :: PPSuffixHandler
|
||||
ppBlobSuffixHandler = ("hsb", \_ _ ->
|
||||
|
@ -85,5 +38,4 @@ ppBlobSuffixHandler = ("hsb", \_ _ ->
|
|||
Just p -> rawSystem p [infile, infile, outfile]
|
||||
Nothing -> error "hsb2hs is needed to build this program: cabal install hsb2hs"
|
||||
return ()
|
||||
|
||||
})
|
||||
|
|
Loading…
Add table
Reference in a new issue