[Haskell-cafe] Re: Proposal: register a package asprovidingseveral API versions

Claus Reinke claus.reinke at talk21.com
Tue Oct 16 12:32:06 EDT 2007


>> are those tricks necessary in this specific case? couldn't we
>> have a list/range of versions in the version: field, and let cabal
>> handle the details?
> 
> I don't understand what you're proposing here.  Surely just writing
> 
> version: 1.0, 2.0
> 
> isn't enough - you need to say what the 1.0 and 2.0 APIs actually *are*, 
> and then wouldn't that require more syntax?  I don't yet see a good reason 
> to do this in a single .cabal file instead of two separate packages.  The 
> two-package way seems to require fewer extensions to Cabal.

yes, and no. cabal is currently not symmetric in this: providers
specify apis (at the level of exposed modules), clients only specify
api numbers as dependencies.

the idea was for the cabal file to specify a single provided api,
but to register that as sufficient for a list of dependency numbers.
so the package would implement the latest api, but could be used
by clients expecting either the old or the new api.

>> aside: what happens if we try to combine two modules M and N
>> that use the same api A, but provided by two different packages
>> P1 and P2? say, M was built when P1 was still around, but when
>> N was built, P2 had replaced P1, still supporting A, but not necessarily 
>> with the same internal representation as used in P1.
> 
> Not sure what you mean by "try to combine".  A concrete example?

lets see - how about this:

-- package P-1, Name: P, Version: 0.1
module A(L,f,g) where
newtype L a = L [a]
f  a (L as) = elem a as
g as = L as

-- package P-2, Name: P, Version: 0.2
module A(L,f,g) where
newtype L a = L (a->Bool)
f  a (L as) = as a
g as = L (`elem` as)

if i got this right, both P-1 and P-2 support the same api A, right
down to types. but while P-1's A and P-2's A are each internally
consistent, they can't be mixed. now, consider

module M where
import A
m = g [1,2,3]

module N where
import A
n :: Integer -> A.L Integer -> Bool
n = f

so, if i install P-1, then build M, then install P-2, then build N, 
wouldn't N pick up the "newer" P-2, while M would use the 
"older" P-1? and if so, what happens if we then add

module Main where
import M
import N
main = print (n 0 m)

i don't seem to be able to predict the result, without actually
trying it out. can you?-) i suspect it won't be pretty, though.

claus



More information about the Haskell-Cafe mailing list