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

Simon Marlow simonmarhaskell at gmail.com
Wed Oct 17 05:13:30 EDT 2007


Claus Reinke wrote:

> 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.

I don't see how that could work.  If the old API is compatible with the new 
API, then they might as well have the same version number, so you don't 
need this.  The only way that two APIs can be completely compatible is if 
they are identical.

A client of an API can be tolerant to certain changes in the API, but that 
is something that the client knows about, not the provider.  e.g. if the 
client knows that they use explicit import lists everywhere, then they can 
be tolerant of additions to the API, and can specify that in the dependency.

>>> 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)

You'll get a type error - try it.  The big change in GHC 6.6 was to allow 
this kind of construction to occur safely.  P-1:A.L is not the same type as 
P-2:A.L, they don't unify.

> 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.

Sure.  We have a test case in our testsuite for this very eventuality, see

http://darcs.haskell.org/testsuite/tests/ghc-regress/typecheck/bug1465

that particular test case arose because someone discovered that the type 
error you get is a bit cryptic (it's better in 6.8.1).

Cheers,
	Simon


More information about the Haskell-Cafe mailing list