[Haskell-cafe] Multiple versions of a cabal package Or what's the right way to update?

david fries djf at gmx.ch
Sun Mar 14 12:50:00 EDT 2010


Dear Caféistas

I desperately need your collective knowledge I have been working on
porting the haskell-platform to the FreeBSD operating system for a while
now and some versioning issues have come up. 

FreeBSD is still running on GHC-6.10.4 (6.12 is in the works). The ghc
package contains a couple of libraries that ghc is built against and
requires to run. For instance, network-2.2.1.2 is one of them. The
problem is that the Haskell Platform requires version 2.2.1.4. 
Under normal circumstances we would port network-2.2.1.4 to FreeBSD and
then specify it as a dependency of the Platform port. But then we end up
with two (exposed) versions of network installed on the system. 

For example, let's assume that I have the following Haskell source
(Networking.hs):

module Networking where

import Data.ByteString.Lazy
import Data.Maybe
import Network.HTTP
import Network.Stream
import Network.URI

getBinary :: String -> IO ByteString
getBinary url = do
  uri <- return $ fromJust $ parseURI url
  rsp <- simpleHTTP $ request uri
  getResponseBody rsp
    where
      request uri = Request
        { rqURI = uri
        , rqMethod = GET
        , rqHeaders = []
        , rqBody = empty }


When I try to compile it (`ghc --make Networking.hs`) I get the
following:

Networking.hs:12:30:
    Couldn't match expected type `network-2.2.1.2:Network.URI.URI'
           against inferred type `URI'
    In the first argument of `request', namely `uri'
    In the second argument of `($)', namely `request uri'
    In a stmt of a 'do' expression: rsp <- simpleHTTP $ request uri

However, the following thing could help:

$ ghc --make Networking.hs -package network-2.2.1.2

The workaround ain't acceptable to the FreeBSD committers, so I have to
come up with something better...

In a perfect world, I'd be able to install the required HP dependencies
without tripping ghc up. Then we could switch over to the platform as a
foundation of GHC-6.12.

I have lots of questions. Is it smart to have multiple installed
versions of the same library? Up until now, we could avoid such
situations. 
What would be the correct approach to updating network? I guess it would
involve rebuilding all installed packages that had previously been
compiled with ghc? Though I hope not - our package management system
could pull that off if necessary.
If it is perhaps a bad idea to update certain "core" libraries, is there
a way to declare them as such in the cabal file?


regards and TIA,
dave



More information about the Haskell-Cafe mailing list