planning for ghc-6.10.1 and hackage

Hi, We're getting pretty close to a final ghc-6.10.1 release. We would like of course for the transition this time to be less painful than last time. We all got a lot of flack last time for having no plan in place and making everyone change all their .cabal files etc. This time we can do a lot better. We have already decided to ship two versions of base, version 3 and version 4. Version 4 is the even more stripped down one, and with changes to exception handling etc. The version 3.1 of base depends on base 4 and re-exports most of it with a few differences so that it provides essentially the same api as base 3.0 did (which was included in ghc-6.8.x). However we are not all the way there yet. If we released ghc-6.10.1 today everything would still break. By everything I mean everyone's private projects and all the packages on hackage. The only packages that would build would be trivial ones, or the ones that come with ghc. There are two primary causes of this breakage: * cabal-installs dependency resolver does not work with base 3 & 4 * Cabal will still build packages using base-4 rather than 3 because most packages say "build-depends: base >= 2" rather than "build-depends: base ==3.*" The current cabal-install dependency resolver is based around the idea of picking at most one version of each package. This is because typically using two versions of any package is a mistake. For base we now have the situation that version 3 depends on version 4. So the current resolver will find a conflict as soon as anything needs base 3. The other problem is that packages currently typically specify an optimistic upwardly open range rather than a pessimistic closed range. Cabal uses the heuristic of picking the highest version of each package that satisfies the version constraints. I propose two solutions: * Fix the dependency resolver * Add support in Cabal and Hackage for suggested version constraints The second is considerably easier than the first. The second involves adjusting the dependency resolver to accept a per-package version constraint, like "base < 4", "QuickCheck < 2" or "parsec < 3". It would be a soft constraint that is used only when there is still a free choice between multiple package versions. This should help the situation with upward open version ranges like "build-depends: base". I have done this first part but not tested it yet. Then we would add this list of suggestions as an extra file in the 00-index.tar.gz file on hackage and make cabal-install use it. Hopefully doing this would allow us to not have to change every .cabal file on hackage, at least not immediately. In tandem we should encourage (using automatic warnings) people to use closed version ranges. The first problem is quite hard. I could really do with some help on it. The current dep resolver is a very simple constraint solving algorithm. It's only as clever as was needed to make things work in most cases. It is not a full general solver. It it based on being able to collect version constraints per-package and end up with exactly one version of a package. The obvious adaptation is to say that we can have multiple slots for a single package, one for base 3 and one for base 4. However it is not clear when we would decide to use two slots. Even if we just hack it and hard code there being two for base, we do not know which slot to put constraints into, probably both. My concern here obviously is that if we release a ghc-6.10.1 and tell everyone to start using it immediately for everything then we'll have chaos and take yet more flack for breaking everything. It would also be a great shame since Simon and Ian have already put a not-insignificant amount of effort into the underlying mechanisms to allow us to provide a compatibility base-3 package. Remember we do have the ability to set up an extra hackage server with everything and test how much builds or breaks with ghc-6.10. I'd like the time to do a test run with that before the release so that we can tell people what the expected level of breakage is and how to fix it. I'm not doing that immediately because I already know nothing will work atm without the two above issues being fixed. So I'll aim to work on both issues this week and report back on how things are going. Duncan

duncan.coutts:
Hi,
We're getting pretty close to a final ghc-6.10.1 release. We would like of course for the transition this time to be less painful than last time. We all got a lot of flack last time for having no plan in place and making everyone change all their .cabal files etc.
This time we can do a lot better. We have already decided to ship two versions of base, version 3 and version 4. Version 4 is the even more stripped down one, and with changes to exception handling etc. The version 3.1 of base depends on base 4 and re-exports most of it with a few differences so that it provides essentially the same api as base 3.0 did (which was included in ghc-6.8.x).
However we are not all the way there yet. If we released ghc-6.10.1 today everything would still break. By everything I mean everyone's private projects and all the packages on hackage. The only packages that would build would be trivial ones, or the ones that come with ghc.
Here are my notes on why this is so hard, and so scary, and what we can do. So Duncan and I spent about 6 hours tonight working out how to make the cabal-install constraint solver, and the Cabal configure invariants, work when programs attempt to use base-3 and base-4 on the same system. Here's a summary of why this is non-trivial, * We're trying to compose packages on the users machine to yield new type correct programs. * We're using cabal dependencies to decide when it is safe to do this. Hopefully we don't rule in any type incorrect combinations, nor rule out to many type correct combinations. * This is scary - in fact, we think the package system admits type incorrect programs (based on Typeable, or initialised global state), as it is similar to the runtime linking problem for modules. * We use constraint solving determine when composition is safe, by looking at "package >= 3 && < 4" style constraints. That is, we try to guess when the composition would yield a type correct program. * Again, we're using constraint solving on this language to determine when composition of Haskell module sets (aka packages) would yield type correct Haskell programs All without attempting to do type checking of the interfaces between packages -- the very thing that says whether this is sound! * This previously relied on a strong invariant: + There was only to be one package-version assignment in a program + People didn't change APIs too much, and tried to follow the versioning spec, and wrote .cabal deps that followed the spec. * But now we allow multiple package-version assignments, as long as one depends on the other, and doesn't redefine types. (You'll notice by now we're in deep scary-land, trying, after compile time, to compose type correct modules into sets of modules (packages), and then composing those sets with each other to yield type correct programs, some of which redefine parts of the module hierarchy, and doing all this without implementing a type checking story for when to combine these sets safely). * So, the solver for cabal-install has to be updated to allow the same package to have multiple, conflicting versions, as long as version X depends on version Y, and then not reject programs that produce this constraint. * This is non trivial, but think this refactoring is possible, but it is hard. ultimately we're still making optimistic assumptions about when module sets can be combined to produce type correct programs, and conservative assumptions, at the same time. What we need is a semantics for packages, that in turn uses a semantics for modules, that explains interfaces in terms of types. Packages of functors, containing modules, which we can truly compose to yield type correct programs. * But we think the cabal-install solver will be refactorable to let a good number of programs work, but it'll take a few days of constraint solver hacking. * The end result is that cabal-install should be able to find automated install plans for packages that ask for base-3, even when base-4 is on the system as well, and it uses pieces of base-3 libraries and base-4 libraries. Some more programs will work than if we didn't ship base-3. * The two other ways of combining packages into Haskell programs, + ghc --make + runhaskell Setup.hs configure will always pick base-4 now, so you won't be able to build programs against the base-3 without manually overriding. This means things that need the old exception API, for example, or syb, will break without manual hiding (--package base-3.0.0.0). * We're missing hard stats on what number of things break under which scheme. -- Don

Don Stewart wrote:
Here's a summary of why this is non-trivial,
* We're trying to compose packages on the users machine to yield new type correct programs.
* We're using cabal dependencies to decide when it is safe to do this. Hopefully we don't rule in any type incorrect combinations, nor rule out to many type correct combinations.
* This is scary - in fact, we think the package system admits type incorrect programs (based on Typeable, or initialised global state), as it is similar to the runtime linking problem for modules.
I think what you're referring to is the problem that occurs if the program links in more than one copy of Data.Typeable, which would then invalidate the assumptions that make Data.Typeable's use of unsafeCoerce safe. I wouldn't call this "type-incorrect" - it's a violation of assumptions made by Data.Typeable, not type-incorrectness in the Haskell sense. But you'll be glad to know this doesn't happen anyway, because Data.Typeable's state is held by the RTS these days, for exactly this reason. However, there are libraries which do have private state (e.g. System.Random). We'd prefer not to have more than one copy of the state, but it's not usually fatal: in the case of System.Random, different clients might get streams of random numbers initialised from different seeds, but that's indistinguishable from sharing a single stream of random numbers. Often this global-state stuff is for caching, which works just fine when multiple clients use different versions of the library - it's just a bit less efficient.
* We use constraint solving determine when composition is safe, by looking at "package >= 3 && < 4" style constraints. That is, we try to guess when the composition would yield a type correct program.
The way to make this completely safe is to ensure that the resulting program only has one of each module, rather than one of each package version - that's an approximation, because the package name might have changed too. Now, we want to relax this in various ways. One way is the base-3/base-4 situation, where base-3 has a lot of the same modules as base-4, but all they do is re-export stuff from other packages. How do we know this is safe? Well, we don't - the only way is to check whether the resulting program typechecks. Another way we want to relax is it when a dependency is "private" to a package; that is, the package API is completely independent of the dependency, and hence changing the dependency cannot cause compilation failure elsewhere. We've talked in the past about how it would be nice to distinguish private from non-private dependencies. Let's be clear: there are only two ways that something could "go wrong" when composing packages: 1. the composition is not type-correct; you get a compile-time error 2. some top-level state is duplicated; if the programmer has been careful in their use of unsafePerformIO, then typically this won't lead to a run-time error. So it's highly unlikely you end up with a program that goes wrong at runtime, and in those cases arguably the library developer has made incorrect assumptions about unsafePerformIO.
* Again, we're using constraint solving on this language to determine when composition of Haskell module sets (aka packages) would yield type correct Haskell programs
All without attempting to do type checking of the interfaces between packages -- the very thing that says whether this is sound!
True - but we already know that package/version pairs are a proxy for interfaces, and subject to user failure. If the package says that it compiles against a given package/version pair, there's no guarantee that it actually does, that's up to the package author to ensure. Now obviously we'd like something more robust here, but that's a separate problem - not an unimportant one, but separate from the issue of how to make cabal-install work with GHC 6.10.1. cabal-install has to start from the assumption that all the dependencies are correct. Then it can safely construct a complete program by combining all the constraints, and additionally ensuring that the combination has no more than one of each module (and possibly relaxing this restriction when we know it is safe to do so).
* So, the solver for cabal-install has to be updated to allow the same package to have multiple, conflicting versions, as long as version X depends on version Y, and then not reject programs that produce this constraint.
Right.
* This is non trivial, but think this refactoring is possible, but it is hard. ultimately we're still making optimistic assumptions about when module sets can be combined to produce type correct programs, and conservative assumptions, at the same time.
What we need is a semantics for packages, that in turn uses a semantics for modules, that explains interfaces in terms of types.
The semantics is quite straightforward: a module is identified by the pair (package-id, module name), and then you just use the Haskell module system semantics. That is, replace all module names in the program with (package-id, module name) pairs according to which packages are in scope in the context of each module, and then proceed to interpret the program as in Haskell 98. The main problem with looking at things this way is that you need to see the whole program - which is what I've been arguing against in the context of instances. So I agree that looking for a semantics for packages that lets you treat them as an abstract entity would be useful. Still, the above interpretation of packages is a good starting point, because it tells you whether a higher-level semantics is really equivalent.
* The end result is that cabal-install should be able to find automated install plans for packages that ask for base-3, even when base-4 is on the system as well, and it uses pieces of base-3 libraries and base-4 libraries. Some more programs will work than if we didn't ship base-3.
So I'm not sure exactly how cabal-install works now, but I imagine you could search for a solution with a backtracking algorithm, and prune solutions that involve multiple versions of the same package, unless those two versions are allowed to co-exist (e.g. base-3/base-4). If backtracking turns out to be too expensive, then maybe more heavyweight constraint-solving would be needed, but I'd try the simple way first. What happens with automatic flag assignments? Presumably we can decide what the flag assignment for each package is up-front? Cheers, Simon

Simon Marlow wrote:
So I'm not sure exactly how cabal-install works now, but I imagine you could search for a solution with a backtracking algorithm, and prune solutions that involve multiple versions of the same package, unless those two versions are allowed to co-exist (e.g. base-3/base-4). If backtracking turns out to be too expensive, then maybe more heavyweight constraint-solving would be needed, but I'd try the simple way first.
Attached is a simple backtracking solver. It doesn't do everything you want, e.g. it doesn't distinguish between installed and uninstalled packages, and it doesn't figure out for itself which versions are allowed together (you have to tell it), but I think it's a good start. It would be interetsing to populate the database with a more realistic collection of packages and try out some complicated install plans. Cheers, Simon module Main(main) where import Data.List import Data.Function import Prelude hiding (EQ) type Package = String type Version = Int type PackageId = (Package,Version) data Constraint = EQ Version | GE Version | LE Version deriving (Eq,Ord,Show) satisfies :: Version -> Constraint -> Bool satisfies v (EQ v') = v == v' satisfies v (GE v') = v >= v' satisfies v (LE v') = v <= v' allowedWith :: PackageId -> PackageId -> Bool allowedWith (p,v1) (q,v2) = p /= q || v1 == v2 || multipleVersionsAllowed p type Dep = (Package, Constraint) depsOf :: PackageId -> [Dep] depsOf pid = head [ deps | (pid',deps) <- packageDB, pid == pid' ] packageIds :: Package -> [PackageId] packageIds pkg = [ pid | (pid@(n,v),_) <- packageDB, n == pkg ] satisfy :: Dep -> [PackageId] satisfy (target,constraint) = [ pid | pid@(_,v) <- packageIds target, v `satisfies` constraint ] -- | solve takes a list of dependencies to resolve, and a list of -- packages we have decided on already, and returns a list of -- solutions. -- solve :: [Dep] -> [PackageId] -> [[PackageId]] solve [] sofar = [sofar] -- no more deps: we win solve (dep:deps) sofar = [ solution | pid <- satisfy dep, pid `consistentWith` sofar, solution <- solve (depsOf pid ++ deps) (pid:sofar) ] consistentWith :: PackageId -> [PackageId] -> Bool consistentWith pid = all (pid `allowedWith`) plan :: Package -> [[PackageId]] plan p = pretty $ solve [(p,GE 0)] [] pretty = nub . map (nub.sort) main = do print $ plan "p" print $ plan "yi" -- ----------------------------------------------------------------------------- -- Data packageDB :: [(PackageId, [Dep])] packageDB = [ (("base",3), []), (("base",4), []), (("p", 1), [("base", LE 4), ("base", GE 3), ("q", GE 1)]), (("q", 1), [("base", LE 3)]), (("bytestring",1), [("base", EQ 4)]), -- installed (("bytestring",2), [("base", EQ 4)]), -- installed (("ghc", 1), [("bytestring", EQ 1)]), -- installed (("ghc", 2), [("bytestring", GE 2)]), (("yi", 1), [("ghc", GE 1), ("bytestring", GE 2)]) ] multipleVersionsAllowed :: Package -> Bool multipleVersionsAllowed "base" = True -- approximation, of course multipleVersionsAllowed _ = False

On Thu, 2008-10-02 at 14:08 +0100, Simon Marlow wrote:
Simon Marlow wrote:
So I'm not sure exactly how cabal-install works now, but I imagine you could search for a solution with a backtracking algorithm, and prune solutions that involve multiple versions of the same package, unless those two versions are allowed to co-exist (e.g. base-3/base-4). If backtracking turns out to be too expensive, then maybe more heavyweight constraint-solving would be needed, but I'd try the simple way first.
Attached is a simple backtracking solver. It doesn't do everything you want, e.g. it doesn't distinguish between installed and uninstalled packages, and it doesn't figure out for itself which versions are allowed together (you have to tell it), but I think it's a good start. It would be interetsing to populate the database with a more realistic collection of packages and try out some complicated install plans.
I've not tried it yet, but the main danger with simple backtracking solvers is that they try too many solutions and take too long. It is afterall an NP-complete problem and the complete search space is exponential. We do need to find solutions for installing all of hackage simultaneously and consistently. The current solver does this in a few tens of seconds (but it does no backtracking). My intuition is that I would not go for a complete solver unless it was a good deal more heavyweight. There is a good paper in this area[1] and is the basis of the solver for the debian packages that the Linspire guys wrote. [1] Modular Lazy Search for Constraint Satisfaction Problems http://citeseer.ist.psu.edu/nordin01modular.html So when we have more time we should look at using a more sophisticated solver along these lines. Duncan

We're getting pretty close to a final ghc-6.10.1 release. We would like of course for the transition this time to be less painful than last time. We all got a lot of flack last time for having no plan in place and making everyone change all their .cabal files etc.
Thanks to everyone looking into making the transition less of an event this time! While you've got everyone's attention: there are beta releases (a kind of pre-release-candidate?-) of ghc-6.10.1: http://www.haskell.org/pipermail/glasgow-haskell-users/2008-September/015539... and there will be release candidates, so package authors can actually try and check whether their package can depend on base4 or should limit itself to base3 (either way, it should still specify exactly the range of versions that is known to work), and whether there are other issues. Two things at least that spring to mind, which authors might want to check: - ghc-6.10.1 comes with haddock 2 (are there hickups in the generated docs?) - ghc-6.10.1 comes with a restructured ghc api (all ghc api clients will break; the fixes are likely to be minor, but fixing will be necessary)
The other problem is that packages currently typically specify an optimistic upwardly open range rather than a pessimistic closed range. Cabal uses the heuristic of picking the highest version of each package that satisfies the version constraints.
One could try to use the Ghc Api to run Ghc in typecheck-only mode, trying the highest versions of dependencies, as given by Cabal's heuristic, and suggesting to add upper bounds on any dependencies with which compilation would give errors but for which lower versions are available within the erroneously specified ranges. Being optimistic, if typechecking succeeds, one might want to continue into compilation without further ado, so one might use Ghc directly, just watching for type-errors relating to packages with open ranges, so that Cabal could suggest to add upper bounds and to try again. Not a solution, but perhaps helpful, until Cabal does its own type-checking of interfaces. Claus PS. Is there a hackage administration mailing list, to which your message could have been copied to reach all package authors?

The other problem is that packages currently typically specify an optimistic upwardly open range rather than a pessimistic closed range. Cabal uses the heuristic of picking the highest version of each package that satisfies the version constraints.
One could try to use the Ghc Api to run Ghc in typecheck-only mode, trying the highest versions of dependencies, as given by Cabal's heuristic, and suggesting to add upper bounds on any dependencies with which compilation would give errors but for which lower versions are available within the erroneously specified ranges.
You might not even need to code your own Ghc Api client - it seems that
using something like this might do for just checking buildability without
generating files, running code, or displaying prompts:
ghc -ignore-dot-ghci

Duncan Coutts wrote:
I propose two solutions:
* Fix the dependency resolver * Add support in Cabal and Hackage for suggested version constraints
Simon PJ just came up with a suggestion for the second part. The idea is this: If we see a dependency like "base >= 3" with no upper limit, we should satisfy it with base-3 in preference to base-4, on the grounds that the package is much more likely to build with base-3. This seems to be a solution that works without any magic shims or "preference files" or anything else. Perhaps we could even go as far as saying "base >= 3.0" is equivalent to "base == 3.0.*". i.e. if you don't supply an upper bound, then we'll give you a conservative one. I wonder how much stuff would break if we did that. Cheers, Simon

If we see a dependency like "base >= 3" with no upper limit, we should satisfy it with base-3 in preference to base-4, on the grounds that the package is much more likely to build with base-3. This seems to be a solution that works without any magic shims or "preference files" or anything else.
That sounds reasonable.
Perhaps we could even go as far as saying "base >= 3.0" is equivalent to "base == 3.0.*". i.e. if you don't supply an upper bound, then we'll give you a conservative one. I wonder how much stuff would break if we did that.
All open-ended dependencies are lies.. Well, actually they are optimistic approximations (some programs will work with base 3 or base 4), and closed dependency ranges are pessimistic approximations (few programs need all of base 3). The problem is that there is no definite interface spec. At the moment, precise package versions are the only thing that Cabal knows about, on the understanding that package+version names (but not details) an API, and that the real API is some unidentified subset of the named API. In light of this, I've been wondering whether the complete list of precise package versions should really be part of the .cabal file: - they are little more than hints: I guess that a specific list of package+version names identifies a superset of the API my package needs, and if that guess turns out to be correct, I leave it in the .cabal file as the closest thing to an import API spec that Cabal allows me to write. - they can be inaccurate both upwards and downwards: my package rarely needs all of the import API named by the build-depends, and I'd often be happy if the import API for my package would be supplied by some other combination of packages (eg, base-4 + syb instead of base-3). - having precise build-depends means augmenting the package tarballs again and again, after testing with newer dependency versions. Wouldn't it make sense to keep only the initial hint in the .cabal file ("this is the precise combination of packages+versions that my package did build with"), and to let Cabal or Ghc or other tools figure out additional combinations that also allow the package to build successfully? These combinations could be tool-generated into a .cabal-configurations file, which could be stored outside the package tarball, and augmented whenever new dependency versions come out. Downloading the package and its successful configuration record would allow cabal-install to pick a combination that best matches locally installed packages. If a package doesn't have a successful configuration record, cabal-install can either try to generate one from the local packages, or insist on downloading the original configuration. If the former, cabal-install ought to report that back to hackage, to save itself work on the next installation. In any case, you wouldn't need to update all hackage package tarballs to add new dependency version numbers (just their .cabal-configurations records), and you could do that incrementally, when new dependency versions come out, and only once per package (instead of everytime someone tries to install it). Does that sound plausible? Claus

On Fri, 2008-10-03 at 14:27 +0100, Claus Reinke wrote:
Perhaps we could even go as far as saying "base >= 3.0" is equivalent to "base == 3.0.*". i.e. if you don't supply an upper bound, then we'll give you a conservative one. I wonder how much stuff would break if we did that.
All open-ended dependencies are lies..
Yes!
Well, actually they are optimistic approximations (some programs will work with base 3 or base 4), and closed dependency ranges are pessimistic approximations (few programs need all of base 3). The problem is that there is no definite interface spec.
Yes. Don and I are rather of the opinion that we need to look much more carefully at the package system. We're basically operating without the reassuring assistance of the type checker. There are some practical things we can do to make the current system work considerably better though. If we get the platform packages to opt into the package versioning policy and get cabal/hackage to warn about upwardly open version ranges then that'd go a long way to making things better. We should also write a tool using the ghc-api to compare apis of different versions of packages to inform people of changes and enforce the versioning policy for packages that have opted in. Having those interface specs around might also help a more robust package composition consistency checker or solver. Duncan

On Fri, Oct 03, 2008 at 09:54:12AM -0700, Duncan Coutts wrote:
better. We should also write a tool using the ghc-api to compare apis of different versions of packages to inform people of changes and enforce the versioning policy for packages that have opted in.
We should also use such a tool to check/generate "this was added in version n" to the haddock docs. Thanks Ian

Hello Simon, Friday, October 3, 2008, 12:55:34 PM, you wrote:
Perhaps we could even go as far as saying "base >= 3.0" is equivalent to "base == 3.0.*". i.e. if you don't supply an upper bound, then we'll give you a conservative one. I wonder how much stuff would break if we did that.
this looks reasonable for any package yjat follows versioning policy since changing major number means that anything in api may change you may use this as "theoretical" foundation for such trick :) of course in the future it will be great if people will start to use intervals with both high and low bounds -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

= must be deprecated or eliminated altogether, and the only reasonable
How can you _reasonably_ put in a high bound if future versions of a library (which might, or even most likely, work with yours) aren't know at the time the limit is put in place? Basically, if you want certainty, thing is (maybe multi-choice) ==, so you can communicate which _discrete_ versions you've tested with it. After all, even minor revisions contain bug fixes, and it is all-too-possible that you might rely on buggy behavior inadvertently. It would be awesome if packages could somehow advertise which older versions they _should_ backwards-compatible with. Cabal/GHC should still pick the closest available match to a version explicitly mentioned by your library (rather than the newest one), and report all risky (non-identical) choices in case of build failure. Reports like: "Possible reasons for failure: base package version requested was 3.2 but the closest match found was 4.1, which didn't advertise backwards compatibility; stm package version required was 2.1, but the closest match found was 2.3 which does advertise backwards compatibility but might be in error". That way people with their own library mixes can hope for the best, brace for the worst and get actionable "go install those requested versions, you dummy" info in case of failure. It would also be awesome if hackage could be a conduit for peer verification of library version compatibility. It would be awesome if cabal could be used to communicate to hackage a successful build with a previously-presumed-risky combination of libraries, so that hackage could update the script appropriately. I suppose you'd want more than a single report (say, three reports) before updating the package to claim compatibility with each specific library version, but that's in the realm of the details. And don't forget platform compatibility. A particular library could work with package X version 3 or 4 on Windows, but require version 4 on Linux. Maybe in version 4 of the package they substituted hardcoded ++ "\\" ++ with portable > or something silly-but-deadly like that. I guess my point is that, if you want cabal to make a dependable determination of whether a package mix will work well together, then you need sufficiently rich info, and simple version comparisons just won't cut it. JCAB Bulat Ziganshin wrote:
Hello Simon,
Friday, October 3, 2008, 12:55:34 PM, you wrote:
Perhaps we could even go as far as saying "base >= 3.0" is equivalent to "base == 3.0.*". i.e. if you don't supply an upper bound, then we'll give you a conservative one. I wonder how much stuff would break if we did that.
this looks reasonable for any package yjat follows versioning policy since changing major number means that anything in api may change
you may use this as "theoretical" foundation for such trick :) of course in the future it will be great if people will start to use intervals with both high and low bounds

On Fri, 2008-10-03 at 09:55 +0100, Simon Marlow wrote:
Duncan Coutts wrote:
I propose two solutions:
* Fix the dependency resolver * Add support in Cabal and Hackage for suggested version constraints
Simon PJ just came up with a suggestion for the second part. The idea is this:
If we see a dependency like "base >= 3" with no upper limit, we should satisfy it with base-3 in preference to base-4, on the grounds that the package is much more likely to build with base-3. This seems to be a solution that works without any magic shims or "preference files" or anything else.
The suggested version thing really turns out to be the same as saying we should satisfy base >= 3 using base-3 rather than base-4. We want that general mechanism anyway. So I think it's actually more general. We don't need to tell the resolver about base specially, it just extends an already existing notion of soft version preferences. The current resolver allows for soft preferences on the installed state, this just extends that to a general version preference. We want it anyway to better manage transitions like QC1 -> 2 or Parsec 2 -> 3.
Perhaps we could even go as far as saying "base >= 3.0" is equivalent to "base == 3.0.*". i.e. if you don't supply an upper bound, then we'll give you a conservative one. I wonder how much stuff would break if we did that.
The biggest problem is really just that the resolver has to deal with two instances of the same package in its solution. It was designed from the beginning with the assumption that it was accumulating version constraints per-package name (and that all constraints on a package version should be simultaneously satisfiable). We should however have packages declare if they have opted into the package versioning policy. Base would be one of them. We could then warn users when they are using bad version ranges in dependencies on such packages. It'd have to be a field in the .cabal file. Any suggestions for a good name? package-version-policy: Yarr! Duncan

On Oct 3, 2008, at 04:55 , Simon Marlow wrote:
Duncan Coutts wrote:
I propose two solutions: * Fix the dependency resolver * Add support in Cabal and Hackage for suggested version constraints
Simon PJ just came up with a suggestion for the second part. The idea is this:
If we see a dependency like "base >= 3" with no upper limit, we should satisfy it with base-3 in preference to base-4, on the grounds that the package is much more likely to build with base-3. This seems to be a solution that works without any magic shims or "preference files" or anything else.
Choose the lowest available version that satisfies all of the constraints? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Fri, 2008-10-03 at 12:53 -0400, Brandon S. Allbery KF8NH wrote:
If we see a dependency like "base >= 3" with no upper limit, we should satisfy it with base-3 in preference to base-4, on the grounds that the package is much more likely to build with base-3. This seems to be a solution that works without any magic shims or "preference files" or anything else.
Choose the lowest available version that satisfies all of the constraints?
Unfortunately this is the opposite of people normal (mostly reasonable) expectations. Perhaps you mean the highest revision of the lowest major version. Again this requires giving a semantics to the version numbers, which is just what the versioning policy does (for packages that have opted in). Duncan

Hello Brandon, Friday, October 3, 2008, 8:53:05 PM, you wrote:
Choose the lowest available version that satisfies all of the constraints?
and bugfixed versions will be never used :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2008 Oct 3, at 18:09, Bulat Ziganshin wrote:
Friday, October 3, 2008, 8:53:05 PM, you wrote:
Choose the lowest available version that satisfies all of the constraints?
and bugfixed versions will be never used :)
As Duncan said, I misspoke slightly. I was actually assuming something like the rules used for shared libraries: given a version X.Y.Z, X changes with API changes, Y with large non-API changes, Z with minor patches, and the resolution algorithm chooses the latest version with the same X (and, on some systems, tries to match Y as well), and older versions are never accepted. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Wed, 2008-10-01 at 16:36 -0700, Duncan Coutts wrote:
I propose two solutions:
* Fix the dependency resolver * Add support in Cabal and Hackage for suggested version constraints
So I'll aim to work on both issues this week and report back on how things are going.
Done! Four days and 15 patches later I can construct install plans for 710 packages from hackage using the darcs cabal-install and last nights ghc-6.10. (It would be more like 730 but I've not got gtk2hs built for 6.10, for ghc-6.8 it's 743 packages) The next step is to actually build everything and compare. We'll do this tomorrow and report results. There are three combinations we are interested in: * baseline: ghc-6.8 and Cabal-1.4 * new Cabal: ghc-6.8 and Cabal-1.6 * new ghc: ghc-6.10 and Cabal-1.6 So we'll try building all 700+ packages all three ways and compare the build reports. We'll report anything interesting that might indicate new ghc bugs. If all looks ok I'll also release Cabal-1.6. Duncan

On Mon, Oct 6, 2008 at 9:16 AM, Duncan Coutts
Done!
Four days and 15 patches later I can construct install plans for 710 packages from hackage using the darcs cabal-install and last nights ghc-6.10. (It would be more like 730 but I've not got gtk2hs built for 6.10, for ghc-6.8 it's 743 packages)
Is this included in the ghc 6.10 rc1? I tried: $ cabal install Diff Resolving dependencies... but it seems to remain stuck there. Thanks, JP.

On Thu, 2008-10-09 at 10:20 +0200, Jean-Philippe Bernardy wrote:
On Mon, Oct 6, 2008 at 9:16 AM, Duncan Coutts
wrote: Done!
Four days and 15 patches later I can construct install plans for 710 packages from hackage using the darcs cabal-install and last nights ghc-6.10. (It would be more like 730 but I've not got gtk2hs built for 6.10, for ghc-6.8 it's 743 packages)
Is this included in the ghc 6.10 rc1? I tried:
The cabal-install program is not included ghc at all. (ghc comes with the Cabal library.)
$ cabal install Diff Resolving dependencies...
but it seems to remain stuck there.
Right, you need the darcs version of cabal-install. Duncan
participants (9)
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Claus Reinke
-
Don Stewart
-
Duncan Coutts
-
Ian Lynagh
-
Jean-Philippe Bernardy
-
Juan Carlos Arevalo Baeza
-
Simon Marlow