From 4b7b646c4fddb1c368aead0315a1f6ce0784b230 Mon Sep 17 00:00:00 2001 From: Daniel Gröber Date: Thu, 28 Sep 2017 21:33:24 +0200 Subject: Move split source into src/ and lib/ --- CabalHelper/Runtime/Licenses.hs | 125 ---------- CabalHelper/Runtime/Main.hs | 539 ---------------------------------------- 2 files changed, 664 deletions(-) delete mode 100644 CabalHelper/Runtime/Licenses.hs delete mode 100644 CabalHelper/Runtime/Main.hs (limited to 'CabalHelper/Runtime') diff --git a/CabalHelper/Runtime/Licenses.hs b/CabalHelper/Runtime/Licenses.hs deleted file mode 100644 index a1794ea..0000000 --- a/CabalHelper/Runtime/Licenses.hs +++ /dev/null @@ -1,125 +0,0 @@ -{-# LANGUAGE CPP #-} - -#ifdef MIN_VERSION_Cabal -#undef CH_MIN_VERSION_Cabal -#define CH_MIN_VERSION_Cabal MIN_VERSION_Cabal -#endif - -module CabalHelper.Runtime.Licenses ( - displayDependencyLicenseList - , groupByLicense - , getDependencyInstalledPackageInfos - ) where - --- Copyright (c) 2014, Jasper Van der Jeugt - --------------------------------------------------------------------------------- -import Control.Arrow ((***), (&&&)) -import Control.Monad (forM_, unless) -import Data.List (foldl', sort) -import Data.Maybe (catMaybes) -import Data.Set (Set) -import qualified Data.Set as Set -import System.Directory (getDirectoryContents) -import System.Exit (exitFailure) -import System.FilePath (takeExtension) -import System.IO (hPutStrLn, stderr) - -import Distribution.InstalledPackageInfo -import Distribution.License -import Distribution.Package -import Distribution.Simple.Configure -import Distribution.Simple.LocalBuildInfo -import Distribution.Simple.PackageIndex -import Distribution.Text -import Distribution.ModuleName -import Distribution.Version (Version) --------------------------------------------------------------------------------- - - - -#if CH_MIN_VERSION_Cabal(1,23,0) --- CPP > 1.22 -type CPackageIndex a = PackageIndex (InstalledPackageInfo) -#elif CH_MIN_VERSION_Cabal(1,22,0) --- CPP >= 1.22 -type CPackageIndex a = PackageIndex (InstalledPackageInfo_ a) -#else -type CPackageIndex a = PackageIndex -#endif - -#if CH_MIN_VERSION_Cabal(1,23,0) --- CPP >= 1.23 -type CInstalledPackageId = UnitId -lookupInstalledPackageId' :: PackageIndex a -> UnitId -> Maybe a -lookupInstalledPackageId' = lookupUnitId -#else -type CInstalledPackageId = InstalledPackageId -lookupInstalledPackageId' = lookupInstalledPackageId -#endif - -findTransitiveDependencies - :: CPackageIndex Distribution.ModuleName.ModuleName - -> Set CInstalledPackageId - -> Set CInstalledPackageId -findTransitiveDependencies pkgIdx set0 = go Set.empty (Set.toList set0) - where - go set [] = set - go set (q : queue) - | q `Set.member` set = go set queue - | otherwise = - case lookupInstalledPackageId' pkgIdx q of - Nothing -> - -- Not found can mean that the package still needs to be - -- installed (e.g. a component of the target cabal package). - -- We can ignore those. - go set queue - Just ipi -> - go (Set.insert q set) (Distribution.InstalledPackageInfo.depends ipi ++ queue) - - --------------------------------------------------------------------------------- -getDependencyInstalledPackageIds - :: LocalBuildInfo -> Set CInstalledPackageId -getDependencyInstalledPackageIds lbi = - findTransitiveDependencies (installedPkgs lbi) $ - Set.fromList $ map fst $ externalPackageDeps lbi - --------------------------------------------------------------------------------- -getDependencyInstalledPackageInfos - :: LocalBuildInfo -> [InstalledPackageInfo] -getDependencyInstalledPackageInfos lbi = catMaybes $ - map (lookupInstalledPackageId' pkgIdx) $ - Set.toList (getDependencyInstalledPackageIds lbi) - where - pkgIdx = installedPkgs lbi - - --------------------------------------------------------------------------------- -groupByLicense - :: [InstalledPackageInfo] - -> [(License, [InstalledPackageInfo])] -groupByLicense = foldl' - (\assoc ipi -> insertAList (license ipi) ipi assoc) [] - where - -- 'Cabal.License' doesn't have an 'Ord' instance so we need to use an - -- association list instead of 'Map'. The number of licenses probably won't - -- exceed 100 so I think we're alright. - insertAList :: Eq k => k -> v -> [(k, [v])] -> [(k, [v])] - insertAList k v [] = [(k, [v])] - insertAList k v ((k', vs) : kvs) - | k == k' = (k, v : vs) : kvs - | otherwise = (k', vs) : insertAList k v kvs - - --------------------------------------------------------------------------------- -displayDependencyLicenseList - :: [(License, [InstalledPackageInfo])] - -> [(String, [(String, Version)])] -displayDependencyLicenseList = - map (display *** map (getName &&& getVersion)) - where - getName = - display . pkgName . sourcePackageId - getVersion = - pkgVersion . sourcePackageId diff --git a/CabalHelper/Runtime/Main.hs b/CabalHelper/Runtime/Main.hs deleted file mode 100644 index 86bf169..0000000 --- a/CabalHelper/Runtime/Main.hs +++ /dev/null @@ -1,539 +0,0 @@ --- Copyright (C) 2015 Daniel Gröber --- --- This program is free software: you can redistribute it and/or modify --- it under the terms of the GNU Affero General Public License as published by --- the Free Software Foundation, either version 3 of the License, or --- (at your option) any later version. --- --- This program is distributed in the hope that it will be useful, --- but WITHOUT ANY WARRANTY; without even the implied warranty of --- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the --- GNU Affero General Public License for more details. --- --- You should have received a copy of the GNU Affero General Public License --- along with this program. If not, see . - -{-# LANGUAGE CPP, BangPatterns, RecordWildCards, RankNTypes, ViewPatterns #-} -{-# OPTIONS_GHC -fno-warn-deprecations #-} - -#ifdef MIN_VERSION_Cabal -#undef CH_MIN_VERSION_Cabal -#define CH_MIN_VERSION_Cabal MIN_VERSION_Cabal -#endif - -import Distribution.Simple.Utils (cabalVersion) -import Distribution.Simple.Configure - -import Distribution.Package (PackageIdentifier, InstalledPackageId, PackageId, - packageName, packageVersion) -import Distribution.PackageDescription (PackageDescription, - GenericPackageDescription(..), - Flag(..), - FlagName(..), - FlagAssignment, - Executable(..), - Library(..), - TestSuite(..), - Benchmark(..), - BuildInfo(..), - TestSuiteInterface(..), - BenchmarkInterface(..), - withLib) -#if CH_MIN_VERSION_Cabal(1,25,0) --- CPP CABAL_MAJOR == 1 && CABAL_MINOR >= 25 -import Distribution.PackageDescription (unFlagName, mkFlagName) -#endif -import Distribution.PackageDescription.Parse (readPackageDescription) -import Distribution.PackageDescription.Configuration (flattenPackageDescription) - -import Distribution.Simple.Program (requireProgram, ghcProgram) -import Distribution.Simple.Program.Types (ConfiguredProgram(..)) -import Distribution.Simple.Configure (getPersistBuildConfig) -import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..), - Component(..), - ComponentName(..), - ComponentLocalBuildInfo(..), - componentBuildInfo, - externalPackageDeps, - withComponentsLBI, - withLibLBI) -#if CH_MIN_VERSION_Cabal(1,23,0) --- >= 1.23 -import Distribution.Simple.LocalBuildInfo (localUnitId) -#else --- <= 1.22 -import Distribution.Simple.LocalBuildInfo (inplacePackageId) -#endif - -import Distribution.Simple.GHC (componentGhcOptions) -import Distribution.Simple.Program.GHC (GhcOptions(..), renderGhcOptions) - -import Distribution.Simple.Setup (ConfigFlags(..),Flag(..)) -import Distribution.Simple.Build (initialBuildSteps) -import Distribution.Simple.BuildPaths (autogenModuleName, cppHeaderName, exeExtension) -import Distribution.Simple.Compiler (PackageDB(..), compilerId) - -import Distribution.Compiler (CompilerId(..)) -import Distribution.ModuleName (components) -import qualified Distribution.ModuleName as C (ModuleName) -import Distribution.Text (display) -import Distribution.Verbosity (Verbosity, silent, deafening, normal) - -import Distribution.Version (Version) -#if CH_MIN_VERSION_Cabal(2,0,0) --- CPP >= 2.0 -import Distribution.Version (versionNumbers, mkVersion) -#endif - -#if CH_MIN_VERSION_Cabal(1,22,0) --- CPP >= 1.22 -import Distribution.Utils.NubList -#endif - -#if CH_MIN_VERSION_Cabal(1,25,0) --- CPP >= 1.25 -import Distribution.Types.ForeignLib (ForeignLib(..)) -import Distribution.Types.UnqualComponentName (unUnqualComponentName) -#endif - -#if CH_MIN_VERSION_Cabal(2,0,0) -import Distribution.Types.UnitId (UnitId) -import Distribution.Types.MungedPackageId (MungedPackageId) -#endif - -import Control.Applicative ((<$>)) -import Control.Arrow (first, second, (&&&)) -import Control.Monad -import Control.Exception (catch, PatternMatchFail(..)) -import Data.List -import qualified Data.Map as Map -import Data.Maybe -import Data.Monoid -import Data.IORef -import qualified Data.Version as DataVersion -import System.Environment -import System.Directory -import System.FilePath -import System.Exit -import System.IO -import System.IO.Unsafe (unsafeInterleaveIO, unsafePerformIO) -import Text.Printf - -import CabalHelper.Shared.Sandbox -import CabalHelper.Shared.Common -import CabalHelper.Shared.InterfaceTypes - -import CabalHelper.Runtime.Licenses - -usage = do - prog <- getProgName - hPutStr stderr $ "Usage: " ++ prog ++ " " ++ usageMsg - where - usageMsg = "" - ++"PROJ_DIR DIST_DIR [--with-* ...] (\n" - ++" version\n" - ++" | print-lbi [--human]\n" - ++" | package-id\n" - ++" | flags\n" - ++" | config-flags\n" - ++" | non-default-config-flags\n" - ++" | write-autogen-files\n" - ++" | compiler-version\n" - ++" | ghc-options [--with-inplace]\n" - ++" | ghc-src-options [--with-inplace]\n" - ++" | ghc-pkg-options [--with-inplace]\n" - ++" | ghc-merged-pkg-options [--with-inplace]\n" - ++" | ghc-lang-options [--with-inplace]\n" - ++" | package-db-stack\n" - ++" | entrypoints\n" - ++" | source-dirs\n" - ++" | licenses\n" - ++" ) ...\n" - -commands :: [String] -commands = [ "print-lbi" - , "package-id" - , "flags" - , "config-flags" - , "non-default-config-flags" - , "write-autogen-files" - , "compiler-version" - , "ghc-options" - , "ghc-src-options" - , "ghc-pkg-options" - , "ghc-lang-options" - , "package-db-stack" - , "entrypoints" - , "source-dirs" - , "licenses"] - -main :: IO () -main = do - args <- getArgs - - projdir:distdir:args' <- case args of - [] -> usage >> exitFailure - _ -> return args - - ddexists <- doesDirectoryExist distdir - when (not ddexists) $ do - errMsg $ "distdir '"++distdir++"' does not exist" - exitFailure - - [cfile] <- filter isCabalFile <$> getDirectoryContents projdir - - v <- maybe silent (const deafening) . lookup "CABAL_HELPER_DEBUG" <$> getEnvironment - lbi <- unsafeInterleaveIO $ getPersistBuildConfig distdir - gpd <- unsafeInterleaveIO $ readPackageDescription v (projdir cfile) - let pd = localPkgDescr lbi - let lvd = (lbi, v, distdir) - - let - -- a =<< b $$ c == (a =<< b) $$ c - infixr 2 $$ - ($$) = ($) - - collectCmdOptions :: [String] -> [[String]] - collectCmdOptions = - reverse . map reverse . foldl f [] . dropWhile isOpt - where - isOpt = ("--" `isPrefixOf`) - f [] x = [[x]] - f (a:as) x - | isOpt x = (x:a):as - | otherwise = [x]:(a:as) - - let cmds = collectCmdOptions args' - - if any (["version"] `isPrefixOf`) cmds - then do - putStrLn $ - printf "using version %s of the Cabal library" (display cabalVersion) - exitSuccess - else return () - - print =<< flip mapM cmds $$ \cmd -> do - case cmd of - "flags":[] -> do - return $ Just $ ChResponseFlags $ sort $ - map (flagName' &&& flagDefault) $ genPackageFlags gpd - - "config-flags":[] -> do - return $ Just $ ChResponseFlags $ sort $ - map (first unFlagName) $ configConfigurationsFlags $ configFlags lbi - - "non-default-config-flags":[] -> do - let flagDefinitons = genPackageFlags gpd - flagAssgnments = configConfigurationsFlags $ configFlags lbi - nonDefaultFlags = - [ (fn, v) - | MkFlag {flagName=(unFlagName -> fn), flagDefault=dv} <- flagDefinitons - , (unFlagName -> fn', v) <- flagAssgnments - , fn == fn' - , v /= dv - ] - return $ Just $ ChResponseFlags $ sort nonDefaultFlags - - "write-autogen-files":[] -> do - initialBuildStepsForAllComponents distdir pd lbi v - return Nothing - - "compiler-version":[] -> do - let CompilerId comp ver = compilerId $ compiler lbi - return $ Just $ ChResponseVersion (show comp) (toDataVersion ver) - - "ghc-options":flags -> do - res <- componentOptions lvd True flags id - return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) - - "ghc-src-options":flags -> do - res <- componentOptions lvd False flags $ \opts -> mempty { - -- Not really needed but "unexpected package db stack: []" - ghcOptPackageDBs = [GlobalPackageDB, UserPackageDB], - - ghcOptCppOptions = ghcOptCppOptions opts, - ghcOptCppIncludePath = ghcOptCppIncludePath opts, - ghcOptCppIncludes = ghcOptCppIncludes opts, - ghcOptFfiIncludes = ghcOptFfiIncludes opts, - ghcOptSourcePathClear = ghcOptSourcePathClear opts, - ghcOptSourcePath = ghcOptSourcePath opts - } - return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) - - "ghc-pkg-options":flags -> do - res <- componentOptions lvd True flags $ \opts -> mempty { - ghcOptPackageDBs = ghcOptPackageDBs opts, - ghcOptPackages = ghcOptPackages opts, - ghcOptHideAllPackages = ghcOptHideAllPackages opts - } - return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) - - "ghc-merged-pkg-options":flags -> do - let pd = localPkgDescr lbi - res <- mconcat . map snd <$> (componentOptions' lvd True flags (\_ _ o -> return o) $ \opts -> mempty { - ghcOptPackageDBs = [], - ghcOptHideAllPackages = NoFlag, - ghcOptPackages = ghcOptPackages opts - }) - - let res' = nubPackageFlags $ res { ghcOptPackageDBs = withPackageDB lbi - , ghcOptHideAllPackages = Flag True - } - - Just . ChResponseList <$> renderGhcOptions' lbi v res' - - "ghc-lang-options":flags -> do - res <- componentOptions lvd False flags $ \opts -> mempty { - ghcOptPackageDBs = [GlobalPackageDB, UserPackageDB], - - ghcOptLanguage = ghcOptLanguage opts, - ghcOptExtensions = ghcOptExtensions opts, - ghcOptExtensionMap = ghcOptExtensionMap opts - } - return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) - - "package-db-stack":[] -> do - let - pkgDb GlobalPackageDB = ChPkgGlobal - pkgDb UserPackageDB = ChPkgUser - pkgDb (SpecificPackageDB s) = ChPkgSpecific s - - -- TODO: Setup.hs has access to the sandbox as well: ghc-mod#478 - return $ Just $ ChResponsePkgDbs $ map pkgDb $ withPackageDB lbi - - "entrypoints":[] -> do - eps <- componentsMap lbi v distdir $ \c clbi bi -> - return $ componentEntrypoints c - -- MUST append Setup component at the end otherwise CabalHelper gets - -- confused - let eps' = eps ++ [(ChSetupHsName, ChSetupEntrypoint)] - return $ Just $ ChResponseEntrypoints eps' - - "source-dirs":[] -> do - res <- componentsMap lbi v distdir $$ \_ _ bi -> return $ hsSourceDirs bi - return $ Just $ ChResponseCompList (res ++ [(ChSetupHsName, [])]) - - "licenses":[] -> do - return $ Just $ ChResponseLicenses $ - map (second (map (second toDataVersion))) $ - displayDependencyLicenseList $ - groupByLicense $ getDependencyInstalledPackageInfos lbi - - "print-lbi":flags -> - case flags of - ["--human"] -> print lbi >> return Nothing - [] -> return $ Just $ ChResponseLbi $ show lbi - - cmd:_ | not (cmd `elem` commands) -> - errMsg ("Unknown command: " ++ cmd) >> usage >> exitFailure - _ -> - errMsg "Invalid usage!" >> usage >> exitFailure - -flagName' = unFlagName . flagName - -#if !CH_MIN_VERSION_Cabal(1,25,0) --- CPP < 1.25 -unFlagName (FlagName n) = n -mkFlagName n = FlagName n -#endif - -toDataVersion :: Version -> DataVersion.Version ---fromDataVersion :: DataVersion.Version -> Version -#if CH_MIN_VERSION_Cabal(2,0,0) -toDataVersion v = DataVersion.Version (versionNumbers v) [] ---fromDataVersion (DataVersion.Version vs _) = mkVersion vs -#else -toDataVersion = id -fromDataVersion = id -#endif - -getLibrary :: PackageDescription -> Library -getLibrary pd = unsafePerformIO $ do - lr <- newIORef (error "libraryMap: empty IORef") - withLib pd (writeIORef lr) - readIORef lr - -getLibraryClbi pd lbi = unsafePerformIO $ do - lr <- newIORef Nothing - - withLibLBI pd lbi $ \ lib clbi -> - writeIORef lr $ Just (lib,clbi) - - readIORef lr - - -componentsMap :: LocalBuildInfo - -> Verbosity - -> FilePath - -> ( Component - -> ComponentLocalBuildInfo - -> BuildInfo - -> IO a) - -> IO [(ChComponentName, a)] -componentsMap lbi v distdir f = do - let pd = localPkgDescr lbi - - lr <- newIORef [] - - -- withComponentsLBI is deprecated but also exists in very old versions - -- it's equivalent to withAllComponentsInBuildOrder in newer versions - withComponentsLBI pd lbi $ \c clbi -> do - let bi = componentBuildInfo c - name = componentNameFromComponent c - - l' <- readIORef lr - r <- f c clbi bi - writeIORef lr $ (componentNameToCh name, r):l' - - reverse <$> readIORef lr - -componentOptions' (lbi, v, distdir) inplaceFlag flags rf f = do - let pd = localPkgDescr lbi - componentsMap lbi v distdir $ \c clbi bi -> let - outdir = componentOutDir lbi c - (clbi', adopts) = case flags of - _ | not inplaceFlag -> (clbi, mempty) - ["--with-inplace"] -> (clbi, mempty) - [] -> removeInplaceDeps v lbi pd clbi - opts = componentGhcOptions normal lbi bi clbi' outdir - opts' = f opts - - in rf lbi v $ nubPackageFlags $ opts' `mappend` adopts - -componentOptions (lbi, v, distdir) inplaceFlag flags f = - componentOptions' (lbi, v, distdir) inplaceFlag flags renderGhcOptions' f - -componentNameToCh CLibName = ChLibName -#if CH_MIN_VERSION_Cabal(1,25,0) --- CPP >= 1.25 -componentNameToCh (CSubLibName n) = ChSubLibName $ unUnqualComponentName' n -componentNameToCh (CFLibName n) = ChFLibName $ unUnqualComponentName' n -#endif -componentNameToCh (CExeName n) = ChExeName $ unUnqualComponentName' n -componentNameToCh (CTestName n) = ChTestName $ unUnqualComponentName' n -componentNameToCh (CBenchName n) = ChBenchName $ unUnqualComponentName' n - -#if CH_MIN_VERSION_Cabal(1,25,0) --- CPP >= 1.25 -unUnqualComponentName' = unUnqualComponentName -#else -unUnqualComponentName' = id -#endif - -#if !CH_MIN_VERSION_Cabal(1,25,0) --- CPP < 1.25 -componentNameFromComponent (CLib Library {}) = CLibName -#elif CH_MIN_VERSION_Cabal(1,25,0) --- CPP >= 1.25 (redundant) -componentNameFromComponent (CLib Library { libName = Nothing }) = CLibName -componentNameFromComponent (CLib Library { libName = Just n }) = CSubLibName n -componentNameFromComponent (CFLib ForeignLib {..}) = CFLibName foreignLibName -#endif -componentNameFromComponent (CExe Executable {..}) = CExeName exeName -componentNameFromComponent (CTest TestSuite {..}) = CTestName testName -componentNameFromComponent (CBench Benchmark {..}) = CBenchName benchmarkName - -componentOutDir lbi (CLib Library {..})= buildDir lbi -componentOutDir lbi (CExe Executable {..})= exeOutDir lbi (unUnqualComponentName' exeName) -componentOutDir lbi (CTest TestSuite { testInterface = TestSuiteExeV10 _ _, ..}) = - exeOutDir lbi (unUnqualComponentName' testName) -componentOutDir lbi (CTest TestSuite { testInterface = TestSuiteLibV09 _ _, ..}) = - exeOutDir lbi (unUnqualComponentName' testName ++ "Stub") -componentOutDir lbi (CBench Benchmark { benchmarkInterface = BenchmarkExeV10 _ _, ..})= - exeOutDir lbi (unUnqualComponentName' benchmarkName) - -gmModuleName :: C.ModuleName -> ChModuleName -gmModuleName = ChModuleName . intercalate "." . components - -componentEntrypoints :: Component -> ChEntrypoint -componentEntrypoints (CLib Library {..}) - = ChLibEntrypoint - (map gmModuleName exposedModules) - (map gmModuleName $ otherModules libBuildInfo) -componentEntrypoints (CExe Executable {..}) - = ChExeEntrypoint modulePath (map gmModuleName $ otherModules buildInfo) -componentEntrypoints (CTest TestSuite { testInterface = TestSuiteExeV10 _ fp, ..}) - = ChExeEntrypoint fp (map gmModuleName $ otherModules testBuildInfo) -componentEntrypoints (CTest TestSuite { testInterface = TestSuiteLibV09 _ mn, ..}) - = ChLibEntrypoint [gmModuleName mn] (map gmModuleName $ otherModules testBuildInfo) -componentEntrypoints (CTest TestSuite {}) - = ChLibEntrypoint [] [] -componentEntrypoints (CBench Benchmark { benchmarkInterface = BenchmarkExeV10 _ fp, ..}) - = ChExeEntrypoint fp (map gmModuleName $ otherModules benchmarkBuildInfo) -componentEntrypoints (CBench Benchmark {}) - = ChLibEntrypoint [] [] - -exeOutDir :: LocalBuildInfo -> String -> FilePath -exeOutDir lbi exeName' = - ----- Copied from Distribution/Simple/GHC.hs:buildOrReplExe - let targetDir = (buildDir lbi) exeName' - exeDir = targetDir (exeName' ++ "-tmp") - in exeDir - - -removeInplaceDeps :: Verbosity - -> LocalBuildInfo - -> PackageDescription - -> ComponentLocalBuildInfo - -> (ComponentLocalBuildInfo, GhcOptions) -removeInplaceDeps v lbi pd clbi = let - (ideps, deps) = partition isInplaceDep (componentPackageDeps clbi) - hasIdeps = not $ null ideps - libopts = - case getLibraryClbi pd lbi of - Just (lib, libclbi) | hasIdeps -> - let - libbi = libBuildInfo lib - liboutdir = componentOutDir lbi (CLib lib) - in - (componentGhcOptions normal lbi libbi libclbi liboutdir) { - ghcOptPackageDBs = [] - } - _ -> mempty - clbi' = clbi { componentPackageDeps = deps } - - in (clbi', libopts) - - where -#if CH_MIN_VERSION_Cabal(2,0,0) - isInplaceDep :: (UnitId, MungedPackageId) -> Bool - isInplaceDep (mpid, pid) = localUnitId lbi == mpid -#else - isInplaceDep :: (InstalledPackageId, PackageId) -> Bool -# if CH_MIN_VERSION_Cabal(1,23,0) --- CPP >= 1.23 - isInplaceDep (ipid, pid) = localUnitId lbi == ipid -# else --- CPP <= 1.22 - isInplaceDep (ipid, pid) = inplacePackageId pid == ipid -# endif -#endif - -#if CH_MIN_VERSION_Cabal(1,22,0) --- CPP >= 1.22 --- >= 1.22 uses NubListR -nubPackageFlags opts = opts -#else -nubPackageFlags opts = opts { ghcOptPackages = nub $ ghcOptPackages opts } -#endif - -renderGhcOptions' :: LocalBuildInfo - -> Verbosity - -> GhcOptions - -> IO [String] -renderGhcOptions' lbi v opts = do -#if !CH_MIN_VERSION_Cabal(1,20,0) --- CPP < 1.20 - (ghcProg, _) <- requireProgram v ghcProgram (withPrograms lbi) - let Just ghcVer = programVersion ghcProg - return $ renderGhcOptions ghcVer opts -#elif CH_MIN_VERSION_Cabal(1,20,0) && !CH_MIN_VERSION_Cabal(1,24,0) --- CPP >= 1.20 && < 1.24 - return $ renderGhcOptions (compiler lbi) opts -#else --- CPP >= 1.24 - return $ renderGhcOptions (compiler lbi) (hostPlatform lbi) opts -#endif - -initialBuildStepsForAllComponents distdir pd lbi v = - initialBuildSteps distdir pd lbi v -- cgit v1.2.3