[Freebsd-haskell] Howto deal with Cabal dependencies?

david fries djf at gmx.ch
Sun Mar 14 11:59:40 EDT 2010


Yes this cleared things a great deal, thanks! 

I wanted to write and let you know where I stand at the moment. I've
been searching the web and reading lots of mailing list posts and so on.
I've also visited the Debian Haskell[1] site to get some info. But I
haven't (yet) come up with a workable solution.

Indeed, it seems like updating core libraries is a really bad
idea(TM) :)

While reading the cabal manual, I discovered that you can hide installed
packages in with: ghc-pkg hide PACKAGENAME-VERSION. Hidden packages are
enclosed in parenthesis in the package list. This way ghc won't see it
when trying to compile a program. So you could hide all, but the latest
version of an installed library. However, I'm sure that this would be
the intended use of that feature

I'll keep on searching. 

regards,
dave

[1] http://wiki.debian.org/Haskell

On Wed, 2010-03-10 at 00:31 +0100, Gabor PALI wrote:
> Hey,
> 
> On 03/09/10 22:22, david fries wrote:
> > You both pointed out that installing ports which are already part of
> > lang/ghc may cause problems. However I don't see why. Take the
> > network module, for example.
> 
> Let me help you then.  I installed your port right from the PR [1],
> and let us 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 got this:
> 
> 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
> 
> 
> But that is a really ugly workaround, I think.
> 
> For your information, the GHC shipped with Haskell Platform (on
> Windows, at least) *does not* include network-2.2.1.2, only
> network-2.2.1.4, so there are no duplicate network packages installed.
> To achieve the same result with your approach (lang/ghc +
> "devel/hs-network2214"), we would need to fumble with the files that
> lang/ghc installed before.
> 
> Perhaps there could be some option in lang/ghc/Makefile to set whether
> we want to install GHC as part (actually SLAVE) of Haskell Platform or
> not, so we can replace the corresponding modules for sake of
> conformity to the specification. That might be a solution, and it
> would not even require a separate port or anything else.
> 
> 
> > A potential network-2.2.1.4 port would be installed by itself in
> > /usr/local/lib/network-2.2.1.4 and its haddock documentation is also
> > in a separate directory.
> 
> Well, your PR contains the port of network-2.2.1.7 :P
> 
> 
> > ghc-pkg list shows two different installed network versions, but GHC
> > & Cabal have been designed to handle multiple module versions.
> 
> Can it do that automatically so I was wrong above?
> 
> 
> > So I don't see what the problem is. Maybe someone could elaborate on
> > that a little bit more. So that I can come up with an acceptable
> > solution.
> 
> I hope now you see my concerns.  But I described a potential solution.
> 
> 
> > Frankly, the issue of version dependencies is pretty important to
> > me. The current happy go lucky way of just have the latest version
> of
> > a module in the portstree is insufficient. I'm sure I'm not the
> first
> > one to bump into this issue. Right? If I had my way, I would
> > explicitly put the version in the name suffix.
> 
> I agree on that, but can you give some examples on when it is better
> to have not the latest version in the ports tree (other than this HP
> issue)?
> 
> A problem could be that the ports tree cannot handle versions so
> elegantly as Cabal does (as far as I know): there is no way to specify
> an upper limit for the version of a dependency, i. e. x <= n, but I
> might be wrong.
> 
> 
> Hope that helps,
> :g
> 
> [1] http://www.freebsd.org/cgi/query-pr.cgi?pr=ports/143649
> 




More information about the FreeBSD-haskell mailing list