Skip to content

Commit

Permalink
Removing chooseSolver and inline Modular solver as default choice
Browse files Browse the repository at this point in the history
  • Loading branch information
yvan-sraka authored and Mikolaj committed Oct 4, 2023
1 parent bbbca4f commit e435054
Show file tree
Hide file tree
Showing 7 changed files with 5 additions and 58 deletions.
8 changes: 1 addition & 7 deletions cabal-install/src/Distribution/Client/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,6 @@ import Distribution.Simple.Program (ProgramDb)
import Distribution.Simple.Setup
( ConfigFlags (..)
, flagToMaybe
, fromFlag
, fromFlagOrDefault
, toFlag
)
Expand Down Expand Up @@ -405,11 +404,6 @@ planLocalPackage
=<< case flagToMaybe (configCabalFilePath configFlags) of
Nothing -> defaultPackageDesc verbosity
Just fp -> return fp
solver <-
chooseSolver
verbosity
(fromFlag $ configSolver configExFlags)
(compilerInfo comp)

let
-- We create a local package and ask to resolve a dependency on it
Expand Down Expand Up @@ -476,7 +470,7 @@ planLocalPackage
(SourcePackageDb mempty packagePrefs)
[SpecificSourcePackage localPkg]

return (resolveDependencies platform (compilerInfo comp) pkgConfigDb solver resolverParams)
return (resolveDependencies platform (compilerInfo comp) pkgConfigDb resolverParams)

-- | Call an installer for an 'SourcePackage' but override the configure
-- flags with the ones given by the 'ReadyPackage'. In particular the
Expand Down
17 changes: 3 additions & 14 deletions cabal-install/src/Distribution/Client/Dependency.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@
module Distribution.Client.Dependency
( -- * The main package dependency resolver
DepResolverParams
, chooseSolver
, resolveDependencies
, Progress (..)
, foldProgress
Expand Down Expand Up @@ -72,8 +71,6 @@ import qualified Prelude as Unsafe (head)

import Distribution.Client.Dependency.Types
( PackagesPreferenceDefault (..)
, PreSolver (..)
, Solver (..)
)
import Distribution.Client.SolverInstallPlan (SolverInstallPlan)
import qualified Distribution.Client.SolverInstallPlan as SolverInstallPlan
Expand Down Expand Up @@ -756,14 +753,8 @@ standardInstallPolicy installedPkgIndex sourcePkgDb pkgSpecifiers =

-- ------------------------------------------------------------

chooseSolver :: Verbosity -> PreSolver -> CompilerInfo -> IO Solver
chooseSolver _verbosity preSolver _cinfo =
case preSolver of
AlwaysModular -> do
return Modular

runSolver :: Solver -> SolverConfig -> DependencyResolver UnresolvedPkgLoc
runSolver Modular = modularResolver
runSolver :: SolverConfig -> DependencyResolver UnresolvedPkgLoc
runSolver = modularResolver

-- | Run the dependency solver.
--
Expand All @@ -774,14 +765,12 @@ resolveDependencies
:: Platform
-> CompilerInfo
-> PkgConfigDb
-> Solver
-> DepResolverParams
-> Progress String String SolverInstallPlan
resolveDependencies platform comp pkgConfigDB solver params =
resolveDependencies platform comp pkgConfigDB params =
Step (showDepResolverParams finalparams) $
fmap (validateSolverResult platform comp indGoals) $
runSolver
solver
( SolverConfig
reordGoals
cntConflicts
Expand Down
6 changes: 0 additions & 6 deletions cabal-install/src/Distribution/Client/Fetch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -173,19 +173,13 @@ planPackages
pkgConfigDb
pkgSpecifiers
| includeDependencies = do
solver <-
chooseSolver
verbosity
(fromFlag (fetchSolver fetchFlags))
(compilerInfo comp)
notice verbosity "Resolving dependencies..."
installPlan <-
foldProgress logMsg (die' verbosity) return $
resolveDependencies
platform
(compilerInfo comp)
pkgConfigDb
solver
resolverParams

-- The packages we want to fetch are those packages the 'InstallPlan'
Expand Down
6 changes: 0 additions & 6 deletions cabal-install/src/Distribution/Client/Freeze.hs
Original file line number Diff line number Diff line change
Expand Up @@ -212,11 +212,6 @@ planPackages
sourcePkgDb
pkgConfigDb
pkgSpecifiers = do
solver <-
chooseSolver
verbosity
(fromFlag (freezeSolver freezeFlags))
(compilerInfo comp)
notice verbosity "Resolving dependencies..."

installPlan <-
Expand All @@ -225,7 +220,6 @@ planPackages
platform
(compilerInfo comp)
pkgConfigDb
solver
resolverParams

return $ pruneInstallPlan installPlan pkgSpecifiers
Expand Down
12 changes: 0 additions & 12 deletions cabal-install/src/Distribution/Client/Install.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,9 +89,6 @@ import Distribution.Client.Configure
, configureSetupScript
)
import Distribution.Client.Dependency
import Distribution.Client.Dependency.Types
( Solver (..)
)
import Distribution.Client.FetchUtils
import qualified Distribution.Client.Haddock as Haddock (regenerateHaddockIndex)
import Distribution.Client.HttpUtils
Expand Down Expand Up @@ -493,18 +490,12 @@ makeInstallPlan
, pkgSpecifiers
, _
) = do
solver <-
chooseSolver
verbosity
(fromFlag (configSolver configExFlags))
(compilerInfo comp)
notice verbosity "Resolving dependencies..."
return $
planPackages
verbosity
comp
platform
solver
configFlags
configExFlags
installFlags
Expand Down Expand Up @@ -562,7 +553,6 @@ planPackages
:: Verbosity
-> Compiler
-> Platform
-> Solver
-> ConfigFlags
-> ConfigExFlags
-> InstallFlags
Expand All @@ -575,7 +565,6 @@ planPackages
verbosity
comp
platform
solver
configFlags
configExFlags
installFlags
Expand All @@ -587,7 +576,6 @@ planPackages
platform
(compilerInfo comp)
pkgConfigDb
solver
resolverParams
>>= if onlyDeps then pruneInstallPlan pkgSpecifiers else return
where
Expand Down
11 changes: 0 additions & 11 deletions cabal-install/src/Distribution/Client/ProjectPlanning.hs
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,6 @@ import Distribution.Client.Store

import Distribution.Client.Config
import Distribution.Client.Dependency
import Distribution.Client.Dependency.Types
import Distribution.Client.DistDirLayout
import Distribution.Client.FetchUtils
import qualified Distribution.Client.IndexUtils as IndexUtils
Expand Down Expand Up @@ -733,20 +732,13 @@ rebuildInstallPlan
-- ones relevant for the compiler.

liftIO $ do
solver <-
chooseSolver
verbosity
(solverSettingSolver solverSettings)
(compilerInfo compiler)

notice verbosity "Resolving dependencies..."
planOrError <-
foldProgress logMsg (pure . Left) (pure . Right) $
planPackages
verbosity
compiler
platform
solver
solverSettings
(installedPackages <> installedPkgIndex)
sourcePkgDb
Expand Down Expand Up @@ -1243,7 +1235,6 @@ planPackages
:: Verbosity
-> Compiler
-> Platform
-> Solver
-> SolverSettings
-> InstalledPackageIndex
-> SourcePackageDb
Expand All @@ -1255,7 +1246,6 @@ planPackages
verbosity
comp
platform
solver
SolverSettings{..}
installedPkgIndex
sourcePkgDb
Expand All @@ -1266,7 +1256,6 @@ planPackages
platform
(compilerInfo comp)
pkgConfigDB
solver
resolverParams
where
-- TODO: [nice to have] disable multiple instances restriction in
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,6 @@ import Language.Haskell.Extension (Extension (..), Language (..))

-- cabal-install
import Distribution.Client.Dependency
import Distribution.Client.Dependency.Types
import qualified Distribution.Client.SolverInstallPlan as CI.SolverInstallPlan
import Distribution.Client.Types

Expand Down Expand Up @@ -821,7 +820,7 @@ exResolve
prefs
verbosity
enableAllTests =
resolveDependencies C.buildPlatform compiler pkgConfigDb Modular params
resolveDependencies C.buildPlatform compiler pkgConfigDb params
where
defaultCompiler = C.unknownCompilerInfo C.buildCompilerId C.NoAbiTag
compiler =
Expand Down

0 comments on commit e435054

Please sign in to comment.