diff --git a/cabal-install/cabal-install.cabal b/cabal-install/cabal-install.cabal index f3f6be8a778..a3e53fa8452 100644 --- a/cabal-install/cabal-install.cabal +++ b/cabal-install/cabal-install.cabal @@ -179,7 +179,6 @@ library Distribution.Client.TargetSelector Distribution.Client.Targets Distribution.Client.Types - Distribution.Client.Types.AllowNewer Distribution.Client.Types.BuildResults Distribution.Client.Types.ConfiguredId Distribution.Client.Types.ConfiguredPackage diff --git a/cabal-install/src/Distribution/Client/Config.hs b/cabal-install/src/Distribution/Client/Config.hs index a40e31636cc..4b0b4c25036 100644 --- a/cabal-install/src/Distribution/Client/Config.hs +++ b/cabal-install/src/Distribution/Client/Config.hs @@ -84,15 +84,17 @@ import Distribution.Client.Setup , reportCommand , uploadCommand ) -import Distribution.Client.Types +import Distribution.Types.AllowNewer ( AllowNewer (..) , AllowOlder (..) - , LocalRepo (..) , RelaxDeps (..) + , isRelaxDeps + ) +import Distribution.Client.Types + ( LocalRepo (..) , RemoteRepo (..) , RepoName (..) , emptyRemoteRepo - , isRelaxDeps , unRepoName ) import Distribution.Client.Types.Credentials (Password (..), Username (..)) diff --git a/cabal-install/src/Distribution/Client/Configure.hs b/cabal-install/src/Distribution/Client/Configure.hs index d0abdac3430..2fef6334282 100644 --- a/cabal-install/src/Distribution/Client/Configure.hs +++ b/cabal-install/src/Distribution/Client/Configure.hs @@ -130,6 +130,7 @@ import Distribution.Version ) import System.FilePath (()) +import Distribution.Types.AllowNewer (AllowOlder(..), AllowNewer (..)) -- | Choose the Cabal version such that the setup scripts compiled against this -- version will support the given command-line flags. Currently, it implements no diff --git a/cabal-install/src/Distribution/Client/Dependency.hs b/cabal-install/src/Distribution/Client/Dependency.hs index 5bc5ec51b86..69883d248c2 100644 --- a/cabal-install/src/Distribution/Client/Dependency.hs +++ b/cabal-install/src/Distribution/Client/Dependency.hs @@ -77,19 +77,17 @@ import Distribution.Client.Dependency.Types ) import Distribution.Client.SolverInstallPlan (SolverInstallPlan) import qualified Distribution.Client.SolverInstallPlan as SolverInstallPlan -import Distribution.Client.Types +import Distribution.Types.AllowNewer ( AllowNewer (..) , AllowOlder (..) - , PackageSpecifier (..) - , RelaxDepMod (..) - , RelaxDepScope (..) - , RelaxDepSubject (..) , RelaxDeps (..) - , RelaxedDep (..) + , isRelaxDeps + ) +import Distribution.Client.Types + ( PackageSpecifier (..) , SourcePackageDb (SourcePackageDb) , UnresolvedPkgLoc , UnresolvedSourcePackage - , isRelaxDeps , pkgSpecifierConstraints , pkgSpecifierTarget ) @@ -163,6 +161,7 @@ import Data.List ) import qualified Data.Map as Map import qualified Data.Set as Set +import Distribution.AllowNewer (RelaxKind (..), relaxPackageDeps) -- ------------------------------------------------------------ @@ -528,8 +527,6 @@ removeUpperBounds (AllowNewer relDeps) = removeBounds RelaxUpper relDeps removeLowerBounds :: AllowOlder -> DepResolverParams -> DepResolverParams removeLowerBounds (AllowOlder relDeps) = removeBounds RelaxLower relDeps -data RelaxKind = RelaxLower | RelaxUpper - -- | Common internal implementation of 'removeLowerBounds'/'removeUpperBounds' removeBounds :: RelaxKind -> RelaxDeps -> DepResolverParams -> DepResolverParams removeBounds _ rd params | not (isRelaxDeps rd) = params -- no-op optimisation @@ -547,54 +544,6 @@ removeBounds relKind relDeps params = { srcpkgDescription = relaxPackageDeps relKind relDeps (srcpkgDescription srcPkg) } --- | Relax the dependencies of this package if needed. --- --- Helper function used by 'removeBounds' -relaxPackageDeps - :: RelaxKind - -> RelaxDeps - -> PD.GenericPackageDescription - -> PD.GenericPackageDescription -relaxPackageDeps _ rd gpd | not (isRelaxDeps rd) = gpd -- subsumed by no-op case in 'removeBounds' -relaxPackageDeps relKind RelaxDepsAll gpd = PD.transformAllBuildDepends relaxAll gpd - where - relaxAll :: Dependency -> Dependency - relaxAll (Dependency pkgName verRange cs) = - Dependency pkgName (removeBound relKind RelaxDepModNone verRange) cs -relaxPackageDeps relKind (RelaxDepsSome depsToRelax0) gpd = - PD.transformAllBuildDepends relaxSome gpd - where - thisPkgName = packageName gpd - thisPkgId = packageId gpd - depsToRelax = Map.fromList $ mapMaybe f depsToRelax0 - - f :: RelaxedDep -> Maybe (RelaxDepSubject, RelaxDepMod) - f (RelaxedDep scope rdm p) = case scope of - RelaxDepScopeAll -> Just (p, rdm) - RelaxDepScopePackage p0 - | p0 == thisPkgName -> Just (p, rdm) - | otherwise -> Nothing - RelaxDepScopePackageId p0 - | p0 == thisPkgId -> Just (p, rdm) - | otherwise -> Nothing - - relaxSome :: Dependency -> Dependency - relaxSome d@(Dependency depName verRange cs) - | Just relMod <- Map.lookup RelaxDepSubjectAll depsToRelax = - -- a '*'-subject acts absorbing, for consistency with - -- the 'Semigroup RelaxDeps' instance - Dependency depName (removeBound relKind relMod verRange) cs - | Just relMod <- Map.lookup (RelaxDepSubjectPkg depName) depsToRelax = - Dependency depName (removeBound relKind relMod verRange) cs - | otherwise = d -- no-op - --- | Internal helper for 'relaxPackageDeps' -removeBound :: RelaxKind -> RelaxDepMod -> VersionRange -> VersionRange -removeBound RelaxLower RelaxDepModNone = removeLowerBound -removeBound RelaxUpper RelaxDepModNone = removeUpperBound -removeBound RelaxLower RelaxDepModCaret = transformCaretLower -removeBound RelaxUpper RelaxDepModCaret = transformCaretUpper - -- | Supply defaults for packages without explicit Setup dependencies -- -- Note: It's important to apply 'addDefaultSetupDepends' after diff --git a/cabal-install/src/Distribution/Client/Install.hs b/cabal-install/src/Distribution/Client/Install.hs index 93ad8e5ae2e..bfb50e48b17 100644 --- a/cabal-install/src/Distribution/Client/Install.hs +++ b/cabal-install/src/Distribution/Client/Install.hs @@ -267,6 +267,7 @@ import Distribution.Version ) import qualified Data.ByteString as BS +import Distribution.Types.AllowNewer (AllowOlder(..), AllowNewer (..)) -- TODO: diff --git a/cabal-install/src/Distribution/Client/ProjectConfig.hs b/cabal-install/src/Distribution/Client/ProjectConfig.hs index 2a0f82215c2..2f137d173ae 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig.hs @@ -221,6 +221,7 @@ import System.IO ( IOMode (ReadMode) , withBinaryFile ) +import Distribution.Types.AllowNewer (AllowOlder(..), AllowNewer (..)) ---------------------------------------- -- Resolving configuration to settings diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs index cf39d2940ee..220cccb7624 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs @@ -35,7 +35,7 @@ import Distribution.Client.Compat.Prelude import Distribution.Types.Flag (FlagName, parsecFlagAssignment) import Distribution.Client.ProjectConfig.Types -import Distribution.Client.Types.AllowNewer (AllowNewer (..), AllowOlder (..)) +import Distribution.Types.AllowNewer (AllowNewer (..), AllowOlder (..)) import Distribution.Client.Types.Repo (LocalRepo (..), RemoteRepo (..), emptyRemoteRepo) import Distribution.Client.Types.RepoName (RepoName (..), unRepoName) import Distribution.Client.Types.SourceRepo (SourceRepoList, sourceRepositoryPackageGrammar) diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs index 3ae80d86d31..57dfb9b8573 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs @@ -32,7 +32,7 @@ import Distribution.Client.Dependency.Types import Distribution.Client.Targets ( UserConstraint ) -import Distribution.Client.Types.AllowNewer (AllowNewer (..), AllowOlder (..)) +import Distribution.Types.AllowNewer (AllowNewer (..), AllowOlder (..)) import Distribution.Client.Types.Repo (LocalRepo, RemoteRepo) import Distribution.Client.Types.SourceRepo (SourceRepoList) import Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy (WriteGhcEnvironmentFilesPolicy) diff --git a/cabal-install/src/Distribution/Client/Setup.hs b/cabal-install/src/Distribution/Client/Setup.hs index f550c6e36e8..a02d3739296 100644 --- a/cabal-install/src/Distribution/Client/Setup.hs +++ b/cabal-install/src/Distribution/Client/Setup.hs @@ -92,7 +92,7 @@ module Distribution.Client.Setup import Distribution.Client.Compat.Prelude hiding (get) import Prelude () -import Distribution.Client.Types.AllowNewer (AllowNewer (..), AllowOlder (..), RelaxDeps (..)) +import Distribution.Types.AllowNewer (AllowNewer (..), AllowOlder (..), RelaxDeps (..)) import Distribution.Client.Types.Credentials (Password (..), Username (..)) import Distribution.Client.Types.Repo (LocalRepo (..), RemoteRepo (..)) import Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy @@ -660,7 +660,9 @@ filterConfigureFlags flags cabalLibVersion -- Note: this is not in the wrong place. configConstraints gets -- repopulated in flags_1_19_1 but it needs to be set to empty for -- newer versions first. - configConstraints = [] + configConstraints = [], + configAllowNewer = AllowNever mempty, + configAllowOlder = AllowOlder mempty } flags_3_11_0 = diff --git a/cabal-install/src/Distribution/Client/Types.hs b/cabal-install/src/Distribution/Client/Types.hs index 710960ee939..338932d1376 100644 --- a/cabal-install/src/Distribution/Client/Types.hs +++ b/cabal-install/src/Distribution/Client/Types.hs @@ -21,8 +21,7 @@ -- -- Various common data types for the entire cabal-install system module Distribution.Client.Types - ( module Distribution.Client.Types.AllowNewer - , module Distribution.Client.Types.ConfiguredId + ( module Distribution.Client.Types.ConfiguredId , module Distribution.Client.Types.ConfiguredPackage , module Distribution.Client.Types.BuildResults , module Distribution.Client.Types.PackageLocation @@ -34,7 +33,6 @@ module Distribution.Client.Types , module Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy ) where -import Distribution.Client.Types.AllowNewer import Distribution.Client.Types.BuildResults import Distribution.Client.Types.ConfiguredId import Distribution.Client.Types.ConfiguredPackage diff --git a/cabal-install/src/Distribution/Client/Types/AllowNewer.hs b/cabal-install/src/Distribution/Client/Types/AllowNewer.hs deleted file mode 100644 index 0a5700174b8..00000000000 --- a/cabal-install/src/Distribution/Client/Types/AllowNewer.hs +++ /dev/null @@ -1,244 +0,0 @@ -{-# LANGUAGE DeriveGeneric #-} - -module Distribution.Client.Types.AllowNewer - ( AllowNewer (..) - , AllowOlder (..) - , RelaxDeps (..) - , mkRelaxDepSome - , RelaxDepMod (..) - , RelaxDepScope (..) - , RelaxDepSubject (..) - , RelaxedDep (..) - , isRelaxDeps - ) where - -import Distribution.Client.Compat.Prelude -import Prelude () - -import Distribution.Parsec (parsecLeadingCommaNonEmpty) -import Distribution.Types.PackageId (PackageId, PackageIdentifier (..)) -import Distribution.Types.PackageName (PackageName, mkPackageName) -import Distribution.Types.Version (nullVersion) - -import qualified Distribution.Compat.CharParsing as P -import qualified Text.PrettyPrint as Disp - --- $setup --- >>> import Distribution.Parsec - --- TODO: When https://github.com/haskell/cabal/issues/4203 gets tackled, --- it may make sense to move these definitions to the Solver.Types --- module - --- | 'RelaxDeps' in the context of upper bounds (i.e. for @--allow-newer@ flag) -newtype AllowNewer = AllowNewer {unAllowNewer :: RelaxDeps} - deriving (Eq, Read, Show, Generic) - --- | 'RelaxDeps' in the context of lower bounds (i.e. for @--allow-older@ flag) -newtype AllowOlder = AllowOlder {unAllowOlder :: RelaxDeps} - deriving (Eq, Read, Show, Generic) - --- | Generic data type for policy when relaxing bounds in dependencies. --- Don't use this directly: use 'AllowOlder' or 'AllowNewer' depending --- on whether or not you are relaxing an lower or upper bound --- (respectively). -data RelaxDeps - = -- | Ignore upper (resp. lower) bounds in some (or no) dependencies on the given packages. - -- - -- @RelaxDepsSome []@ is the default, i.e. honor the bounds in all - -- dependencies, never choose versions newer (resp. older) than allowed. - RelaxDepsSome [RelaxedDep] - | -- | Ignore upper (resp. lower) bounds in dependencies on all packages. - -- - -- __Note__: This is should be semantically equivalent to - -- - -- > RelaxDepsSome [RelaxedDep RelaxDepScopeAll RelaxDepModNone RelaxDepSubjectAll] - -- - -- (TODO: consider normalising 'RelaxDeps' and/or 'RelaxedDep') - RelaxDepsAll - deriving (Eq, Read, Show, Generic) - --- | Dependencies can be relaxed either for all packages in the install plan, or --- only for some packages. -data RelaxedDep = RelaxedDep !RelaxDepScope !RelaxDepMod !RelaxDepSubject - deriving (Eq, Read, Show, Generic) - --- | Specify the scope of a relaxation, i.e. limit which depending --- packages are allowed to have their version constraints relaxed. -data RelaxDepScope - = -- | Apply relaxation in any package - RelaxDepScopeAll - | -- | Apply relaxation to in all versions of a package - RelaxDepScopePackage !PackageName - | -- | Apply relaxation to a specific version of a package only - RelaxDepScopePackageId !PackageId - deriving (Eq, Read, Show, Generic) - --- | Modifier for dependency relaxation -data RelaxDepMod - = -- | Default semantics - RelaxDepModNone - | -- | Apply relaxation only to @^>=@ constraints - RelaxDepModCaret - deriving (Eq, Read, Show, Generic) - --- | Express whether to relax bounds /on/ @all@ packages, or a single package -data RelaxDepSubject - = RelaxDepSubjectAll - | RelaxDepSubjectPkg !PackageName - deriving (Eq, Ord, Read, Show, Generic) - -instance Pretty RelaxedDep where - pretty (RelaxedDep scope rdmod subj) = case scope of - RelaxDepScopeAll -> Disp.text "*:" Disp.<> modDep - RelaxDepScopePackage p0 -> pretty p0 Disp.<> Disp.colon Disp.<> modDep - RelaxDepScopePackageId p0 -> pretty p0 Disp.<> Disp.colon Disp.<> modDep - where - modDep = case rdmod of - RelaxDepModNone -> pretty subj - RelaxDepModCaret -> Disp.char '^' Disp.<> pretty subj - -instance Parsec RelaxedDep where - parsec = P.char '*' *> relaxedDepStarP <|> (parsec >>= relaxedDepPkgidP) - --- continuation after * -relaxedDepStarP :: CabalParsing m => m RelaxedDep -relaxedDepStarP = - RelaxedDep RelaxDepScopeAll <$ P.char ':' <*> modP <*> parsec - <|> pure (RelaxedDep RelaxDepScopeAll RelaxDepModNone RelaxDepSubjectAll) - --- continuation after package identifier -relaxedDepPkgidP :: CabalParsing m => PackageIdentifier -> m RelaxedDep -relaxedDepPkgidP pid@(PackageIdentifier pn v) - | pn == mkPackageName "all" - , v == nullVersion = - RelaxedDep RelaxDepScopeAll <$ P.char ':' <*> modP <*> parsec - <|> pure (RelaxedDep RelaxDepScopeAll RelaxDepModNone RelaxDepSubjectAll) - | v == nullVersion = - RelaxedDep (RelaxDepScopePackage pn) <$ P.char ':' <*> modP <*> parsec - <|> pure (RelaxedDep RelaxDepScopeAll RelaxDepModNone (RelaxDepSubjectPkg pn)) - | otherwise = - RelaxedDep (RelaxDepScopePackageId pid) <$ P.char ':' <*> modP <*> parsec - -modP :: P.CharParsing m => m RelaxDepMod -modP = RelaxDepModCaret <$ P.char '^' <|> pure RelaxDepModNone - -instance Pretty RelaxDepSubject where - pretty RelaxDepSubjectAll = Disp.text "*" - pretty (RelaxDepSubjectPkg pn) = pretty pn - -instance Parsec RelaxDepSubject where - parsec = RelaxDepSubjectAll <$ P.char '*' <|> pkgn - where - pkgn = do - pn <- parsec - pure $ - if pn == mkPackageName "all" - then RelaxDepSubjectAll - else RelaxDepSubjectPkg pn - -instance Pretty RelaxDeps where - pretty rd | not (isRelaxDeps rd) = Disp.text "none" - pretty (RelaxDepsSome pkgs) = - Disp.fsep - . Disp.punctuate Disp.comma - . map pretty - $ pkgs - pretty RelaxDepsAll = Disp.text "all" - --- | --- --- >>> simpleParsec "all" :: Maybe RelaxDeps --- Just RelaxDepsAll --- --- >>> simpleParsec "none" :: Maybe RelaxDeps --- Just (RelaxDepsSome []) --- --- >>> simpleParsec "*, *" :: Maybe RelaxDeps --- Just RelaxDepsAll --- --- >>> simpleParsec "*:*" :: Maybe RelaxDeps --- Just RelaxDepsAll --- --- >>> simpleParsec "foo:bar, quu:puu" :: Maybe RelaxDeps --- Just (RelaxDepsSome [RelaxedDep (RelaxDepScopePackage (PackageName "foo")) RelaxDepModNone (RelaxDepSubjectPkg (PackageName "bar")),RelaxedDep (RelaxDepScopePackage (PackageName "quu")) RelaxDepModNone (RelaxDepSubjectPkg (PackageName "puu"))]) --- --- This is not a glitch, even it looks like: --- --- >>> simpleParsec ", all" :: Maybe RelaxDeps --- Just RelaxDepsAll --- --- >>> simpleParsec "" :: Maybe RelaxDeps --- Nothing -instance Parsec RelaxDeps where - parsec = do - xs <- parsecLeadingCommaNonEmpty parsec - pure $ case toList xs of - [RelaxedDep RelaxDepScopeAll RelaxDepModNone RelaxDepSubjectAll] -> - RelaxDepsAll - [RelaxedDep RelaxDepScopeAll RelaxDepModNone (RelaxDepSubjectPkg pn)] - | pn == mkPackageName "none" -> - mempty - xs' -> mkRelaxDepSome xs' - -instance Binary RelaxDeps -instance Binary RelaxDepMod -instance Binary RelaxDepScope -instance Binary RelaxDepSubject -instance Binary RelaxedDep -instance Binary AllowNewer -instance Binary AllowOlder - -instance Structured RelaxDeps -instance Structured RelaxDepMod -instance Structured RelaxDepScope -instance Structured RelaxDepSubject -instance Structured RelaxedDep -instance Structured AllowNewer -instance Structured AllowOlder - --- | Return 'True' if 'RelaxDeps' specifies a non-empty set of relaxations --- --- Equivalent to @isRelaxDeps = (/= 'mempty')@ -isRelaxDeps :: RelaxDeps -> Bool -isRelaxDeps (RelaxDepsSome []) = False -isRelaxDeps (RelaxDepsSome (_ : _)) = True -isRelaxDeps RelaxDepsAll = True - --- | A smarter 'RelaxedDepsSome', @*:*@ is the same as @all@. -mkRelaxDepSome :: [RelaxedDep] -> RelaxDeps -mkRelaxDepSome xs - | any (== RelaxedDep RelaxDepScopeAll RelaxDepModNone RelaxDepSubjectAll) xs = - RelaxDepsAll - | otherwise = - RelaxDepsSome xs - --- | 'RelaxDepsAll' is the /absorbing element/ -instance Semigroup RelaxDeps where - -- identity element - RelaxDepsSome [] <> r = r - l@(RelaxDepsSome _) <> RelaxDepsSome [] = l - -- absorbing element - l@RelaxDepsAll <> _ = l - (RelaxDepsSome _) <> r@RelaxDepsAll = r - -- combining non-{identity,absorbing} elements - (RelaxDepsSome a) <> (RelaxDepsSome b) = RelaxDepsSome (a ++ b) - --- | @'RelaxDepsSome' []@ is the /identity element/ -instance Monoid RelaxDeps where - mempty = RelaxDepsSome [] - mappend = (<>) - -instance Semigroup AllowNewer where - AllowNewer x <> AllowNewer y = AllowNewer (x <> y) - -instance Semigroup AllowOlder where - AllowOlder x <> AllowOlder y = AllowOlder (x <> y) - -instance Monoid AllowNewer where - mempty = AllowNewer mempty - mappend = (<>) - -instance Monoid AllowOlder where - mempty = AllowOlder mempty - mappend = (<>) diff --git a/cabal-install/tests/UnitTests/Distribution/Client/ArbitraryInstances.hs b/cabal-install/tests/UnitTests/Distribution/Client/ArbitraryInstances.hs index 0ff8e280823..cd085322cfb 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/ArbitraryInstances.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/ArbitraryInstances.hs @@ -38,7 +38,7 @@ import Distribution.Client.IndexUtils.IndexState (RepoIndexState (..), TotalInde import Distribution.Client.IndexUtils.Timestamp (Timestamp, epochTimeToTimestamp) import Distribution.Client.Targets import Distribution.Client.Types (RepoName (..), WriteGhcEnvironmentFilesPolicy) -import Distribution.Client.Types.AllowNewer +import Distribution.Types.AllowNewer import Distribution.Client.Types.OverwritePolicy (OverwritePolicy) import Distribution.Solver.Types.OptionalStanza (OptionalStanza (..), OptionalStanzaMap, OptionalStanzaSet, optStanzaSetFromList, optStanzaTabulate) import Distribution.Solver.Types.PackageConstraint (PackageProperty (..)) diff --git a/cabal-install/tests/UnitTests/Distribution/Client/Described.hs b/cabal-install/tests/UnitTests/Distribution/Client/Described.hs index fbd544a9a0b..c46a8ae880a 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/Described.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/Described.hs @@ -18,7 +18,7 @@ import Distribution.Client.IndexUtils.IndexState (RepoIndexState, TotalIndexStat import Distribution.Client.IndexUtils.Timestamp (Timestamp) import Distribution.Client.Targets (UserConstraint) import Distribution.Client.Types (RepoName) -import Distribution.Client.Types.AllowNewer (RelaxDepSubject, RelaxDeps, RelaxedDep) +import Distribution.Types.AllowNewer (RelaxDepSubject, RelaxDeps, RelaxedDep) tests :: TestTree tests = diff --git a/cabal-install/tests/UnitTests/Distribution/Client/DescribedInstances.hs b/cabal-install/tests/UnitTests/Distribution/Client/DescribedInstances.hs index 66b9649db11..45acfd00b92 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/DescribedInstances.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/DescribedInstances.hs @@ -19,7 +19,7 @@ import Distribution.Client.IndexUtils.IndexState (RepoIndexState, TotalIndexStat import Distribution.Client.IndexUtils.Timestamp (Timestamp) import Distribution.Client.Targets (UserConstraint) import Distribution.Client.Types (RepoName) -import Distribution.Client.Types.AllowNewer (RelaxDepSubject, RelaxDeps, RelaxedDep) +import Distribution.Types.AllowNewer (RelaxDepSubject, RelaxDeps, RelaxedDep) ------------------------------------------------------------------------------- -- BuildReport diff --git a/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs b/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs index b1108d77701..94084e8fc80 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs @@ -66,6 +66,7 @@ import Data.TreeDiff.QuickCheck import Test.Tasty import Test.Tasty.HUnit import Test.Tasty.QuickCheck +import Distribution.Types.AllowNewer tests :: [TestTree] tests = diff --git a/cabal-install/tests/UnitTests/Distribution/Client/TreeDiffInstances.hs b/cabal-install/tests/UnitTests/Distribution/Client/TreeDiffInstances.hs index 495c4cbf402..6a64934606c 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/TreeDiffInstances.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/TreeDiffInstances.hs @@ -20,6 +20,7 @@ import Distribution.Client.Types import Distribution.Client.Types.OverwritePolicy (OverwritePolicy) import Distribution.Client.Types.SourceRepo (SourceRepositoryPackage) +import Distribution.Types.AllowNewer import Distribution.Simple.Compiler (PackageDB) import Data.TreeDiff.Class