Proposal: splitting the network package

Michael Snoyman michael at snoyman.com
Thu Jan 31 13:22:57 CET 2013


On Thu, Jan 31, 2013 at 12:28 PM, Henning Thielemann <
lemming at henning-thielemann.de> wrote:

>
> On Thu, 31 Jan 2013, Thomas Schilling wrote:
>
>  I don't think this would work. If "network" still contains a module
>> Network.URI and a package adds a dependency on "network-uri" which
>> also exports a module Network.URI, then you would have to specify the
>> package name in your import, i.e.:
>>
>>  import "network-uri" Network.URI
>>
>> Then, once Network.URI is removed from "network", users have to edit
>> their sources again to remove the explicit package import. I think the
>> only reasonable way to handle things is to use flags in a .cabal file,
>> i.e., the same way we had to deal with base-3 => base-4 transition
>> (which was very annoying).
>>
>
> 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
>
> ?
>
> Interestingly, the GHC documentation uses Network.Socket for explaining
> the PackageImports extension.
>
>
> ______________________________**_________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/**mailman/listinfo/libraries<http://www.haskell.org/mailman/listinfo/libraries>
>


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.

Note: I think there might be a requirement that a library section always
have at least one exported module. If so, I suppose network-uri should
always export some extra package as well, perhaps Network.URI.Temp which
contains everything in Network.URI.

Michael
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20130131/3db03a7e/attachment.htm>


More information about the Libraries mailing list