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
|
2015-04-15 11:13:00 +00:00
|
|
|
import Distribution.Simple.Register
|
2015-02-04 00:12:51 +00:00
|
|
|
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
|
|
|
|
2016-01-13 03:49:38 +00:00
|
|
|
import Safe
|
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
|
|
|
|
2015-04-15 11:13:00 +00:00
|
|
|
, instHook = inst
|
|
|
|
, copyHook = copy
|
2015-02-04 00:12:51 +00:00
|
|
|
|
2015-03-05 18:47:40 +00:00
|
|
|
-- , postConf = sanityCheckCabalVersions
|
2015-02-04 00:12:51 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
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)
|
|
|
|
|
2015-04-15 11:13:00 +00:00
|
|
|
-- mostly copypasta from 'defaultInstallHook'
|
|
|
|
inst ::
|
|
|
|
PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
|
|
|
|
inst pd lbi _uf ifl = do
|
|
|
|
let copyFlags = defaultCopyFlags {
|
|
|
|
copyDistPref = installDistPref ifl,
|
|
|
|
copyDest = toFlag NoCopyDest,
|
|
|
|
copyVerbosity = installVerbosity ifl
|
|
|
|
}
|
|
|
|
xInstallTarget pd lbi (\pd' lbi' -> install pd' lbi' copyFlags)
|
|
|
|
let registerFlags = defaultRegisterFlags {
|
|
|
|
regDistPref = installDistPref ifl,
|
|
|
|
regInPlace = installInPlace ifl,
|
|
|
|
regPackageDB = installPackageDB ifl,
|
|
|
|
regVerbosity = installVerbosity ifl
|
|
|
|
}
|
|
|
|
when (hasLibs pd) $ register pd lbi registerFlags
|
|
|
|
|
|
|
|
copy :: PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
|
|
|
|
copy pd lbi _uh cf =
|
|
|
|
xInstallTarget pd lbi (\pd' lbi' -> install pd' lbi' cf)
|
|
|
|
|
|
|
|
xInstallTarget :: PackageDescription
|
|
|
|
-> LocalBuildInfo
|
|
|
|
-> (PackageDescription -> LocalBuildInfo -> IO ())
|
|
|
|
-> IO ()
|
|
|
|
xInstallTarget pd lbi fn = do
|
2015-02-04 00:12:51 +00:00
|
|
|
let (extended, regular) = partition (isJust . installTarget) (executables pd)
|
|
|
|
|
|
|
|
let pd_regular = pd { executables = regular }
|
|
|
|
|
2015-04-15 11:13:00 +00:00
|
|
|
_ <- flip mapM extended $ \exe -> do
|
2015-02-04 00:12:51 +00:00
|
|
|
putStrLn $ "extended " ++ show (exeName exe)
|
|
|
|
|
|
|
|
let
|
|
|
|
idirtpl = installDirTemplates lbi
|
|
|
|
env = installDirsTemplateEnv idirtpl
|
|
|
|
libexecdir' = fromPathTemplate (libexecdir idirtpl)
|
|
|
|
|
|
|
|
pd_extended = onlyExePackageDesc [exe] pd
|
2016-01-13 03:49:38 +00:00
|
|
|
install_target = fromJustNote "xInstallTarget" $ installTarget exe
|
2015-02-04 00:12:51 +00:00
|
|
|
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''
|
|
|
|
}
|
|
|
|
}
|
2015-04-15 11:13:00 +00:00
|
|
|
fn pd_extended lbi'
|
2015-02-04 00:12:51 +00:00
|
|
|
|
2015-04-15 11:13:00 +00:00
|
|
|
fn pd_regular lbi
|
2015-02-04 00:12:51 +00:00
|
|
|
|
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)
|
|
|
|
|
2015-04-15 11:13:00 +00:00
|
|
|
onlyExePackageDesc :: [Executable] -> PackageDescription -> PackageDescription
|
2015-02-04 00:12:51 +00:00
|
|
|
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"
|
|
|
|
|
2015-03-05 18:47:40 +00:00
|
|
|
-- 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
|
|
|
|
-- let cabalHelperCabalVer = compCabalVer (CExeName "cabal-helper")
|
|
|
|
|
|
|
|
-- when (not $ cabalVer `sameMajorVersionAs` cabalHelperCabalVer) $
|
|
|
|
-- failCabalVersionDifferent cabalVer cabalHelperCabalVer
|
|
|
|
|
|
|
|
-- -- carry on as usual
|
|
|
|
-- (postConf simpleUserHooks) args cf desc lbi
|
|
|
|
|
|
|
|
-- where
|
|
|
|
-- earlierVersionThan ver ver' =
|
|
|
|
-- ver `withinRange` earlierVersion ver'
|
|
|
|
-- sameMajorVersionAs ver ver' =
|
|
|
|
-- ver `withinRange` withinVersion (Version (take 2 $ versionBranch ver') [])
|
|
|
|
|
|
|
|
-- 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"
|