
Also "network" is where we want the network stuff to live, not
"network-socket".
On Wed, Feb 6, 2013 at 5:49 PM, Michael Snoyman
On Wed, Feb 6, 2013 at 11:22 AM, Herbert Valerio Riedel
wrote: Michael Snoyman
writes: [...]
An alternative would be to split the "network" package into "network-uri" and "network-socket". Users of network-uri would have to switch to network-socket as well. However, the types of "network" and "network-socket" would be incompatible unless the "network-socket" package re-exports the modules from "network" or vice versa.
E.g. could we put this into the "network" package:
{-# LANGUAGE PackageImports #-} module Network.Socket ( module S ) where
import qualified "network-socket" Network.Socket as S
?
[...]
Recently, we have a similar situation with http-conduit. Based on that, I'd recommend going for a conditional export situation.
* Release a new version of network (1.5) that does not include the Network.URI module. * Create a network-uri package that uses conditionals in the cabal file. * If it's compiled against network version 1.4 or earlier, it doesn't provide any modules. * If it's compiled against network 1.5 or later, it provides the Network.URI module.
This way, there's only ever one package which is providing Network.URI.
[...]
What's the actual downside with Henning's proposed package splitting method?
I.e., the new transitional `network` package wouldn't have any visible changes in its exports (and so wouldn't require any major version bump), but its (re-exported) implementation gets moved into two new packages, `network-uri` and `network-socket`.
So users of `network` which don't want to or can't switch yet to the new `network-{uri,socket}` packages can remain on `network` for the time being.
After an appropriate deprecation cycle, the `network` packages doesn't get updated anymore to support newer major package versions of `network-{uri,socket}` which may then start to break compatibility significantly at the type-level.
To me, this seems to avoid breaking the PVP contract, as well as avoiding requiring clients of `network` to introduce conditional-compilation directives. Moreover, it wouldn't require client packages to switch to new packages right away, while sharing the data types of the new `network-{socket,uri}` packages.
Am I overlooking something?
cheers, hvr
Well, that approach requires the creation of an extra package and ultimately deprecating the main package, forcing users to have to learn about a new package. I'd rather not have to rename a package just because I want to split off one piece of functionality to a separate package.
Michael
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
--
Gregory Collins