Skip to content
Snippets Groups Projects
Commit 3a69f2ea authored by Duncan Coutts's avatar Duncan Coutts Committed by Edward Z. Yang
Browse files

Check for specifying compiler program locations per-package

You're not allowed to specify a different compiler program for different
packages within the same project. Given that in general we allow
specifying config about programs on a per-package basis this needs a
specific check.

Also add a place and a TODO for Future work in this area which is to
check up front that we can find the programs and to monitor them for
changes. Also, currently none of the program config ends up in the
package hashes, so it doesn't cause them to be rebuilt.
parent 20d00264
No related branches found
No related tags found
No related merge requests found
......@@ -34,6 +34,10 @@ module Distribution.Client.ProjectConfig (
resolveSolverSettings,
BuildTimeSettings(..),
resolveBuildTimeSettings,
-- * Checking configuration
checkBadPerPackageCompilerPaths,
BadPerPackageCompilerPaths(..)
) where
import Distribution.Client.ProjectConfig.Types
......@@ -62,6 +66,8 @@ import Distribution.PackageDescription.Parse
( readPackageDescription )
import Distribution.Simple.Compiler
( Compiler, compilerInfo )
import Distribution.Simple.Program
( ConfiguredProgram(..) )
import Distribution.Simple.Setup
( Flag(Flag), toFlag, flagToMaybe, flagToList
, fromFlag, AllowNewer(..) )
......@@ -92,6 +98,8 @@ import Data.Typeable
import Data.Maybe
import Data.Either
import qualified Data.Map as Map
import Data.Map (Map)
import qualified Data.Set as Set
import Distribution.Compat.Semigroup
import System.FilePath hiding (combine)
import System.Directory
......@@ -681,3 +689,37 @@ readSourcePackage verbosity (ProjectPackageLocalDirectory dir cabalFile) = do
readSourcePackage _verbosity _ =
fail $ "TODO: add support for fetching and reading local tarballs, remote "
++ "tarballs, remote repos and passing named packages through"
---------------------------------------------
-- Checking configuration sanity
--
data BadPerPackageCompilerPaths
= BadPerPackageCompilerPaths [(PackageName, String)]
deriving (Show, Typeable)
instance Exception BadPerPackageCompilerPaths
--TODO: [required eventually] displayException for nice rendering
--TODO: [nice to have] custom exception subclass for Doc rendering, colour etc
-- | The project configuration is not allowed to specify program locations for
-- programs used by the compiler as these have to be the same for each set of
-- packages.
--
-- We cannot check this until we know which programs the compiler uses, which
-- in principle is not until we've configured the compiler.
--
-- Throws 'BadPerPackageCompilerPaths'
--
checkBadPerPackageCompilerPaths :: [ConfiguredProgram]
-> Map PackageName PackageConfig
-> IO ()
checkBadPerPackageCompilerPaths compilerPrograms packagesConfig =
case [ (pkgname, progname)
| let compProgNames = Set.fromList (map programId compilerPrograms)
, (pkgname, pkgconf) <- Map.toList packagesConfig
, progname <- Map.keys (getMapLast (packageConfigProgramPaths pkgconf))
, progname `Set.member` compProgNames ] of
[] -> return ()
ps -> throwIO (BadPerPackageCompilerPaths ps)
......@@ -241,6 +241,7 @@ rebuildInstallPlan verbosity
(projectConfig, projectConfigTransient) <- phaseReadProjectConfig
localPackages <- phaseReadLocalPackages projectConfig
compilerEtc <- phaseConfigureCompiler projectConfig
_ <- phaseConfigurePrograms projectConfig compilerEtc
solverPlan <- phaseRunSolver projectConfigTransient
compilerEtc localPackages
(elaboratedPlan,
......@@ -357,6 +358,37 @@ rebuildInstallPlan verbosity
$ defaultProgramDb
-- Configuring other programs.
--
-- Having configred the compiler, now we configure all the remaining
-- programs. This is to check we can find them, and to monitor them for
-- changes.
--
-- TODO: [required eventually] we don't actually do this yet.
--
-- We rely on the fact that the previous phase added the program config for
-- all local packages, but that all the programs configured so far are the
-- compiler program or related util programs.
--
phaseConfigurePrograms :: ProjectConfig
-> (Compiler, Platform, ProgramDb)
-> Rebuild ()
phaseConfigurePrograms projectConfig (_, _, compilerprogdb) = do
-- Users are allowed to specify program locations independently for
-- each package (e.g. to use a particular version of a pre-processor
-- for some packages). However they cannot do this for the compiler
-- itself as that's just not going to work. So we check for this.
liftIO $ checkBadPerPackageCompilerPaths
(configuredPrograms compilerprogdb)
(getMapMappend (projectConfigSpecificPackage projectConfig))
--TODO: [required eventually] find/configure other programs that the
-- user specifies.
--TODO: [required eventually] find/configure all build-tools
-- but note that some of them may be built as part of the plan.
-- Run the solver to get the initial install plan.
-- This is expensive so we cache it independently.
--
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment