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

Merge pull request #3723 from grayjay/issue-3436

Consistently use the Cabal version picked by the dependency solver.
parents dd6cf0dc a94764ea
No related branches found
No related tags found
No related merge requests found
Showing
with 157 additions and 19 deletions
......@@ -106,7 +106,7 @@ import Control.Applicative ( (<$>), (<*>) )
import Data.Monoid ( mempty )
#endif
import Control.Monad ( when, unless )
import Data.List ( foldl1' )
import Data.List ( find, foldl1' )
import Data.Maybe ( fromMaybe, isJust )
import Data.Char ( isSpace )
import Distribution.Client.Compat.ExecutablePath ( getExecutablePath )
......@@ -389,26 +389,45 @@ externalSetupMethod verbosity options pkg bt mkargs = do
Nothing -> getInstalledPackages verbosity
comp (usePackageDB options') conf
cabalLibVersionToUse :: IO (Version, (Maybe ComponentId)
-- Choose the version of Cabal to use if the setup script has a dependency on
-- Cabal, and possibly update the setup script options. The version also
-- determines how to filter the flags to Setup.
--
-- We first check whether the dependency solver has specified a Cabal version.
-- If it has, we use the solver's version without looking at the installed
-- package index (See issue #3436). Otherwise, we pick the Cabal version by
-- checking 'useCabalSpecVersion', then the saved version, and finally the
-- versions available in the index.
--
-- The version chosen here must match the one used in 'compileSetupExecutable'
-- (See issue #3433).
cabalLibVersionToUse :: IO (Version, Maybe ComponentId
,SetupScriptOptions)
cabalLibVersionToUse =
case useCabalSpecVersion options of
Just version -> do
case find (hasCabal . snd) (useDependencies options) of
Just (unitId, pkgId) -> do
let version = pkgVersion pkgId
updateSetupScript version bt
writeFile setupVersionFile (show version ++ "\n")
return (version, Nothing, options)
Nothing -> do
savedVer <- savedVersion
case savedVer of
Just version | version `withinRange` useCabalVersion options
-> do updateSetupScript version bt
-- Does the previously compiled setup executable still exist
-- and is it up-to date?
useExisting <- canUseExistingSetup version
if useExisting
then return (version, Nothing, options)
else installedVersion
_ -> installedVersion
writeSetupVersionFile version
return (version, Just unitId, options)
Nothing ->
case useCabalSpecVersion options of
Just version -> do
updateSetupScript version bt
writeSetupVersionFile version
return (version, Nothing, options)
Nothing -> do
savedVer <- savedVersion
case savedVer of
Just version | version `withinRange` useCabalVersion options
-> do updateSetupScript version bt
-- Does the previously compiled setup executable still exist
-- and is it up-to date?
useExisting <- canUseExistingSetup version
if useExisting
then return (version, Nothing, options)
else installedVersion
_ -> installedVersion
where
-- This check duplicates the checks in 'getCachedSetupExecutable' /
-- 'compileSetupExecutable'. Unfortunately, we have to perform it twice
......@@ -424,13 +443,20 @@ externalSetupMethod verbosity options pkg bt mkargs = do
(&&) <$> setupProgFile `existsAndIsMoreRecentThan` setupHs
<*> setupProgFile `existsAndIsMoreRecentThan` setupVersionFile
writeSetupVersionFile :: Version -> IO ()
writeSetupVersionFile version =
writeFile setupVersionFile (show version ++ "\n")
hasCabal (PackageIdentifier (PackageName "Cabal") _) = True
hasCabal _ = False
installedVersion :: IO (Version, Maybe InstalledPackageId
,SetupScriptOptions)
installedVersion = do
(comp, conf, options') <- configureCompiler options
(version, mipkgid, options'') <- installedCabalVersion options' comp conf
updateSetupScript version bt
writeFile setupVersionFile (show version ++ "\n")
writeSetupVersionFile version
return (version, mipkgid, options'')
savedVersion :: IO (Maybe Version)
......
......@@ -23,6 +23,19 @@ Extra-Source-Files:
-- Do NOT edit this section manually; instead, run the script.
-- BEGIN gen-extra-source-files
tests/IntegrationTests/common.sh
tests/IntegrationTests/custom-setup/Cabal-99998/Cabal.cabal
tests/IntegrationTests/custom-setup/Cabal-99998/CabalMessage.hs
tests/IntegrationTests/custom-setup/Cabal-99999/Cabal.cabal
tests/IntegrationTests/custom-setup/Cabal-99999/CabalMessage.hs
tests/IntegrationTests/custom-setup/custom-setup-without-cabal-defaultMain/Setup.hs
tests/IntegrationTests/custom-setup/custom-setup-without-cabal-defaultMain/custom-setup-without-cabal-defaultMain.cabal
tests/IntegrationTests/custom-setup/custom-setup-without-cabal/Setup.hs
tests/IntegrationTests/custom-setup/custom-setup-without-cabal/custom-setup-without-cabal.cabal
tests/IntegrationTests/custom-setup/custom-setup/Setup.hs
tests/IntegrationTests/custom-setup/custom-setup/custom-setup.cabal
tests/IntegrationTests/custom-setup/custom_setup_without_Cabal_doesnt_allow_Cabal_import.sh
tests/IntegrationTests/custom-setup/custom_setup_without_Cabal_doesnt_require_Cabal.sh
tests/IntegrationTests/custom-setup/installs_Cabal_as_setup_dep.sh
tests/IntegrationTests/custom/custom_dep.sh
tests/IntegrationTests/custom/custom_dep/client/B.hs
tests/IntegrationTests/custom/custom_dep/client/Setup.hs
......
name: Cabal
version: 99998
build-type: Simple
cabal-version: >= 1.2
library
build-depends: base
exposed-modules: CabalMessage
module CabalMessage where
message = "This is Cabal-99998"
name: Cabal
version: 99999
build-type: Simple
cabal-version: >= 1.2
library
build-depends: base
exposed-modules: CabalMessage
module CabalMessage where
message = "This is Cabal-99999"
import Distribution.Simple
main = defaultMain
name: custom-setup-without-cabal-defaultMain
version: 1.0
build-type: Custom
cabal-version: >= 1.2
custom-setup
setup-depends: base
library
import System.Exit
import System.IO
main = hPutStrLn stderr "My custom Setup" >> exitFailure
name: custom-setup-without-cabal
version: 1.0
build-type: Custom
cabal-version: >= 99999
custom-setup
setup-depends: base
library
import CabalMessage (message)
import System.Exit
import System.IO
main = hPutStrLn stderr message >> exitFailure
name: custom-setup
version: 1.0
build-type: Custom
cabal-version: >= 99999
custom-setup
setup-depends: base, Cabal >= 99999
library
. ./common.sh
cd custom-setup-without-cabal-defaultMain
# This package has explicit setup dependencies that do not include Cabal.
# Compilation should fail because Setup.hs imports Distribution.Simple.
! cabal new-build custom-setup-without-cabal-defaultMain > output 2>&1
cat output
grep -q "\(Could not find module\|Failed to load interface for\).*Distribution\\.Simple" output \
|| die "Should not have been able to import Cabal"
grep -q "It is a member of the hidden package .*Cabal-" output \
|| die "Cabal should be available"
. ./common.sh
cd custom-setup-without-cabal
# This package has explicit setup dependencies that do not include Cabal.
# new-build should try to build it, even though the cabal-version cannot be
# satisfied by an installed version of Cabal (cabal-version: >= 99999). However,
# configure should fail because Setup.hs just prints an error message and exits.
! cabal new-build custom-setup-without-cabal > output 2>&1
cat output
grep -q "My custom Setup" output \
|| die "Expected output from custom Setup"
# Regression test for issue #3436
. ./common.sh
cabal sandbox init
cabal install ./Cabal-99998
cabal sandbox add-source Cabal-99999
# Install custom-setup, which has a setup dependency on Cabal-99999.
# cabal should build the setup script with Cabal-99999, but then
# configure should fail because Setup just prints an error message
# imported from Cabal and exits.
! cabal install custom-setup/ > output 2>&1
cat output
grep -q "This is Cabal-99999" output || die "Expected output from Cabal-99999"
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