[arch-haskell] BSD guy needing help with haskell-platform

david fries djf at gmx.ch
Mon Mar 15 17:52:27 EDT 2010


Hi Archers,

I have been working on porting the Haskell-Platform to the FreeBSD
operating system for a while now and some issues have come up. I've come
here because I think Arch Linux has the best Haskell support among all
the Linux distros and I was hoping that I could learn from your
experience and maybe adopt some best practices too. I know this is way
off topic, but we *nix guys must stick together, right ;)

The haskell-platform has been released over a year ago and it still
isn't available on FreeBSD. So I decided to do it myself. However I've
run into problems. Let me begin by giving you an idea of the situation:

Our approach is very compiler-centric. We're still running on GHC-6.10.4
(6.12 is in the testing phase). Our ghc compiler package contains a
couple of "builtin" (i.e. not available as separate separate packages)
libraries that it requires. 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 I would port network-2.2.1.4 to FreeBSD and
then specify it as a dependency of the Platform port (Currently, the
plan is to make it a meta package). But then we would end up with two
(exposed) versions of the network library 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 above workaround ain't acceptable to the FreeBSD committers, so I
have to
come up with something better to get the Port into the official
repository.

The way things are setup, there is no way for me to replace the
network-2.2.1.2 library which is part of our ghc compiler package.

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 and
use that as a foundation for GHC-6.12. 

In your opinion, what would be the best approach to updating network?
BTW, I guess it would involve rebuilding all installed packages that had
previously been compiled with ghc?

Currently the attitude in our camp is that cabal packages that were
installed together with the compiler is simply are off limits and
shouldn't be tampered with. Do you have a similar policy?

I've been also reading the debian-haskell mailing list archives. It
seems they have been facing similar version discrepancies. They've dealt
with it by patching the setup to make cabal shut up [1]. 
What approach did you guys take?

I'm grateful for any comments

regards and TIA,
dave

[1] http://lists.debian.org/debian-haskell/2009/10/msg00007.html



More information about the arch-haskell mailing list