Hi Paolo, Paolo Giarrusso wrote:
cabal install p1 p2 is supposed to find a single consistent install plan for p1 and p2 and the transitive dependencies of either of them. This is useful if you plan to use p1 and p2 in a single project.
Ahah! Then it's a feature. The need for consistency stems from a bug: in a tracker entry you linked to, http://hackage.haskell.org/trac/hackage/ticket/704, duncan argues that "we also want to be able to do things like linking multiple versions of a Haskell package into a single application".
I think this is a slightly different matter. Consider a package pair, which defines an abstract datatype of pairs in version 1: module Pair (Pair, fst, snd, pair) where data Pair a b = Pair a b fst (Pair a b) = a snd (Pair a b) = b pair a b = Pair a b In version 2 of pair, the internal representation of the datatype is changed: module Pair (Pair, fst, snd, pair) where data Pair a b = Pair b a fst (Pair b a) = a snd (Pair b a) = b pair a b = Pair b a Now we have a package foo which depends on pair-1: module Foo (foo) where import Pair foo = pair 42 '?' And a package bar which depends on pair-2: module Bar (bar) where import Pair bar = fst Now, we write a program which uses both foo and bar: module Program where import Foo import Bar main = print $ bar $ foo Even with the technical ability to link all of foo, bar, pair-1 and pair-2 together, I don't see how this program could be reasonably compiled. Therefore, I think that the notion of consistent install plans is relevant semantically, not just to work around some deficiency in the linking system. Tillmann