Re: [Haskell-cafe] Bundle patterns with type aliases

2021-09-16 Thread David Feuer
Here's a class example:

class (MFoldable t, Monoid t) => Sequence t where
  singleton :: Elem t -> t
   

One might wish to write pattern synonyms for viewing the ends of a
sequence, like the ones in Data.Sequence, and bundle them with this class.

On Thu, Sep 16, 2021, 2:22 PM Carter Schonwald 
wrote:

> These are great ideas! Could you please create a ghc tracker ticket with a
> tiny examples or two?
>
> There may be specific technical reasons we might not be able to do so for
> type synonyms in ghc, but I don’t see any obvious barriers in the case of
> David’s excellent idea, I’ve def seen lots of great code out there where
> you’d really want either associated pattern synonyms or to bundle pattern
> synonyms with the exported public interface for a type class.
>
> I’m sure there’s some devil in the details but these sound lovely.  Step
> -1 is making up 1-2 toy examples and explaining what and why you want it on
> a ghc ticket!
>
> On Wed, Sep 8, 2021 at 1:25 PM David Feuer  wrote:
>
>> I would like that, along with the ability to bundle patterns with classes.
>>
>> On Wed, Sep 8, 2021, 1:13 PM Keith  wrote:
>>
>>> Is there currently a way to 'bundle' a pattern with a type alias? And if
>>> not, could that capability be added to the PatternSynonyms GHC extension?
>>> (Is this the right place to ask, or should I be asking a GHC list?)
>>>
>>> --Keith
>>> Sent from my phone with K-9 Mail.
>>> ___
>>> Haskell-Cafe mailing list
>>> To (un)subscribe, modify options or view archives go to:
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>> Only members subscribed via the mailman list are allowed to post.
>>
>> ___
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
>
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Bundle patterns with type aliases

2021-09-16 Thread David Feuer
Here's an example:

pattern State :: (s -> (a, s)) -> State s a
pattern State f <- (coerce . runStateT -> f) where
  State = state

This would be very nice to bundle with the State type synonym.

On Thu, Sep 16, 2021, 2:22 PM Carter Schonwald 
wrote:

> These are great ideas! Could you please create a ghc tracker ticket with a
> tiny examples or two?
>
> There may be specific technical reasons we might not be able to do so for
> type synonyms in ghc, but I don’t see any obvious barriers in the case of
> David’s excellent idea, I’ve def seen lots of great code out there where
> you’d really want either associated pattern synonyms or to bundle pattern
> synonyms with the exported public interface for a type class.
>
> I’m sure there’s some devil in the details but these sound lovely.  Step
> -1 is making up 1-2 toy examples and explaining what and why you want it on
> a ghc ticket!
>
> On Wed, Sep 8, 2021 at 1:25 PM David Feuer  wrote:
>
>> I would like that, along with the ability to bundle patterns with classes.
>>
>> On Wed, Sep 8, 2021, 1:13 PM Keith  wrote:
>>
>>> Is there currently a way to 'bundle' a pattern with a type alias? And if
>>> not, could that capability be added to the PatternSynonyms GHC extension?
>>> (Is this the right place to ask, or should I be asking a GHC list?)
>>>
>>> --Keith
>>> Sent from my phone with K-9 Mail.
>>> ___
>>> Haskell-Cafe mailing list
>>> To (un)subscribe, modify options or view archives go to:
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>> Only members subscribed via the mailman list are allowed to post.
>>
>> ___
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
>
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Bundle patterns with type aliases

2021-09-16 Thread Carter Schonwald
These are great ideas! Could you please create a ghc tracker ticket with a
tiny examples or two?

There may be specific technical reasons we might not be able to do so for
type synonyms in ghc, but I don’t see any obvious barriers in the case of
David’s excellent idea, I’ve def seen lots of great code out there where
you’d really want either associated pattern synonyms or to bundle pattern
synonyms with the exported public interface for a type class.

I’m sure there’s some devil in the details but these sound lovely.  Step -1
is making up 1-2 toy examples and explaining what and why you want it on a
ghc ticket!

On Wed, Sep 8, 2021 at 1:25 PM David Feuer  wrote:

> I would like that, along with the ability to bundle patterns with classes.
>
> On Wed, Sep 8, 2021, 1:13 PM Keith  wrote:
>
>> Is there currently a way to 'bundle' a pattern with a type alias? And if
>> not, could that capability be added to the PatternSynonyms GHC extension?
>> (Is this the right place to ask, or should I be asking a GHC list?)
>>
>> --Keith
>> Sent from my phone with K-9 Mail.
>> ___
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
>
> ___
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/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 dan.d...@gmail.com 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 Dan Doel
Filed. Bug #8952.


On Wed, Apr 2, 2014 at 3:41 PM, wren romano winterkonin...@gmail.comwrote:

 On Tue, Apr 1, 2014 at 3:02 PM, Dan Doel dan.d...@gmail.com 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


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: Elimination of absurd patterns

2011-05-03 Thread C Rodrigues

I tried it again using a development version of GHC 7.1 that I downloaded in 
March.
The results are the same, with GHC generating different code for the supposedly
equivalent data types. 'barName' has an impossible pattern match against
constructor 'BarExtra', whereas 'fooName' does not.



 Date: Mon, 2 May 2011 23:03:23 -0300
 Subject: Re: Elimination of absurd patterns
 From: felipe.le...@gmail.com
 To: red...@hotmail.com
 CC: glasgow-haskell-users@haskell.org

 On Mon, May 2, 2011 at 6:20 PM, C Rodrigues  wrote:
  I was experimenting with using GADTs for subtyping when I found something
  interesting.  Hopefully someone can satisfy my curiosity.
  Here are two equivalent GADTs.  My understanding was that GHC would
  translate Foo and Bar into isomorphic data types.  However, GHC 6.12.3
  generates better code for 'fooName' than for 'barName'.  In 'fooName', there
  is no pattern match against 'FooExtra'.  In 'barName', there is a pattern
  match against 'BarExtra'.  What makes these data types different?

 IIRC, GHC 6.12.3 had some problems with type equalities. Did you try GHC 
 7.0.3?

 Cheers, =)

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


Elimination of absurd patterns

2011-05-02 Thread C Rodrigues

I was experimenting with using GADTs for subtyping when I found something 
interesting.  Hopefully someone can satisfy my curiosity.
Here are two equivalent GADTs.  My understanding was that GHC would translate 
Foo and Bar into isomorphic data types.  However, GHC 6.12.3 generates 
better code for 'fooName' than for 'barName'.  In 'fooName', there is no 
pattern match against 'FooExtra'.  In 'barName', there is a pattern match 
against 'BarExtra'.  What makes these data types different?

data Tagdata TagExtra

data Foo a where  Foo :: String - Foo a  FooExtra :: IORef String - Foo 
TagExtra
-- The cmm code for fooName does not match against 'FooExtra'fooName :: Foo Tag 
- StringfooName (Foo s) = s

data Bar a where  Bar :: String - Bar a  BarExtra :: a ~ TagExtra = IORef 
String - Bar a
-- The cmm code for barName will try to pattern-match against 'BarExtra'barName 
:: Bar Tag - StringbarName (Bar s) = s
  ___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Elimination of absurd patterns (reformatted)

2011-05-02 Thread C Rodrigues

I'm re-sending this e-mail, hopefully with proper line breaks this time.

I was experimenting with using GADTs for subtyping when I found something 
interesting.  Hopefully someone can satisfy my curiosity.

Here are two equivalent GADTs.  My understanding was that GHC would translate 
Foo and Bar into isomorphic data types.
However, GHC 6.12.3 generates better code for 'fooName' than for 'barName'.  In 
'fooName', there is no pattern match against 'FooExtra'.
In 'barName', there is a pattern match against 'BarExtra'.  What makes these 
data types different?


data Tag
data TagExtra



data Foo a where
  Foo :: String - Foo a
  FooExtra :: IORef String - Foo TagExtra

-- The cmm code for fooName does not match against 'FooExtra'
fooName :: Foo Tag - String
fooName (Foo s) = s



data Bar a where
  Bar :: String - Bar a
  BarExtra :: a ~ TagExtra = IORef String - Bar a

-- The cmm code for barName will try to pattern-match against 'BarExtra'
barName :: Bar Tag - String
barName (Bar s) = s
  
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Elimination of absurd patterns (reformatted)

2011-05-02 Thread Brent Yorgey
On Mon, May 02, 2011 at 09:25:06PM +, C Rodrigues wrote:
 
 I'm re-sending this e-mail, hopefully with proper line breaks this time.
 
 I was experimenting with using GADTs for subtyping when I found something 
 interesting.  Hopefully someone can satisfy my curiosity.
 
 Here are two equivalent GADTs.  My understanding was that GHC would translate 
 Foo and Bar into isomorphic data types.
 However, GHC 6.12.3 generates better code for 'fooName' than for 'barName'.  
 In 'fooName', there is no pattern match against 'FooExtra'.
 In 'barName', there is a pattern match against 'BarExtra'.  What
 makes these data types different?

Not a real answer to your question, but have you tried this with GHC
7.0.3? The type checker changed a lot between 6.12 and 7 and it may
now behave more consistently (although I do not know for sure).

-Brent

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


Re: Elimination of absurd patterns

2011-05-02 Thread Felipe Almeida Lessa
On Mon, May 2, 2011 at 6:20 PM, C Rodrigues red...@hotmail.com wrote:
 I was experimenting with using GADTs for subtyping when I found something
 interesting.  Hopefully someone can satisfy my curiosity.
 Here are two equivalent GADTs.  My understanding was that GHC would
 translate Foo and Bar into isomorphic data types.  However, GHC 6.12.3
 generates better code for 'fooName' than for 'barName'.  In 'fooName', there
 is no pattern match against 'FooExtra'.  In 'barName', there is a pattern
 match against 'BarExtra'.  What makes these data types different?

IIRC, GHC 6.12.3 had some problems with type equalities.  Did you try GHC 7.0.3?

Cheers, =)

-- 
Felipe.

___
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


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 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

cite
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)
/cite

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 Simon Peyton-Jones
| cite
| 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)
| /cite
|
| 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
Simon Peyton-Jones wrote:
 | cite
 | 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)
 | /cite
 |
 | 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


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


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


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


RE: Transformational Patterns?

2006-07-25 Thread Simon Peyton-Jones
| After reading the paper Pattern Guards and Transformational Patterns
| by Martin Erwig and Simon Peyton Jones, I'm left wondering about the
| status of transformational patterns?  Can we expect to see these at
| some point in GHC?  Or have they gone by the wayside in favor of some
| other alternative?
| 
| When I had finished reading the paper, I was disappointed to find out
| that they were not implemented as I was convinced of the merits based
| on the arguments presented in the paper.

We have no immediate plans to add views or transformational patterns to
GHC.

Why not?
a) we already have pattern guards
http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.htm
l#pattern-guards which do part of the job

b) in any language, there is a trade-off between complexity and
expressiveness.  It's not immediately clear which side of the line views
lie.

c) there are a number of alternative designs, and no clear winner

Having said that, I think one can make a strong case that some form of
views support is essential to allow abstraction, and that views should
therefore have direct support.   Indeed, it's on the table for Haskell
Prime 
http://hackage.haskell.org/trac/haskell-prime/wiki/Views

It would be a Good Thing, I believe, if those interested in views and/or
transformational patterns could use the above Wiki to record the various
possible designs, and try to converge on one. Then it might be an
interesting intern project to implement it:
http://hackage.haskell.org/trac/ghc/wiki/Internships

Simon

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


Transformational Patterns?

2006-07-18 Thread Pete Kazmier
After reading the paper Pattern Guards and Transformational Patterns
by Martin Erwig and Simon Peyton Jones, I'm left wondering about the
status of transformational patterns?  Can we expect to see these at
some point in GHC?  Or have they gone by the wayside in favor of some
other alternative?  

When I had finished reading the paper, I was disappointed to find out
that they were not implemented as I was convinced of the merits based
on the arguments presented in the paper.

Thanks,
Pete

[1] http://research.microsoft.com/~simonpj/Papers/pat.htm

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


exhaustive pattern warning bug with irrefutable patterns

2005-12-03 Thread John Meacham

the following gives a 'non-exhaustive pattern matching' error when it
shouldn't. the ~-pattern always matches. It is not the function that is
non-exhausitive, but the irrefutable binding, which are necessarily
always non-exhausive so warning about it is the wrong thing to do.

f :: [a] - a
f [x] = x
f ~(_:xs) = f xs   

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: -fwarn-incomplete-patterns, not always warns

2005-12-02 Thread Simon Peyton-Jones
It's a GHC weakness.  I've added your example to the currently-open bug
for it:

http://sourceforge.net/tracker/index.php?func=detailaid=1075259group_i
d=8032atid=108032

Simon
| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Neil Mitchell
| Sent: 01 December 2005 20:56
| To: glasgow-haskell-users@haskell.org
| Subject: -fwarn-incomplete-patterns, not always warns
| 
| Hi,
| 
| I have been playing around with -fwarn-incomplete-patterns under GHC
| 6.4.1 on Windows.
| 
| -- no warning
| ex1 x = ss
| where (s:ss) = x
| 
| -- no warning
| ex2 x = let (s:ss) = x in ss
| 
| --Warning: Pattern match(es) are non-exhaustive
| -- In a case alternative: Patterns not matched: []
| ex3 x = case x of ~(s:ss) - ss
| 
| I have translated all 3 functions using the rules supplied in the
| Haskell 98 report, so they all have the same meaning, but only one
| gives an error. Is it intentional to ignore where/let pattern matches?
| 
| Thanks
| 
| Neil
| ___
| 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


-fwarn-incomplete-patterns, not always warns

2005-12-01 Thread Neil Mitchell
Hi,

I have been playing around with -fwarn-incomplete-patterns under GHC
6.4.1 on Windows.

-- no warning
ex1 x = ss
where (s:ss) = x

-- no warning
ex2 x = let (s:ss) = x in ss

--Warning: Pattern match(es) are non-exhaustive
-- In a case alternative: Patterns not matched: []
ex3 x = case x of ~(s:ss) - ss

I have translated all 3 functions using the rules supplied in the
Haskell 98 report, so they all have the same meaning, but only one
gives an error. Is it intentional to ignore where/let pattern matches?

Thanks

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


[ ghc-Feature Requests-1189559 ] incomplete patterns and GADT

2005-04-26 Thread SourceForge.net
Feature Requests item #1189559, was opened at 2005-04-25 08:29
Message generated for change (Tracker Item Submitted) made by Item Submitter
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=358032aid=1189559group_id=8032

Category: None
Group: None
Status: Open
Priority: 5
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: incomplete patterns and GADT

Initial Comment:
I would like to compile with 
-fwarn-incomplete-patterns and use GADTs, 
but I have bogus error messages. 
Suppose I define : 
 
data T a where 
C1 :: T Char 
C2 :: T Float 
 
then a function : 
 
exhaustive :: T Char - Char 
exhaustive C1 = ' ' 
 
If I compile with incomplete pattern warnings, 
I get that my function exhaustive is not 
exhaustive. 
But if I add a case : 
 
exhaust C2 = ' ' 
 
then the compiler accurately warns me that this 
case is inaccessible. 
Would it be possible to add the accessibility check 
when compiling with incomplete patterns detection ? 

--

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detailatid=358032aid=1189559group_id=8032
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Non-exhaustive patterns in basicTypes/Var.lhs

2004-02-03 Thread Simon Peyton-Jones
We can't reproduce this at all.  What version of GHC are you using?  Can
you show a complete script?

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Peter Simons
| Sent: 18 January 2004 19:54
| To: [EMAIL PROTECTED]
| Subject: Non-exhaustive patterns in basicTypes/Var.lhs
| 
| QuickCheck's 'generate' function works fine in GHCi, but
| only for the _first_ time I call it. After that, I get an
| error:
| 
|  | Ok, modules loaded: Main.
|  | *Main generate 3 (mkStdGen 28) (return 'x')
|  | Loading package QuickCheck ... linking ... done.
|  | 'x'
|  |
|  | *Main generate 3 (mkStdGen 28) (return 'x')
|  | *** Exception: basicTypes/Var.lhs:226:32-58: Non-exhaustive
|  | patterns in record update
| 
| Peter
| 
| ___
| Glasgow-haskell-users mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Non-exhaustive patterns in basicTypes/Var.lhs

2004-01-18 Thread Peter Simons
QuickCheck's 'generate' function works fine in GHCi, but
only for the _first_ time I call it. After that, I get an
error:

 | Ok, modules loaded: Main.
 | *Main generate 3 (mkStdGen 28) (return 'x')
 | Loading package QuickCheck ... linking ... done.
 | 'x'
 |
 | *Main generate 3 (mkStdGen 28) (return 'x')
 | *** Exception: basicTypes/Var.lhs:226:32-58: Non-exhaustive
 | patterns in record update

Peter

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: fno-implicit-prelude and literal numeric patterns

2002-07-22 Thread Simon Peyton-Jones


| The user's guide is silent about which version of Eq is used 
| for literal patterns, but I assume that it follows the (n+k) 
| example and so Prelude Eq is used for the overloaded use of ==.

That's right.  I'll add a note to that effect in the users guide.

| What is the reason for using Prelude.Ord (and Prelude.Eq)? 
| 
| This seems very limiting since you can replace Num but you 
| can't replace Eq, and moreover, your new versions of the 
| Numeric classes must be subclasses of Prelude.Eq, rather than 
| another Eq. 
|...
| Is there are strong reason for avoiding the alternative: 
| whatever == and = are in scope? Perhaps it is the 
| if-then-else that must refer to Prelude.Bool?

Well, I had to stop somewhere.  (As I have previously remarked on this
thread, it is hard to make *everything* rebindable.)  With more effort
one could make more things rebindable.

My goal was to make numerics completely rebindable; the current
omission is (only) the handling of defaults.  

At the moment I simpy don't know what a good 'final' design might be,
and I'm pretty reluctant to develop this feature incrementally.  If a 
consensus emerges,  then yes (unless it's a heart-and-lung job) I'll
implement it or help one of you to do so.

Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: Or-patterns

2000-12-06 Thread Simon Peyton-Jones

Sensible suggestion

No technical problem, just one more thing to do.
If anyone feels inclined to implement it I'll gladly incorporate 
the fruits of their labours in the GHC code base.

Simon

| -Original Message-
| From: George Russell [mailto:[EMAIL PROTECTED]]
| Sent: 04 December 2000 16:18
| To: [EMAIL PROTECTED]
| Subject: Or-patterns
| 
| 
| Why not steal a good idea from Standard ML/New Jersey now and 
| again?  This has
| "Or-patterns" which allow you to match against a disjunction 
| of patterns,
| EG
| 
| fun sleepIn (Date.Sat | Date.Sun) = true
| |   sleepIn _ = false
| 
| Where you have variables in the patterns, you bind only the 
| variables which appear 
| in all the patterns, and you unify the types accordingly.
| 
| Of course you can do without this feature, but I feel it 
| shouldn't be too hard
| to implement and for me at least it would be occasionally useful.
| 
| ___
| Glasgow-haskell-users mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
| 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Or-patterns

2000-12-06 Thread Marcin 'Qrczak' Kowalczyk

Mon, 04 Dec 2000 17:17:42 +0100, George Russell [EMAIL PROTECTED] pisze:

 Where you have variables in the patterns, you bind only the
 variables which appear in all the patterns, and you unify the
 types accordingly.

Or bind them all (otherwise there would be _ written) and get bottom
in case the matching subpattern did not bind the given variable.

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Or-patterns

2000-12-04 Thread George Russell

Why not steal a good idea from Standard ML/New Jersey now and again?  This has
"Or-patterns" which allow you to match against a disjunction of patterns,
EG

fun sleepIn (Date.Sat | Date.Sun) = true
|   sleepIn _ = false

Where you have variables in the patterns, you bind only the variables which appear 
in all the patterns, and you unify the types accordingly.

Of course you can do without this feature, but I feel it shouldn't be too hard
to implement and for me at least it would be occasionally useful.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users