2015-02-04 00:12:51 +00:00
|
|
|
#!/usr/bin/env runhaskell
|
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
2010-04-02 15:16:22 +00:00
|
|
|
import Distribution.Simple
|
2015-02-04 00:12:51 +00:00
|
|
|
import Distribution.Simple.Setup
|
|
|
|
import Distribution.Simple.Install
|
|
|
|
import Distribution.Simple.InstallDirs as ID
|
2015-01-16 14:46:58 +00:00
|
|
|
import Distribution.Simple.LocalBuildInfo
|
2015-02-04 00:12:51 +00:00
|
|
|
import Distribution.PackageDescription
|
2015-01-16 14:46:58 +00:00
|
|
|
|
2015-02-04 00:12:51 +00:00
|
|
|
import Control.Arrow
|
2015-01-16 14:46:58 +00:00
|
|
|
import Control.Applicative
|
2015-02-04 00:12:51 +00:00
|
|
|
import Control.Monad
|
|
|
|
import Data.List
|
|
|
|
import Data.Maybe
|
2015-01-16 14:46:58 +00:00
|
|
|
import Data.Version
|
2015-02-04 00:12:51 +00:00
|
|
|
import Data.Monoid
|
2015-01-16 14:46:58 +00:00
|
|
|
import System.Process
|
|
|
|
import System.Exit
|
2015-02-04 00:12:51 +00:00
|
|
|
import System.FilePath
|
2015-01-16 14:46:58 +00:00
|
|
|
import Text.ParserCombinators.ReadP
|
|
|
|
|
2015-02-04 00:12:51 +00:00
|
|
|
import SetupCompat
|
2015-01-16 14:46:58 +00:00
|
|
|
|
|
|
|
main :: IO ()
|
|
|
|
main = defaultMainWithHooks $ simpleUserHooks {
|
2015-02-04 00:12:51 +00:00
|
|
|
confHook = \(gpd, hbi) cf ->
|
2015-02-08 13:17:53 +00:00
|
|
|
xBuildDependsLike <$> (confHook simpleUserHooks) (gpd, hbi) cf
|
2015-02-04 00:12:51 +00:00
|
|
|
|
|
|
|
, copyHook = xInstallTargetHook
|
|
|
|
|
|
|
|
, instHook = \pd lbi uh ifl ->
|
|
|
|
(instHook simpleUserHooks) pd lbi uh ifl
|
|
|
|
|
|
|
|
, postConf = sanityCheckCabalVersions
|
|
|
|
}
|
|
|
|
|
|
|
|
xBuildDependsLike :: LocalBuildInfo -> LocalBuildInfo
|
|
|
|
xBuildDependsLike lbi =
|
|
|
|
let
|
|
|
|
cc = componentsConfigs lbi
|
|
|
|
pd = localPkgDescr lbi
|
|
|
|
deps = dependsMap lbi
|
|
|
|
in setComponentsConfigs lbi
|
|
|
|
[ (cn, updateClbi deps comp clbi, cdeps)
|
|
|
|
| (cn, clbi, cdeps) <- cc
|
|
|
|
, let comp = getComponent pd cn
|
|
|
|
]
|
|
|
|
|
|
|
|
where
|
2015-02-08 13:17:53 +00:00
|
|
|
updateClbi deps comp clbi = setUnionDeps (otherDeps deps comp) clbi
|
2015-02-04 00:12:51 +00:00
|
|
|
|
|
|
|
dependsMap ::
|
2015-02-08 13:17:53 +00:00
|
|
|
LocalBuildInfo -> [(ComponentName, Deps)]
|
2015-02-04 00:12:51 +00:00
|
|
|
dependsMap lbi =
|
2015-02-08 13:17:53 +00:00
|
|
|
second getDeps <$> allComponentsInBuildOrder lbi
|
2015-02-04 00:12:51 +00:00
|
|
|
|
2015-02-08 13:17:53 +00:00
|
|
|
otherDeps :: [(ComponentName, Deps)] -> Component -> Deps
|
|
|
|
otherDeps deps comp = fromMaybe noDeps $
|
2015-02-04 00:12:51 +00:00
|
|
|
flip lookup deps =<< read <$> lookup "x-build-depends-like" fields
|
|
|
|
where
|
|
|
|
fields = customFieldsBI (componentBuildInfo comp)
|
|
|
|
|
|
|
|
xInstallTargetHook ::
|
|
|
|
PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
|
|
|
|
xInstallTargetHook pd lbi uh cf = do
|
|
|
|
let (extended, regular) = partition (isJust . installTarget) (executables pd)
|
|
|
|
|
|
|
|
let pd_regular = pd { executables = regular }
|
|
|
|
|
|
|
|
flip mapM extended $ \exe -> do
|
|
|
|
putStrLn $ "extended " ++ show (exeName exe)
|
|
|
|
|
|
|
|
let
|
|
|
|
idirtpl = installDirTemplates lbi
|
|
|
|
env = installDirsTemplateEnv idirtpl
|
|
|
|
libexecdir' = fromPathTemplate (libexecdir idirtpl)
|
|
|
|
|
|
|
|
pd_extended = onlyExePackageDesc [exe] pd
|
|
|
|
install_target = fromJust $ installTarget exe
|
|
|
|
install_target' = ID.substPathTemplate env install_target
|
|
|
|
-- $libexec isn't a real thing :/ so we have to simulate it
|
|
|
|
install_target'' = substLibExec' libexecdir' install_target'
|
|
|
|
|
|
|
|
let lbi' = lbi {
|
|
|
|
installDirTemplates =
|
|
|
|
(installDirTemplates lbi) {
|
|
|
|
bindir = install_target''
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
install pd_extended lbi' cf
|
|
|
|
|
|
|
|
install pd_regular lbi cf
|
|
|
|
|
2015-01-16 14:46:58 +00:00
|
|
|
where
|
2015-02-04 00:12:51 +00:00
|
|
|
installTarget :: Executable -> Maybe PathTemplate
|
|
|
|
installTarget exe =
|
|
|
|
toPathTemplate <$> lookup "x-install-target" (customFieldsBI $ buildInfo exe)
|
2015-01-16 14:46:58 +00:00
|
|
|
|
2015-02-04 00:12:51 +00:00
|
|
|
substLibExec libexecdir "$libexecdir" = libexecdir
|
|
|
|
substLibExec _ comp = comp
|
|
|
|
|
|
|
|
substLibExec' dir =
|
|
|
|
withPT $
|
|
|
|
withSP $ map (substLibExec dir . dropTrailingPathSeparator)
|
|
|
|
|
|
|
|
|
|
|
|
withPT f pt = toPathTemplate $ f (fromPathTemplate pt)
|
|
|
|
withSP f p = joinPath $ f (splitPath p)
|
|
|
|
|
|
|
|
onlyExePackageDesc exes pd = emptyPackageDescription {
|
|
|
|
package = package pd
|
|
|
|
, executables = exes
|
|
|
|
}
|
|
|
|
|
|
|
|
parseVer str =
|
|
|
|
case filter ((=="") . snd) $ readP_to_S parseVersion str of
|
|
|
|
[(ver, _)] -> ver
|
|
|
|
_ -> error $ "No parse (Ver) :(\n" ++ str ++ "\n"
|
|
|
|
|
|
|
|
sanityCheckCabalVersions args cf desc lbi = do
|
|
|
|
(cabalInstallVer, cabalVer) <- getCabalExecVer
|
|
|
|
|
|
|
|
let
|
|
|
|
ghcVer = compilerVersion (compiler lbi)
|
|
|
|
-- ghc >= 7.10?
|
|
|
|
minGhc710 = ghcVer `withinRange` orLaterVersion (parseVer "7.10")
|
|
|
|
|
|
|
|
when minGhc710 $ do
|
2015-02-07 22:55:57 +00:00
|
|
|
let cabalHelperCabalVer = compCabalVer (CExeName "cabal-helper")
|
2015-02-04 00:12:51 +00:00
|
|
|
|
|
|
|
when (not $ cabalVer `sameMajorVersionAs` cabalHelperCabalVer) $
|
|
|
|
failCabalVersionDifferent cabalVer cabalHelperCabalVer
|
|
|
|
|
|
|
|
-- carry on as usual
|
|
|
|
(postConf simpleUserHooks) args cf desc lbi
|
|
|
|
|
|
|
|
where
|
2015-01-16 14:46:58 +00:00
|
|
|
earlierVersionThan ver ver' =
|
|
|
|
ver `withinRange` earlierVersion ver'
|
|
|
|
sameMajorVersionAs ver ver' =
|
|
|
|
ver `withinRange` withinVersion (Version (take 2 $ versionBranch ver') [])
|
2015-02-04 00:12:51 +00:00
|
|
|
|
|
|
|
compCabalVer comp = let
|
|
|
|
clbi = getComponentLocalBuildInfo lbi comp
|
|
|
|
|
|
|
|
[cabalVer] =
|
|
|
|
[ ver | (_, PackageIdentifier pkg ver) <- componentPackageDeps clbi
|
|
|
|
, pkg == PackageName "Cabal" ]
|
|
|
|
in cabalVer
|
|
|
|
|
|
|
|
|
|
|
|
getCabalExecVer = do
|
|
|
|
["cabal-install", "version", cabalInstallVer, "using", "version", cabalVer, "of", "the", "Cabal", "library"] <- words <$> readProcess "cabal" ["--version"] ""
|
|
|
|
return (parseVer cabalInstallVer, parseVer cabalVer)
|
|
|
|
|
|
|
|
failCabalVersionDifferent cabalVer libCabalVer =
|
|
|
|
putStrLn rerr >> exitFailure
|
|
|
|
where
|
|
|
|
replace :: String -> String -> String -> String
|
|
|
|
replace _ _ [] = []
|
|
|
|
replace n r h@(h':hs)
|
|
|
|
| map snd (n `zip` h ) == n = r ++ replace n r (drop (length n) h)
|
|
|
|
| otherwise = h':replace n r hs
|
|
|
|
|
|
|
|
rerr = replace "X.XX.X.X" (showVersion libCabalVer) $
|
|
|
|
replace "Y.YY.Y.Y" (showVersion cabalVer) err
|
|
|
|
err = "\
|
|
|
|
\Error: Cabal seems to have decided ghc-mod should be built using Cabal\n\
|
|
|
|
\X.XX.X.X while the `cabal' executable in your PATH was built with Cabal\n\
|
|
|
|
\Y.YY.Y.Y. This will lead to conflicts when running ghc-mod in any project\n\
|
|
|
|
\where you use this `cabal' executable. Please compile ghc-mod using the same\n\
|
|
|
|
\Cabal version as your `cabal' executable or recompile cabal-install using\n\
|
|
|
|
\this version of the Cabal library.\n\
|
|
|
|
\\n\
|
|
|
|
\See: https://github.com/kazu-yamamoto/ghc-mod/wiki/InconsistentCabalVersions\n"
|