Re: Bang Patterns

2014-04-02 Thread Dan Doel
Filed. Bug #8952.


On Wed, Apr 2, 2014 at 3:41 PM, wren romano wrote:

> On Tue, Apr 1, 2014 at 3:02 PM, Dan Doel  wrote:
> > Specifically, consider:
> >
> > case Nothing of
> >   !(~(Just x)) -> 5
> >   Nothing -> 12
> >
> > Now, the way I'd expect this to work, and how I think the spec says it
> > works, is that my Nothing is evaluated, and then the irrefutable ~(Just
> x)
> > matches Nothing, giving a result of 5. In fact, GHC warns about
> overlapping
> > patterns for this.
>
> It's sensible to give an overlap warning --that is, assuming we don't
> want overlap to be an error-- since the irrefutable pattern matches
> everything, and adding bangs doesn't change what values are matched
> (it only changes whether we diverge or not).
>
> However, I have no idea how top-level bang in case-expressions is
> supposed to be interpreted. If anything, it should be ignored since we
> must already force the scrutinee to WHNF before matching *any* of the
> clauses of a case-expression. However, I thought bangs were restricted
> to (1) immediately before variables, and (2) for top-level use in
> let/where clauses...
>
> In any case, following the standard desugaring of the specs:
>
> case Nothing of !(~(Just x)) -> 5 ; Nothing -> 12
>
> === { next to last box of
> <
> http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html
> >,
> the proposed clause (t) for section 3.17.3, figure 4 }
>
> Nothing `seq` case Nothing of ~(Just x) -> 5 ; Nothing -> 12
>
> === { Haskell Report, section 3.17.3, figure 3, clause (d) }
>
> Nothing `seq` (\x -> 5) (case Nothing of Just x -> x)
>
> Which most definitely does not evaluate to 12. Either the specs are
> wrong (dubious) or the implementation is. File a bug report.
>
> --
> Live well,
> ~wren
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bang Patterns

2014-04-02 Thread wren romano
On Tue, Apr 1, 2014 at 3:02 PM, Dan Doel  wrote:
> Specifically, consider:
>
> case Nothing of
>   !(~(Just x)) -> 5
>   Nothing -> 12
>
> Now, the way I'd expect this to work, and how I think the spec says it
> works, is that my Nothing is evaluated, and then the irrefutable ~(Just x)
> matches Nothing, giving a result of 5. In fact, GHC warns about overlapping
> patterns for this.

It's sensible to give an overlap warning --that is, assuming we don't
want overlap to be an error-- since the irrefutable pattern matches
everything, and adding bangs doesn't change what values are matched
(it only changes whether we diverge or not).

However, I have no idea how top-level bang in case-expressions is
supposed to be interpreted. If anything, it should be ignored since we
must already force the scrutinee to WHNF before matching *any* of the
clauses of a case-expression. However, I thought bangs were restricted
to (1) immediately before variables, and (2) for top-level use in
let/where clauses...

In any case, following the standard desugaring of the specs:

case Nothing of !(~(Just x)) -> 5 ; Nothing -> 12

=== { next to last box of
,
the proposed clause (t) for section 3.17.3, figure 4 }

Nothing `seq` case Nothing of ~(Just x) -> 5 ; Nothing -> 12

=== { Haskell Report, section 3.17.3, figure 3, clause (d) }

Nothing `seq` (\x -> 5) (case Nothing of Just x -> x)

Which most definitely does not evaluate to 12. Either the specs are
wrong (dubious) or the implementation is. File a bug report.

-- 
Live well,
~wren
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Bang Patterns

2014-04-01 Thread Dan Doel
Greetings,

I've been thinking about bang patterns as part of implementing our own
Haskell-like compiler here, and have been testing out GHC's implementation
to see how it works. I've come to one case that seems like it doesn't work
how I think it should, or how it is described, and wanted to ask about it.

Specifically, consider:

case Nothing of
  !(~(Just x)) -> 5
  Nothing -> 12

Now, the way I'd expect this to work, and how I think the spec says it
works, is that my Nothing is evaluated, and then the irrefutable ~(Just x)
matches Nothing, giving a result of 5. In fact, GHC warns about overlapping
patterns for this.

However, this actually evaluates to 12, meaning that !(~p) appears to
cancel out and be equivalent to p. It seems to me this might be a side
effect of the logic used to implement 'let !p = ...', but I'm not certain.

So, my question is whether this is intentional. If it is, then the bang
patterns description should probably mention it, since it's subtly
different than the rest of the specification. Also the warning should be
removed, because there is no overlapping in the above case statement. If it
is unintentional, we should probably decide either to make it intentional
(and perform the above changes), or to change the implementation. :)

Cheers,
-- Dan
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Suggestion for bang patterns documentation

2009-02-27 Thread Christian Maeder
Simon Peyton-Jones wrote:
> | 
> | The let-binding can be recursive. However, it is much more common for
> | the let-binding to be non-recursive, in which case the following law
> | holds: (let !p = rhs in body)  is equivalent to (case rhs of !p -> body)
> | 
> |
> | Shouldn't the bang be removed in the final case pattern?
> 
> No.  If p was a simple variable, then
> case rhs of x -> body
> is non-strict in Haskell, but should be strict here.

Thanks for pointing this out. But the case with a simple variable (and
no distinction) is special anyway (sort of a monomorphic let binding).

> | P.S. It should be mentioned that ~ and ! only make sense for single
> | variant data types (like tuples)
> 
> That isn't true.  Both are useful for multi-variant types

Right, a non-empty list should behave like a pair as long as I don't
want to know the variant beforehand and thereby forcing evaluation anyway.

Cheers Christian

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Suggestion for bang patterns documentation

2009-02-27 Thread Simon Peyton-Jones
| 
| The let-binding can be recursive. However, it is much more common for
| the let-binding to be non-recursive, in which case the following law
| holds: (let !p = rhs in body)  is equivalent to (case rhs of !p -> body)
| 
|
| Shouldn't the bang be removed in the final case pattern?

No.  If p was a simple variable, then
case rhs of x -> body
is non-strict in Haskell, but should be strict here.

| P.S. It should be mentioned that ~ and ! only make sense for single
| variant data types (like tuples)

That isn't true.  Both are useful for multi-variant types

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Suggestion for bang patterns documentation

2009-02-27 Thread Christian Maeder
Brian Bloniarz wrote:
> I got confused by the GHC documentation recently, I was wondering how
> it could be improved. From:
> http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html


The let-binding can be recursive. However, it is much more common for
the let-binding to be non-recursive, in which case the following law
holds: (let !p = rhs in body)  is equivalent to (case rhs of !p -> body)


Shouldn't the bang be removed in the final case pattern?

Furthermore with existential types the let binding is not supported:

 data E = forall a . Show a => E a

 f :: E -> String
 f x = case x of E a -> show a

f works, but g

 g :: E -> String
 g x = let !(E a) = x in show a

fails (with or without the bang):

My brain just exploded.
I can't handle pattern bindings for existentially-quantified
constructors.
Instead, use a case-expression, or do-notation, to unpack the
constructor.
In the binding group for
!(E a)
In a pattern binding: !(E a) = x
In the expression: let !(E a) = x in show a
In the definition of `g': g x = let !(E a) = x in show a

Cheers Christian

P.S. It should be mentioned that ~ and ! only make sense for single
variant data types (like tuples)

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Suggestion for bang patterns documentation

2009-02-27 Thread Christian Maeder
Brian Bloniarz wrote:
> I got confused by the GHC documentation recently, I was wondering how
> it could be improved. From:
> http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html

Seeing the rule
 pat ::= !pat

you'll probably want to avoid patterns like: "!!pat", "! ! pat", or "~ !
~ pat".

Even the current http://www.haskell.org/onlinelibrary/exps.html#sect3.17.1

  apat -> ~ apat

allows "~ ~x". (Note the space!) So maybe a separate non-terminal "bpat"
should be used with:

 bpat -> [~|!] apat

(and bpat used within pat). You may also want to exclude "v@ ~(...)" in
favor of "~v@(...)".

>> A bang only really has an effect if it precedes a variable or wild-card 
>> pattern:
>> f3 !(x,y) = [x,y]
>> f4 (x,y)  = [x,y]
>> Here, f3 and f4 are identical; putting a bang before a pattern that
>> forces evaluation anyway does nothing.

Maybe the duality (if it is one) should be added that an irrefutable
pattern above would make a difference but not within the let below.

> The first sentence is true, but only in settings where the pattern is being
> evaluated eagerly -- the bang in:
>> f3 a = let !(x,y) = a in [1,x,y]
>> f4 a = let (x,y) = a in [1,x,y]
> has an effect.

Cheers Christian

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Suggestion for bang patterns documentation

2009-02-27 Thread Simon Peyton-Jones
good idea. done

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Brian Bloniarz
| Sent: 27 February 2009 03:56
| To: glasgow-haskell-users@haskell.org
| Subject: Suggestion for bang patterns documentation
|
|
| I got confused by the GHC documentation recently, I was wondering how
| it could be improved. From:
| http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html
|
| > A bang only really has an effect if it precedes a variable or wild-card 
pattern:
| > f3 !(x,y) = [x,y]
| > f4 (x,y)  = [x,y]
| > Here, f3 and f4 are identical; putting a bang before a pattern that
| > forces evaluation anyway does nothing.
|
| The first sentence is true, but only in settings where the pattern is being
| evaluated eagerly -- the bang in:
| > f3 a = let !(x,y) = a in [1,x,y]
| > f4 a = let (x,y) = a in [1,x,y]
| has an effect.
|
| The first time I read this, I took the first sentence to be a unqualified 
truth
| and ended up thinking that !(x,y) was equivalent to (x,y) everywhere. Stuff
| that comes later actually clarifies this, but I missed it.
|
| What about making the distinction clear upfront? Something like:
| > A bang in an eager pattern match only really has an effect if it precedes a
| variable
| > or wild-card pattern:
| > f3 !(x,y) = [x,y]
| > f4 (x,y)  = [x,y]
| > Because f4 _|_ will force the evaluation of the pattern match anyway, f3 
and f4
| > are identical; the bang does nothing.
|
| It also might be a good idea to immediately follow this with the let/where 
usage:
|
| > A bang can also preceed a let/where binding to make the pattern match 
strict. For
| example:
| > let ![x,y] = e in b
| > is a strict pattern...
| (in the existing docs, let comes a bit later):
|
| Just a thought. Hopefully someone can come up with a better way of
| wording what I'm getting at.
|
| Thanks,
| -Brian
|
| _
| Windows Live(tm) Hotmail(r)...more than just e-mail.
| 
http://windowslive.com/howitworks?ocid=TXT_TAGLM_WL_t2_hm_justgotbetter_howitworks_0
| 22009___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Suggestion for bang patterns documentation

2009-02-26 Thread Brian Bloniarz

I got confused by the GHC documentation recently, I was wondering how
it could be improved. From:
http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html

> A bang only really has an effect if it precedes a variable or wild-card 
> pattern:
> f3 !(x,y) = [x,y]
> f4 (x,y)  = [x,y]
> Here, f3 and f4 are identical; putting a bang before a pattern that
> forces evaluation anyway does nothing.

The first sentence is true, but only in settings where the pattern is being
evaluated eagerly -- the bang in:
> f3 a = let !(x,y) = a in [1,x,y]
> f4 a = let (x,y) = a in [1,x,y]
has an effect.

The first time I read this, I took the first sentence to be a unqualified truth
and ended up thinking that !(x,y) was equivalent to (x,y) everywhere. Stuff
that comes later actually clarifies this, but I missed it.

What about making the distinction clear upfront? Something like:
> A bang in an eager pattern match only really has an effect if it precedes a 
> variable
> or wild-card pattern:
> f3 !(x,y) = [x,y]
> f4 (x,y)  = [x,y]
> Because f4 _|_ will force the evaluation of the pattern match anyway, f3 and 
> f4
> are identical; the bang does nothing.

It also might be a good idea to immediately follow this with the let/where 
usage:

> A bang can also preceed a let/where binding to make the pattern match strict. 
> For example:
> let ![x,y] = e in b
> is a strict pattern...
(in the existing docs, let comes a bit later):

Just a thought. Hopefully someone can come up with a better way of
wording what I'm getting at.

Thanks,
-Brian

_
Windows Live™ Hotmail®…more than just e-mail. 
http://windowslive.com/howitworks?ocid=TXT_TAGLM_WL_t2_hm_justgotbetter_howitworks_022009___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: bang patterns give fundamentally new capabilities?

2006-12-08 Thread Simon Peyton-Jones

| > | Also, is there a way to do something similar but for 'lazy' rather than
| > | 'seq'? I want something of type
| > |
| > | type World__ = State# RealWorld
| > |
| > | {-# NOINLINE newWorld__ #-}
| > | newWorld__ :: a -> World__
| > | newWorld__ x = realWord#  -- ???
| > |
| > | except that I need newWorld__ to be lazy in its first argument. I need
| > | to convince the opimizer that the World__ newWorld__ is returning
| > | depends on the argument passed to newWorld__.
| >
| > I don't understand what you meant here.  The definition of newWorld__ that 
you give is, of course,
| lazy in x.
|
| it is getting type 'Absent' assigned to it by the demand analysis, I
| want it to be lazy (and not strict)

Ah I think I understand now.  You want a lazy primop
discard# :: a -> ()
Now you can write
newWorld x = discard x `seq` realWorld#

The code generator treats (discard# x) as (), and
(case (discard# x) of () -> e) as e.

It should be a primop so that this behaviour is not exposed too early.  An 
alternative would be to do the transformation in the core-to-STG step, but that 
might be too early.   Still easier would be to write
discard x = ()
{-# NOINLINE[0] discard #-}
to prevent it getting inlined until the final stages of the optmisier.  The 
trouble is that I have no idea of what it means to expose discard "too early" 
is in your case.

Not hard to implement if you feel like doing so.

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: bang patterns give fundamentally new capabilities?

2006-12-04 Thread Kirsten Chevalier

On 12/3/06, John Meacham <[EMAIL PROTECTED]> wrote:

On Sat, Dec 02, 2006 at 11:02:28PM +, Simon Peyton-Jones wrote:

[snip]

> | Also, is there a way to do something similar but for 'lazy' rather than
> | 'seq'? I want something of type
> |
> | type World__ = State# RealWorld
> |
> | {-# NOINLINE newWorld__ #-}
> | newWorld__ :: a -> World__
> | newWorld__ x = realWord#  -- ???
> |
> | except that I need newWorld__ to be lazy in its first argument. I need
> | to convince the opimizer that the World__ newWorld__ is returning
> | depends on the argument passed to newWorld__.
>
> I don't understand what you meant here.  The definition of newWorld__ that 
you give is, of course, lazy in x.

it is getting type 'Absent' assigned to it by the demand analysis, I
want it to be lazy (and not strict)

3 newWorld__ :: a -> World__ {- Arity: 1 HasNoCafRefs Strictness: A -}



Well, yeah, that's because it *is* absent. If you want to convince the
demand analyzer that it isn't, then use x somewhere on the right-hand
side of the definition of newWorld__. Maybe I could be more helpful if
I knew what you were really trying to do here? (My best guess is that
you're trying to implement your own IO monad, which really shouldn't
be possible AFAIK unless there's something seriously wrong with GHC
that I don't know about. Unless you use The Function That Shall Not Be
Named.)

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: bang patterns give fundamentally new capabilities?

2006-12-03 Thread John Meacham
On Sat, Dec 02, 2006 at 11:02:28PM +, Simon Peyton-Jones wrote:
> | I was recently presented with the problem of writing a function like so
> |
> | seqInt__ :: forall a . a -> Int# -> Int#
> | seqInt__ x y = x `seq` y
> |
> | which seems fine, except 'seq' of type forall a b . a -> b -> b cannot
> | be applied to an unboxed value.
> 
> Actually it works fine.  Did you try it?  Seq is special because its second 
> type argument can be instantiated to an unboxed type.  I see that is not 
> documented in the user manual; it should be.

I was getting this problem,
http://hackage.haskell.org/trac/ghc/ticket/1031

I assumed it was because I was passing an unboxed value to seq because
when I switched them all to bang patterns, it started to work. but I
guess it was a different issue alltogether.

> 
> GHC has a kinding system that looks quite similar to the one you described 
> for jhc.  Here's teh
> comment from compiler/Type.lhs
> 
>  ?
> / \
>/   \
>   ??   (#)
>  /  \
> *   #
> 
> where   *[LiftedTypeKind]   means boxed type
> #[UnliftedTypeKind] means unboxed type
> (#)  [UbxTupleKind] means unboxed tuple
> ??   [ArgTypeKind]  is the lub of *,#
> ?[OpenTypeKind] means any type at all

yup. certainly not an accident. :)

incidentally, (tangent)
the more I think about it after writing my other mail, my rule ((#),?,!)
seems to be not very useful, the only reason it makes a difference is
because of the existence of 'seq' which lets me tell the difference
between _|_ and \_ -> _|_. replacing it wich ((#),?,#->) where #-> is
the kind of unboxed functions. with no rule of the form (#->,?,?) means
that it is statically guarenteed things that take unboxed tuples are
always fully applied to their arguments. i.e. exactly what we want for
join points or other functions we wish to ensure become loops. Seems
much more useful than functions of kind '!'. (end tangent)

> 
> | Also, is there a way to do something similar but for 'lazy' rather than
> | 'seq'? I want something of type
> |
> | type World__ = State# RealWorld
> |
> | {-# NOINLINE newWorld__ #-}
> | newWorld__ :: a -> World__
> | newWorld__ x = realWord#  -- ???
> |
> | except that I need newWorld__ to be lazy in its first argument. I need
> | to convince the opimizer that the World__ newWorld__ is returning
> | depends on the argument passed to newWorld__.
> 
> I don't understand what you meant here.  The definition of newWorld__ that 
> you give is, of course, lazy in x.

it is getting type 'Absent' assigned to it by the demand analysis, I
want it to be lazy (and not strict)

3 newWorld__ :: a -> World__ {- Arity: 1 HasNoCafRefs Strictness: A -}

John
  


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: bang patterns give fundamentally new capabilities?

2006-12-02 Thread Simon Peyton-Jones
| I was recently presented with the problem of writing a function like so
|
| seqInt__ :: forall a . a -> Int# -> Int#
| seqInt__ x y = x `seq` y
|
| which seems fine, except 'seq' of type forall a b . a -> b -> b cannot
| be applied to an unboxed value.

Actually it works fine.  Did you try it?  Seq is special because its second 
type argument can be instantiated to an unboxed type.  I see that is not 
documented in the user manual; it should be.

GHC has a kinding system that looks quite similar to the one you described for 
jhc.  Here's teh
comment from compiler/Type.lhs

 ?
/ \
   /   \
  ??   (#)
 /  \
*   #

where   *[LiftedTypeKind]   means boxed type
#[UnliftedTypeKind] means unboxed type
(#)  [UbxTupleKind] means unboxed tuple
??   [ArgTypeKind]  is the lub of *,#
?[OpenTypeKind] means any type at all

| Also, is there a way to do something similar but for 'lazy' rather than
| 'seq'? I want something of type
|
| type World__ = State# RealWorld
|
| {-# NOINLINE newWorld__ #-}
| newWorld__ :: a -> World__
| newWorld__ x = realWord#  -- ???
|
| except that I need newWorld__ to be lazy in its first argument. I need
| to convince the opimizer that the World__ newWorld__ is returning
| depends on the argument passed to newWorld__.

I don't understand what you meant here.  The definition of newWorld__ that you 
give is, of course, lazy in x.

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: bang patterns give fundamentally new capabilities?

2006-11-30 Thread Tomasz Zielonka
On Thu, Nov 30, 2006 at 08:13:13PM -0800, John Meacham wrote:
> I was recently presented with the problem of writing a function like so
> 
> seqInt__ :: forall a . a -> Int# -> Int#
> seqInt__ x y = x `seq` y
> 
> which seems fine, except 'seq' of type forall a b . a -> b -> b cannot
> be applied to an unboxed value.
> 
> I could not think of a way to actually get the behavior

How about something like this:

seqInt__ :: forall a . a -> Int# -> Int#
seqInt__ x y =
case x `seq` (I# y) of
(I# y') -> y'

The question is: will GHC optimize out the unneccesary boxing and
unboxing? Looking at the output from "ghc -O2 -ddump-simpl" makes me
think the answer is "yes".

Best regards
Tomasz
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


bang patterns give fundamentally new capabilities?

2006-11-30 Thread John Meacham

I was recently presented with the problem of writing a function like so

seqInt__ :: forall a . a -> Int# -> Int#
seqInt__ x y = x `seq` y

which seems fine, except 'seq' of type forall a b . a -> b -> b cannot
be applied to an unboxed value.

I could not think of a way to actually get the behavior I wanted until I
remembered bang patterns.

seqInt__ :: forall a . a -> Int# -> Int#
seqInt__ !x y = y

which seems to work!

my question is, is this actually something fundamentally new that bang
patterns allow or was I just not able to figure out the "old" way to do
it?

Also, is there a way to do something similar but for 'lazy' rather than
'seq'? I want something of type

type World__ = State# RealWorld
 
{-# NOINLINE newWorld__ #-}
newWorld__ :: a -> World__
newWorld__ x = realWord#  -- ???

except that I need newWorld__ to be lazy in its first argument. I need
to convince the opimizer that the World__ newWorld__ is returning
depends on the argument passed to newWorld__.

using any wacky ghc primitives in 6.6 is fine, I would just like
something that stands up to ghc -O2. when compiling with -O, ghc is too
clever and sees through tricks like this. (at least, that is what I
think is happening)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users