diff --git a/cabal-install/src/Distribution/Client/Dependency.hs b/cabal-install/src/Distribution/Client/Dependency.hs index 50c08076b699b9b561a4f3bd2a5f6ee28f450aff..06308e002f09ea41befb32c66b0cc498bb01492f 100644 --- a/cabal-install/src/Distribution/Client/Dependency.hs +++ b/cabal-install/src/Distribution/Client/Dependency.hs @@ -13,8 +13,8 @@ -- Top level interface to dependency resolution. ----------------------------------------------------------------------------- module Distribution.Client.Dependency ( - DepResolverParams, -- * The main package dependency resolver + DepResolverParams, chooseSolver, resolveDependencies, Progress(..), diff --git a/cabal-install/src/Distribution/Client/RebuildMonad.hs b/cabal-install/src/Distribution/Client/RebuildMonad.hs index ec7e9843bdc557174aa68ff856b1c057dcbf89fc..3818aced7a3c08dea42ba439ffe1c6c5e4f168d6 100644 --- a/cabal-install/src/Distribution/Client/RebuildMonad.hs +++ b/cabal-install/src/Distribution/Client/RebuildMonad.hs @@ -294,9 +294,10 @@ findFileWithExtensionMonitored extensions searchPath baseName = , ext <- nub extensions ] -- | Like 'findFirstFile', but in the 'Rebuild' monad. -findFirstFileMonitored :: (a -> FilePath) -> [a] -> Rebuild (Maybe a) +findFirstFileMonitored :: forall a. (a -> FilePath) -> [a] -> Rebuild (Maybe a) findFirstFileMonitored file = findFirst - where findFirst [] = return Nothing + where findFirst :: [a] -> Rebuild (Maybe a) + findFirst [] = return Nothing findFirst (x:xs) = do exists <- doesFileExistMonitored (file x) if exists then return (Just x) diff --git a/cabal-install/src/Distribution/Client/Reconfigure.hs b/cabal-install/src/Distribution/Client/Reconfigure.hs index cb15790e5dd01d22752ddab8c80058f1e433a401..5be346fdd32eb0b932fc2594d2f86dad743a0be2 100644 --- a/cabal-install/src/Distribution/Client/Reconfigure.hs +++ b/cabal-install/src/Distribution/Client/Reconfigure.hs @@ -119,14 +119,16 @@ reconfigure else do - let checks = + let checks :: Check (ConfigFlags, ConfigExFlags) + checks = checkVerb <> checkDist <> checkOutdated <> check (Any frc, flags@(configFlags, _)) <- runCheck checks mempty savedFlags - let config' = updateInstallDirs (configUserInstall configFlags) config + let config' :: SavedConfig + config' = updateInstallDirs (configUserInstall configFlags) config when frc $ configureAction flags extraArgs globalFlags return config' @@ -135,11 +137,13 @@ reconfigure -- Changing the verbosity does not require reconfiguration, but the new -- verbosity should be used if reconfiguring. + checkVerb :: Check (ConfigFlags, b) checkVerb = Check $ \_ (configFlags, configExFlags) -> do let configFlags' = configFlags { configVerbosity = toFlag verbosity} return (mempty, (configFlags', configExFlags)) -- Reconfiguration is required if @--build-dir@ changes. + checkDist :: Check (ConfigFlags, b) checkDist = Check $ \_ (configFlags, configExFlags) -> do -- Always set the chosen @--build-dir@ before saving the flags, -- or bad things could happen. @@ -149,6 +153,7 @@ reconfigure let configFlags' = configFlags { configDistPref = toFlag dist } return (Any distChanged, (configFlags', configExFlags)) + checkOutdated :: Check (ConfigFlags, b) checkOutdated = Check $ \_ flags@(configFlags, _) -> do let buildConfig = localBuildInfoFile dist @@ -172,7 +177,8 @@ reconfigure outdated <- existsAndIsMoreRecentThan descrFile buildConfig when outdated $ info verbosity (descrFile ++ " was changed") - let failed = + let failed :: Any + failed = Any outdated <> Any userPackageEnvironmentFileModified <> Any (not configured) diff --git a/cabal-install/src/Distribution/Client/SolverInstallPlan.hs b/cabal-install/src/Distribution/Client/SolverInstallPlan.hs index f4fbbfdadbd84890178b60e645bdefcb5fe4c203..02ac3973218a9e79517fd2239b44809bc90b314b 100644 --- a/cabal-install/src/Distribution/Client/SolverInstallPlan.hs +++ b/cabal-install/src/Distribution/Client/SolverInstallPlan.hs @@ -126,6 +126,7 @@ showPlanPackage (Configured spkg) = comps | null deps = "" | otherwise = " " ++ unwords (map prettyShow $ Foldable.toList deps) where + deps :: Set CD.Component deps = CD.components (solverPkgLibDeps spkg) <> CD.components (solverPkgExeDeps spkg) @@ -271,6 +272,7 @@ nonSetupClosure :: SolverPlanIndex -> SolverPlanIndex nonSetupClosure index pkgids0 = closure Graph.empty pkgids0 where + closure :: Graph SolverPlanPackage -> [SolverId] -> SolverPlanIndex closure completed [] = completed closure completed (pkgid:pkgids) = case Graph.lookup pkgid index of @@ -293,6 +295,7 @@ rootSets (IndependentGoals indepGoals) index = if indepGoals then map (:[]) libRoots else [libRoots] ++ setupRoots index where + libRoots :: [SolverId] libRoots = libraryRoots index -- | Compute the library roots of a plan diff --git a/cabal-install/src/Distribution/Client/SourceFiles.hs b/cabal-install/src/Distribution/Client/SourceFiles.hs index 279593684714d32b5a95ab408adb51a7ee2a2791..b6edd067b74adbe04f90e325fe0ed00934933a3c 100644 --- a/cabal-install/src/Distribution/Client/SourceFiles.hs +++ b/cabal-install/src/Distribution/Client/SourceFiles.hs @@ -21,6 +21,7 @@ import Distribution.Simple.PreProcess import Distribution.Types.PackageDescription import Distribution.Types.Component +import Distribution.Types.ComponentRequestedSpec (ComponentRequestedSpec) import Distribution.Types.Library import Distribution.Types.Executable import Distribution.Types.Benchmark @@ -48,8 +49,11 @@ needElaboratedPackage :: ElaboratedConfiguredPackage -> ElaboratedPackage -> Reb needElaboratedPackage elab epkg = traverse_ (needComponent pkg_descr) (enabledComponents pkg_descr enabled) where + pkg_descr :: PackageDescription pkg_descr = elabPkgDescription elab + enabled_stanzas :: OptionalStanzaSet enabled_stanzas = pkgStanzasEnabled epkg + enabled :: ComponentRequestedSpec enabled = enableStanzas enabled_stanzas needElaboratedComponent :: ElaboratedConfiguredPackage -> ElaboratedComponent -> Rebuild () @@ -58,7 +62,9 @@ needElaboratedComponent elab ecomp = Nothing -> needSetup Just comp -> needComponent pkg_descr comp where + pkg_descr :: PackageDescription pkg_descr = elabPkgDescription elab + mb_comp :: Maybe Component mb_comp = fmap (getComponent pkg_descr) (compComponentName ecomp) needComponent :: PackageDescription -> Component -> Rebuild () @@ -101,6 +107,7 @@ needTestSuite pkg_descr t needBuildInfo pkg_descr bi [m] TestSuiteUnsupported _ -> return () -- soft fail where + bi :: BuildInfo bi = testBuildInfo t needMainFile :: BuildInfo -> FilePath -> Rebuild () @@ -130,6 +137,7 @@ needBenchmark pkg_descr bm needMainFile bi mainPath BenchmarkUnsupported _ -> return () -- soft fail where + bi :: BuildInfo bi = benchmarkBuildInfo bm needBuildInfo :: PackageDescription -> BuildInfo -> [ModuleName] -> Rebuild ()