Re: [Haskell-cafe] Hackage is down?

2012-08-11 Thread Henk-Jan van Tuyl
On Sat, 11 Aug 2012 21:10:24 +0200, Justin Greene  
 wrote:


Anyone have a download link for the haskell platform for windows?  I  
can't

find one with hackage down.



This link depends on the OS you are using; I found the Haskell Platform  
page in the Web Archive[0]. The downloads are at the Galois site[1].


Regards,
Henk-Jan van Tuyl


[0]  
http://web.archive.org/web/20110716180206/http://hackage.haskell.org/platform/

[1] http://lambda.galois.com/hp-tmp/2011.2.0.1/


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-11 Thread Alexander Solla
On Sat, Aug 11, 2012 at 12:01 PM, Antoine Latter  wrote:

> It should be pretty easy to write an adapter function of type "String ->
> (Show a => a)".
>

Not with that type.  Give it a try.

Hint:  what is the extension of the type variable 'a'?  What do you know
about it?  How would you use that to write the function?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hackage is down?

2012-08-11 Thread Justin Greene
Anyone have a download link for the haskell platform for windows?  I can't
find one with hackage down.

On Sat, Aug 11, 2012 at 1:39 PM, Thomas DuBuisson <
thomas.dubuis...@gmail.com> wrote:

> It will be down most of today - we are switching over to a new network
> connection.
>
> On Sat, Aug 11, 2012 at 11:31 AM, hanjoosten  wrote:
> > Hi,
> >
> > Hackage seems to be down. Is there anyone out here who knows how to get
> it
> > online again?
> >
> > Thanks!
> >
> >
> >
> > --
> > View this message in context:
> http://haskell.1045720.n5.nabble.com/Hackage-is-down-tp5715912.html
> > Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-11 Thread Antoine Latter
It should be pretty easy to write an adapter function of type "String ->
(Show a => a)".
On Aug 11, 2012 12:34 PM, "Patrick Palka"  wrote:

> On Sat, Aug 11, 2012 at 4:14 AM,  wrote:
>
>>
>> I'd like to point out that the only operation we can do on the first
>> argument of MkFoo is to show to it. This is all we can ever do:
>> we have no idea of its type but we know we can show it and get a
>> String.
>>
>
> That's not all you can do: you can also pass the first argument of MkFoo
> to a function that expects a Show a => a argument, like the function
> 'print'. Can you do that with just a String (that represents show x for
> some x)?
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hackage is down?

2012-08-11 Thread Johan Tibell
+Malcom

On Sat, Aug 11, 2012 at 11:31 AM, hanjoosten  wrote:
> Hi,
>
> Hackage seems to be down. Is there anyone out here who knows how to get it
> online again?
>
> Thanks!
>
>
>
> --
> View this message in context: 
> http://haskell.1045720.n5.nabble.com/Hackage-is-down-tp5715912.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hackage is down?

2012-08-11 Thread Thomas DuBuisson
It will be down most of today - we are switching over to a new network
connection.

On Sat, Aug 11, 2012 at 11:31 AM, hanjoosten  wrote:
> Hi,
>
> Hackage seems to be down. Is there anyone out here who knows how to get it
> online again?
>
> Thanks!
>
>
>
> --
> View this message in context: 
> http://haskell.1045720.n5.nabble.com/Hackage-is-down-tp5715912.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Hackage is down?

2012-08-11 Thread hanjoosten
Hi,

Hackage seems to be down. Is there anyone out here who knows how to get it
online again?

Thanks!



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Hackage-is-down-tp5715912.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-11 Thread Patrick Palka
On Sat, Aug 11, 2012 at 4:14 AM,  wrote:

>
> I'd like to point out that the only operation we can do on the first
> argument of MkFoo is to show to it. This is all we can ever do:
> we have no idea of its type but we know we can show it and get a
> String.
>

That's not all you can do: you can also pass the first argument of MkFoo to
a function that expects a Show a => a argument, like the function 'print'.
Can you do that with just a String (that represents show x for some x)?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-11 Thread David Feuer
Has anyone used existential types to represent items on a schedule in a
scheduled lazy data structure?
On Aug 11, 2012 4:15 AM,  wrote:

>
> > data A = A deriving Show
> > data B = B deriving Show
> > data C = C deriving Show
> >
> > data Foo = forall a. Show a => MkFoo a (Int -> Bool)
> >
> > instance Show Foo where
> >show (MkFoo a f) = show a
>
> I'd like to point out that the only operation we can do on the first
> argument of MkFoo is to show to it. This is all we can ever do:
> we have no idea of its type but we know we can show it and get a
> String. Why not to apply show to start with (it won't be evaluated
> until required anyway)? Therefore, the data type Foo above is in all
> respects equivalent to
>
> > data Foo = MkFoo String (Int -> Bool)
>
> and no existentials are ever needed. The following article explains
> elimination of existentials in more detail, touching upon the original
> problem, of bringing different types into union.
>
> http://okmij.org/ftp/Computation/Existentials.html
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fwd: hGetContents Illegal byte sequence / ghc-pkg

2012-08-11 Thread Benjamin Edwards
Responding to the list..

-- Forwarded message --
From: Benjamin Edwards 
Date: 11 August 2012 17:37
Subject: Re: [Haskell-cafe] hGetContents Illegal byte sequence / ghc-pkg
To: David McBride 


Thank you Gents,

Most useful. One thing that had escaped me is that of course, even if
hGetContents and friends are respecting *my* locale, I have a binary distro
and the package database probably isn't in my locale. I will try and find
that.

Thanks,
 Ben


On 11 August 2012 15:26, David McBride  wrote:

> I had this same problem a couple weeks ago when trying to install
> virthualenv and I don't really understand it got into a bad state, but the
> way I solved it was by fixing the locale settings on my gentoo machine so
> that I'm using UTF8.  That just involved a few changes in /etc and then the
> problem went away.
>
> On Sat, Aug 11, 2012 at 7:13 AM, Benjamin Edwards 
> wrote:
>
>> Hello café,
>>
>> I have a program that is crashing, and I have no idea why:
>>
>> module Main
>>   where
>>
>> import System.Process (readProcessWithExitCode)
>>
>>
>> main :: IO ()
>> main = do _ <- readProcessWithExitCode "ghc-pkg" ["describe", "hoopl"] ""
>>   putStrLn "Should never get here"
>>
>> this is using the process package from hackage. The program crashes with
>>
>> minimal-test: fd:5: hGetContents: invalid argument (invalid byte sequence)
>> minimal-test: thread blocked indefinitely in an MVar operation
>>
>> inspecting the source of readProcessWithExitCode yields an obvious
>> explanation to the MVar problem, but I don't understand why hGetContents is
>> so offended.
>>
>> For the lazy it is defined as follows:
>>
>> readProcessWithExitCode
>> :: FilePath -- ^ command to run
>> -> [String] -- ^ any arguments
>> -> String   -- ^ standard input
>> -> IO (ExitCode,String,String) -- ^ exitcode, stdout, stderr
>> readProcessWithExitCode cmd args input = do
>> (Just inh, Just outh, Just errh, pid) <-
>> createProcess (proc cmd args){ std_in  = CreatePipe,
>>std_out = CreatePipe,
>>std_err = CreatePipe }
>>
>> outMVar <- newEmptyMVar
>>
>> -- fork off a thread to start consuming stdout
>> out  <- hGetContents outh
>> _ <- forkIO $ C.evaluate (length out) >> putMVar outMVar ()
>>
>> -- fork off a thread to start consuming stderr
>> err  <- hGetContents errh
>> _ <- forkIO $ C.evaluate (length err) >> putMVar outMVar ()
>>
>> -- now write and flush any input
>> when (not (null input)) $ do hPutStr inh input; hFlush inh
>> hClose inh -- done with stdin
>>
>> -- wait on the output
>> takeMVar outMVar
>> takeMVar outMVar
>> hClose outh
>> hClose errh
>>
>> -- wait on the process
>> ex <- waitForProcess pid
>>
>> return (ex, out, err)
>>
>> Now having looked at the source of ghc-pkg it is dumping it's output
>> using putStr and friends, so that should be using my local encoding on the
>> system, right? and so should hGetContents in my program..?
>>
>> Now, for the curious: the reason I care is that this problem has
>> effectively prevented me from using virthualenv. Sadness and woe.
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hGetContents Illegal byte sequence / ghc-pkg

2012-08-11 Thread David McBride
I had this same problem a couple weeks ago when trying to install
virthualenv and I don't really understand it got into a bad state, but the
way I solved it was by fixing the locale settings on my gentoo machine so
that I'm using UTF8.  That just involved a few changes in /etc and then the
problem went away.

On Sat, Aug 11, 2012 at 7:13 AM, Benjamin Edwards wrote:

> Hello café,
>
> I have a program that is crashing, and I have no idea why:
>
> module Main
>   where
>
> import System.Process (readProcessWithExitCode)
>
>
> main :: IO ()
> main = do _ <- readProcessWithExitCode "ghc-pkg" ["describe", "hoopl"] ""
>   putStrLn "Should never get here"
>
> this is using the process package from hackage. The program crashes with
>
> minimal-test: fd:5: hGetContents: invalid argument (invalid byte sequence)
> minimal-test: thread blocked indefinitely in an MVar operation
>
> inspecting the source of readProcessWithExitCode yields an obvious
> explanation to the MVar problem, but I don't understand why hGetContents is
> so offended.
>
> For the lazy it is defined as follows:
>
> readProcessWithExitCode
> :: FilePath -- ^ command to run
> -> [String] -- ^ any arguments
> -> String   -- ^ standard input
> -> IO (ExitCode,String,String) -- ^ exitcode, stdout, stderr
> readProcessWithExitCode cmd args input = do
> (Just inh, Just outh, Just errh, pid) <-
> createProcess (proc cmd args){ std_in  = CreatePipe,
>std_out = CreatePipe,
>std_err = CreatePipe }
>
> outMVar <- newEmptyMVar
>
> -- fork off a thread to start consuming stdout
> out  <- hGetContents outh
> _ <- forkIO $ C.evaluate (length out) >> putMVar outMVar ()
>
> -- fork off a thread to start consuming stderr
> err  <- hGetContents errh
> _ <- forkIO $ C.evaluate (length err) >> putMVar outMVar ()
>
> -- now write and flush any input
> when (not (null input)) $ do hPutStr inh input; hFlush inh
> hClose inh -- done with stdin
>
> -- wait on the output
> takeMVar outMVar
> takeMVar outMVar
> hClose outh
> hClose errh
>
> -- wait on the process
> ex <- waitForProcess pid
>
> return (ex, out, err)
>
> Now having looked at the source of ghc-pkg it is dumping it's output using
> putStr and friends, so that should be using my local encoding on the
> system, right? and so should hGetContents in my program..?
>
> Now, for the curious: the reason I care is that this problem has
> effectively prevented me from using virthualenv. Sadness and woe.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hGetContents Illegal byte sequence / ghc-pkg

2012-08-11 Thread Brandon Allbery
On Sat, Aug 11, 2012 at 7:13 AM, Benjamin Edwards wrote:

> inspecting the source of readProcessWithExitCode yields an obvious
> explanation to the MVar problem, but I don't understand why hGetContents is
> so offended.
>

I think last time I looked into this there was no normalization of
package.conf data; if it was read in in a particular encoding, it was
stored in that encoding and you can get an exception trying to dump it in a
different encoding.  Certainly I have found ISO8859-1 encoded text in my
package.conf.d/* files, when I would expect (and was configured for) UTF-8.
 This also suggests that ISO8859-1 text in a *.cabal file would remain
ISO8859-1 in the resulting package.conf file even if UTF-8 encoding was
active at the time.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hGetContents Illegal byte sequence / ghc-pkg

2012-08-11 Thread Brent Yorgey
On Sat, Aug 11, 2012 at 12:13:45PM +0100, Benjamin Edwards wrote:
> Hello café,
> 
> I have a program that is crashing, and I have no idea why:
> 
> module Main
>   where
> 
> import System.Process (readProcessWithExitCode)
> 
> 
> main :: IO ()
> main = do _ <- readProcessWithExitCode "ghc-pkg" ["describe", "hoopl"] ""
>   putStrLn "Should never get here"
> 
> this is using the process package from hackage. The program crashes with
> 
> minimal-test: fd:5: hGetContents: invalid argument (invalid byte sequence)
> minimal-test: thread blocked indefinitely in an MVar operation
> 
> inspecting the source of readProcessWithExitCode yields an obvious
> explanation to the MVar problem, but I don't understand why hGetContents is
> so offended.

The 'invalid argument' error from hGetContents indicates that a wrong
encoding is being assumed.  I don't know enough about how
putStr/hGetContents decide on an encoding, but in any case it works
for me (that is, it prints "Should never get here").  The likely
sticking point is that one of the authors of hoopl, João Dias, has a
name which contains U+00E3: LATIN SMALL LETTER A WITH TILDE.

Try doing  

  ghc-pkg describe hoopl > hoopl.txt
  file hoopl.txt

to get an indication of what encoding is being used, or manually take
a look at the bytes being generated using

  ghc-pkg describe hoopl | hexdump -C

I don't know what the solution is but at least this should give some
additional information.

-Brent

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] hGetContents Illegal byte sequence / ghc-pkg

2012-08-11 Thread Benjamin Edwards
Hello café,

I have a program that is crashing, and I have no idea why:

module Main
  where

import System.Process (readProcessWithExitCode)


main :: IO ()
main = do _ <- readProcessWithExitCode "ghc-pkg" ["describe", "hoopl"] ""
  putStrLn "Should never get here"

this is using the process package from hackage. The program crashes with

minimal-test: fd:5: hGetContents: invalid argument (invalid byte sequence)
minimal-test: thread blocked indefinitely in an MVar operation

inspecting the source of readProcessWithExitCode yields an obvious
explanation to the MVar problem, but I don't understand why hGetContents is
so offended.

For the lazy it is defined as follows:

readProcessWithExitCode
:: FilePath -- ^ command to run
-> [String] -- ^ any arguments
-> String   -- ^ standard input
-> IO (ExitCode,String,String) -- ^ exitcode, stdout, stderr
readProcessWithExitCode cmd args input = do
(Just inh, Just outh, Just errh, pid) <-
createProcess (proc cmd args){ std_in  = CreatePipe,
   std_out = CreatePipe,
   std_err = CreatePipe }

outMVar <- newEmptyMVar

-- fork off a thread to start consuming stdout
out  <- hGetContents outh
_ <- forkIO $ C.evaluate (length out) >> putMVar outMVar ()

-- fork off a thread to start consuming stderr
err  <- hGetContents errh
_ <- forkIO $ C.evaluate (length err) >> putMVar outMVar ()

-- now write and flush any input
when (not (null input)) $ do hPutStr inh input; hFlush inh
hClose inh -- done with stdin

-- wait on the output
takeMVar outMVar
takeMVar outMVar
hClose outh
hClose errh

-- wait on the process
ex <- waitForProcess pid

return (ex, out, err)

Now having looked at the source of ghc-pkg it is dumping it's output using
putStr and friends, so that should be using my local encoding on the
system, right? and so should hGetContents in my program..?

Now, for the curious: the reason I care is that this problem has
effectively prevented me from using virthualenv. Sadness and woe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-11 Thread oleg

> data A = A deriving Show
> data B = B deriving Show
> data C = C deriving Show
>
> data Foo = forall a. Show a => MkFoo a (Int -> Bool)
>
> instance Show Foo where
>show (MkFoo a f) = show a

I'd like to point out that the only operation we can do on the first
argument of MkFoo is to show to it. This is all we can ever do:
we have no idea of its type but we know we can show it and get a
String. Why not to apply show to start with (it won't be evaluated
until required anyway)? Therefore, the data type Foo above is in all
respects equivalent to

> data Foo = MkFoo String (Int -> Bool)

and no existentials are ever needed. The following article explains
elimination of existentials in more detail, touching upon the original
problem, of bringing different types into union.

http://okmij.org/ftp/Computation/Existentials.html



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Data and OverlappingInstances

2012-08-11 Thread oleg

Timo von Holtz wrote:

> class Test a where
>   foo :: Monad m => m a
>
> instance Num a => Test a where
>   foo = return 1
>
> instance Test Int where
>   foo = return 2
>
> test constr = fromConstrM foo constr

I'm afraid the type checker is right. From the type of fromConstrM
  fromConstrM :: forall m a. (Monad m, Data a) => (forall d. Data d => m d)
-> Constr -> m a

we see its first argument has the type
(forall d. Data d => m d)

If instead it had the type 
(forall d. Test d => m d)

we would have no problem. As it is, when you pass 'foo' of the type
(Test d, Monad m) => m d
as the first argument of fromConstrM, which only assures the Data d
constraint on 'd' and _nothing_ else, the compiler checks if it can get
rid of (discharge) the constraint Test d. That is, the compiler is
forced to choose an instance for Test. But there is not information to
do that.

Overlapping here is irrelevant. If you had non-overlapping instances

> class Test a where
>   foo :: Monad m => m a
>
> instance Num a => Test [a] where
>   foo = return [1]
>
> instance Test Int where
>   foo = return 2
>
> test constr = fromConstrM foo constr

'test' still causes the problem. The error message now describes the
real problem:

Could not deduce (Test d) arising from a use of `foo'
from the context (Monad m, Data a)
  bound by the inferred type of
   test :: (Monad m, Data a) => Constr -> m a
  at /tmp/d.hs:16:1-36
or from (Data d)
  bound by a type expected by the context: Data d => m d
  at /tmp/d.hs:16:15-36
Possible fix:
  add (Test d) to the context of
a type expected by the context: Data d => m d
or the inferred type of test :: (Monad m, Data a) => Constr -> m a
In the first argument of `fromConstrM', namely `foo'

and it recommends the right fix: change the type of fromConstrM to be

  fromConstrM :: forall m a. (Monad m, Data a) => 
( forall d. (Test d, Data d) => m d) -> Constr -> m a

That will solve the problem. Alas, fromConstrM is a library function
and we are not at liberty to change its type.

> Right now I use a "case (typeOf x) of" kind of construct
That is precisely the right way to use Data. SYB provides good
combinators for building functions (generic producers) of that sort.
But you never need unSafeCoerce: gcast is sufficient.





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CRIP: the Curiously Reoccuring Instance Pattern

2012-08-11 Thread oleg

Anthony Clayden wrote:
> So three questions in light of the approach of abandoning FunDeps and
> therefore not getting interference with overlapping:
> A. Does TTypeable need to be so complicated?
> B. Is TTypeable needed at all?
> C. Does the 'simplistic' version of type equality testing suffer possible
> IncoherentInstances?

It is important to keep in mind that Type Families (and Data Families)
are _strictly_ more expressive than Functional dependencies. For
example, there does not seem to be a way to achieve the injectivity of
Leibniz equality
http://okmij.org/ftp/Computation/extra-polymorphism.html#injectivity
without type families (and relaying instead on functional
dependencies, implemented with TypeCast or directly).

I'd like to be able to write
data Foo a = Foo (SeqT a)
where 
SeqT Bool = Integer
SeqT a= [a]  otherwise
(A sequence of Booleans is often better represented as an Integer). A
more practical example is
http://okmij.org/ftp/Haskell/GMapSpec.hs
http://okmij.org/ftp/Haskell/TTypeable/GMapSpecT.hs

It is possible to sort of combine overlapping with associated types,
but is quite ungainly. It is not possible to have overlapping
associated types _at present_. Therefore, at present, TTYpeable is
necessary and it has to be implemented as it is.

You point out New Axioms. They will change things. I have to repeat my
position however, which I have already stated several times. TTypeable
needs no new features from the language and it is available now. There
is no problem of figuring out how TTypeable interacts with existing
features of Haskell since TTypeable is implemented with what we
already have. New Axioms add to the burden of checking how this new
feature interacts with others. There have been many examples when one
feature, excellent by itself, badly interacts with others. (I recall
GADT and irrefutable pattern matching.)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe