Re: Modification of State Transformer

2002-08-12 Thread Shawn P. Garbett

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On Sunday 11 August 2002 07:26 pm, Scott J. wrote:
 Hi,

 I invite you then to explain what happens with every step.

 The use of forall is misleading and fast to be misunderstood: I mention
 here the inner forall's.

 Thx

 Scott
  This list is great. The implementation in the ST module solves the
  problem and I understand how it works.
 
  Shawn

Given the level of detailed explanations to date, I don't see the point. But 
I'll go ahead and do so anyway, by summarizing what I've learned from the 
previous posts.

I had read the example in Bird'd book on state transformers. The definition 
of state however was a fixed type in the examples. Wanting to extend the 
definition and make it more general I was trying to figure out how to modify 
the type. 

Bird's definition was:
newtype St a = MkSt (State - (a,State))
type State   = type

I had attempted to extend the type as follows
newtype St a s = MkSt (s - (a,s))

This died in the compiler when declaring this type as an instance of Monad:
instance Monad St where 
return x = MkSt f where f s = (x,s)
p = q  = MkSt f where f s = apply(q x) s'
where (x,s') = apply p s
ghc returned the following (referencing the instance line):
Couldn't match `*' against `* - *'
Expected kind: (* - *) - *
Inferred kind: (* - * - *) - *
When checking kinds in `Monad St'
In the instance declaration for `Monad St'

When a type constructor has an argument it has a type of `* - *'.
When a type constructor has two arguments it has a type of `* - * - *'.
This construction of the type can be extended to n arguments by having the 
number of `-' match the n arguments of type and the `*' be n+1. 

The class definition of Monad contains the following:
class Monad m where
return :: a - m a
(=)  :: m a - (a - m b) - m b


So the class of St a s needs reduction from `* - * - *' to `* - *' to fit 
the single argument type constructor of the Monad class. By using (St a) 
which causes the type constructor to be of type `(* - *) - *'. Since `(* - 
*)' can be used as `*', by creation of another type. This because equivalent 
to `* - *'.

The only thing left is reversing the order so that the result type is of the 
correct form in the Monad usage. I.e, in my initial ordering the `return' of 
the Monad would end up returning something of type `s' which is not 
particularly useful, since type `a' is the desired return type from the 
transformer.

So the corrected version of State becomes:
newtype St s a = MkSt (s - (a, s))

instance Monad (St s) where
...

Shawn Garbett
- -- 
You're in a maze of twisty little statements, all alike.
Public Key available from http://www.garbett.org/public-key
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.0.7 (GNU/Linux)

iD8DBQE9V8P4DtpPjAQxZ6ARAq0VAJ9toEiEm+d58vgbKEofzXBISyXrEACfasbc
eaEg2zVi9y90vk+fXKGSrt0=
=OrwN
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Fw: Modification of State Transformer

2002-08-12 Thread Scott J.


- Original Message -
From: Scott J. [EMAIL PROTECTED]
To: Shawn P. Garbett [EMAIL PROTECTED]
Sent: Monday, August 12, 2002 9:04 PM
Subject: Re: Modification of State Transformer


 I 'm sorry,

 What I meant was discussion about the state transformer ST s a itself. And
 how it works. What does mean the second inner forall loop and so on. I
can't
 find explanations of this in the Haskell library.

 Regards

 Scott
 - Original Message -
 From: Shawn P. Garbett [EMAIL PROTECTED]
 To: Scott J. [EMAIL PROTECTED]
 Cc: [EMAIL PROTECTED]
 Sent: Monday, August 12, 2002 4:19 PM
 Subject: Re: Modification of State Transformer


  -BEGIN PGP SIGNED MESSAGE-
  Hash: SHA1
 
  On Sunday 11 August 2002 07:26 pm, Scott J. wrote:
   Hi,
  
   I invite you then to explain what happens with every step.
  
   The use of forall is misleading and fast to be misunderstood: I
 mention
   here the inner forall's.
  
   Thx
  
   Scott
This list is great. The implementation in the ST module solves the
problem and I understand how it works.
   
Shawn
 
  Given the level of detailed explanations to date, I don't see the point.
 But
  I'll go ahead and do so anyway, by summarizing what I've learned from
the
  previous posts.
 
  I had read the example in Bird'd book on state transformers. The
 definition
  of state however was a fixed type in the examples. Wanting to extend the
  definition and make it more general I was trying to figure out how to
 modify
  the type.
 
  Bird's definition was:
  newtype St a = MkSt (State - (a,State))
  type State   = type
 
  I had attempted to extend the type as follows
  newtype St a s = MkSt (s - (a,s))
 
  This died in the compiler when declaring this type as an instance of
 Monad:
  instance Monad St where
  return x = MkSt f where f s = (x,s)
  p = q  = MkSt f where f s = apply(q x) s'
  where (x,s') = apply p s
  ghc returned the following (referencing the instance line):
  Couldn't match `*' against `* - *'
  Expected kind: (* - *) - *
  Inferred kind: (* - * - *) - *
  When checking kinds in `Monad St'
  In the instance declaration for `Monad St'
 
  When a type constructor has an argument it has a type of `* - *'.
  When a type constructor has two arguments it has a type of `* - * -
*'.
  This construction of the type can be extended to n arguments by having
the
  number of `-' match the n arguments of type and the `*' be n+1.
 
  The class definition of Monad contains the following:
  class Monad m where
  return :: a - m a
  (=)  :: m a - (a - m b) - m b
 
 
  So the class of St a s needs reduction from `* - * - *' to `* - *' to
 fit
  the single argument type constructor of the Monad class. By using (St a)
  which causes the type constructor to be of type `(* - *) - *'. Since
 `(* -
  *)' can be used as `*', by creation of another type. This because
 equivalent
  to `* - *'.
 
  The only thing left is reversing the order so that the result type is of
 the
  correct form in the Monad usage. I.e, in my initial ordering the
`return'
 of
  the Monad would end up returning something of type `s' which is not
  particularly useful, since type `a' is the desired return type from the
  transformer.
 
  So the corrected version of State becomes:
  newtype St s a = MkSt (s - (a, s))
 
  instance Monad (St s) where
  ...
 
  Shawn Garbett
  - --
  You're in a maze of twisty little statements, all alike.
  Public Key available from http://www.garbett.org/public-key
  -BEGIN PGP SIGNATURE-
  Version: GnuPG v1.0.7 (GNU/Linux)
 
  iD8DBQE9V8P4DtpPjAQxZ6ARAq0VAJ9toEiEm+d58vgbKEofzXBISyXrEACfasbc
  eaEg2zVi9y90vk+fXKGSrt0=
  =OrwN
  -END PGP SIGNATURE-
  ___
  Haskell-Cafe mailing list
  [EMAIL PROTECTED]
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Fw: Modification of State Transformer

2002-08-12 Thread Shawn P. Garbett

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On Monday 12 August 2002 02:08 pm, Scott J. wrote:
 - Original Message -
 From: Scott J. [EMAIL PROTECTED]
  What I meant was discussion about the state transformer ST s a itself.
  And how it works. What does mean the second inner forall loop and so on.
  I can't find explanations of this in the Haskell library.

Oh!

If you look in the paper that's mentioned: _Lazy_Functional_State_Threads_, 
by John Launchbury and Simon Jones, 1994, there's a big section on this.

To quote:

Section 2.4 Encapsulaion

So far we have been able to combine state transformers to make larger state 
transformers, but how can we make a state transformer part of a larger 
program which does not manipulate state at all? What we need is a function, 
runST, with a type something like the following:
runST :: ST s a - a

The idea is that runST takes a state transformer as its argument, conjures up
an initial empty state, applies the state transformer to it, and returns the
result while discarding the final state.

... Discussion of usage implications, and how this initial guess at type 
creates all kinds of potential usage problems ...

To put it another way, the argument of runST should no make any assumptions 
about what has already been allocated in the initial state, That is, runST 
should work regardless of what initial state it is given. So the type of 
runST should be:
runST :: forall a . (forall s.ST s a) - a
This is not a Hindley-Milner type, because the quantifiers are not all at the 
top level; it is an example of rank-2 polymorphism (McCracken [1984]).

Section 5.2 Types

Most of the type rules are the usual Hindley-Milner rules. The most 
interesting addition is the typing judgement for runST. Treating it as a 
language construct avoids the need to go beyond Hindley-Milner types. So 
rather than actually give runST the type
runST :: forall a . (forall s.ST s a) - a
as suggested in the introduction, we ensure that its typing judgment has the 
same effect.


- -- 
You're in a maze of twisty little statements, all alike.
Public Key available from http://www.garbett.org/public-key
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.0.7 (GNU/Linux)

iD8DBQE9WAthDtpPjAQxZ6ARAgsqAJ9i+oIdWHvQB80xmEhugQTklOtpvQCdFbM5
ol6XOKjp7FGdM3oetPUTw+E=
=+exg
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Modification of State Transformer

2002-08-11 Thread Scott J.

Hi,

I invite you then to explain what happens with every step.

The use of forall is misleading and fast to be misunderstood: I mention
here the inner forall's.

Thx

Scott
- Original Message -
From: Shawn P. Garbett [EMAIL PROTECTED]
To: Jon Cast [EMAIL PROTECTED]
Cc: [EMAIL PROTECTED]
Sent: Friday, August 09, 2002 3:16 AM
Subject: Re: Modification of State Transformer


  Btw: This has already been done, in GHC: see the ST module in GHC's
  library
 
http://www.haskell.org/ghc/docs/latest/html/base/Control.Monad.ST.html.

 This list is great. The implementation in the ST module solves the problem
 and I understand how it works.

 Shawn


 --
 You're in a maze of twisty little statements, all alike.
 Public Key available from http://www.garbett.org/public-key
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Modification of State Transformer

2002-08-08 Thread Tom Pledger

Shawn P. Garbett writes:
 :
 | What I want is something like this, so that the state transformer has a 
 | generic state type: 
 | 
 | newtype St a s = MkSt (s - (a, s))
 | 
 | apply :: St a s - s - (a, s)
 | apply (MkSt f) s  = f s
 | 
 | instance Monad St where
 |   return x  = MkSt f where f s = (x,s)
 |   p = q   = MkSt f where f s = apply (q x) s'
 |  where (x, s') = apply p s
 | ---
 | The trouble occurs on the instance line
 | Couldn't match `*' against `* - *'
 | Expected kind: (* - *) - *
 | Inferred kind: (* - * - *) - *

Let's compare your declaration of St with the type signatures in class
Monad.

class Monad m where
return :: a - m a
(=)  :: m a - (a - m b) - m b
-- etc.

If we instantiate m as St, we get a type of   a - St a   for return,
which lacks the state variable s.  In turn, s corresponds to the third
* in the inferred kind in the error message.

Try partially applying St to its state variable, and declaring a Monad
instance of that partial application, which will have the right kind
*-*.

Regards,
Tom
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Modification of State Transformer

2002-08-08 Thread Ken Shan

On 2002-08-08T14:11:54-0500, Shawn P. Garbett wrote:
 newtype St a s = MkSt (s - (a, s))
 instance Monad St where

This line should say

instance Monad (St a) where

because it is (St a) that is a Monad, not St by itself.

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
http://www.ethnologue.com/



msg01872/pgp0.pgp
Description: PGP signature


Re: Modification of State Transformer

2002-08-08 Thread Jon Cast

Shawn P. Garbett [EMAIL PROTECTED] wrote:
 I'm trying to modify Richard Bird's state transformer. The example
 in his book (_Introduction_to_Functional_Programming_using_Haskell_)
 has State defined as a explicit type.

 I.e. Here's the relevant snippet:

 -- State transformer definition

 newtype St a = MkSt (State - (a, State))
 type State   = Int

 -- State transformer applied to state
 apply :: St a - State - (a, State)
 apply (MkSt f) s  = f s

 -- State monad

 instance Monad St where
   return x  = MkSt f where f s = (x,s)
   p = q   = MkSt f where f s = apply (q x) s'
  where (x, s') = apply p s
 -

 What I want is something like this, so that the state transformer
 has a generic state type:

Btw: This has already been done, in GHC: see the ST module in GHC's
library
http://www.haskell.org/ghc/docs/latest/html/base/Control.Monad.ST.html.
To answer your specific question, though:

 newtype St a s = MkSt (s - (a, s))

These are in the wrong order (see below); you want:

 newtype St s a = MkSt (s - (a, s))

 apply :: St a s - s - (a, s)
 apply (MkSt f) s  = f s

Again, s/St a s/St s a/.

 instance Monad St where
   return x  = MkSt f where f s = (x,s)
   p = q   = MkSt f where f s = apply (q x) s'
  where (x, s') = apply p s
 ---
 The trouble occurs on the instance line
 Couldn't match `*' against `* - *'
 Expected kind: (* - *) - *
 Inferred kind: (* - * - *) - *
 When checking kinds in `Monad St'
 In the instance declaration for `Monad St'
 Failed, modules loaded: none.

Right.  The problem here is that St is a type constructor with two
arguments (i.e., of kind (* - * - *)), whereas Monad wants a type
constructor with one argument (i.e., of kind (* - *)).  Hence the
error.  This is the same type of error you'd get if you tried to
declare an instance for `Eq Tree', where `Tree' is a standard
(polymorphic) BST.  The way you solve that is to instantiate `Eq (Tree
a)', and it's the same thing here: instantiate `Monad (St s)'.
Of course, you need to switch the order of the arguments to St first
(as done above), so Haskell knows `s' is a the state type, not the
result type.

HTH

Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Modification of State Transformer

2002-08-08 Thread Shawn P. Garbett

 Btw: This has already been done, in GHC: see the ST module in GHC's
 library
 http://www.haskell.org/ghc/docs/latest/html/base/Control.Monad.ST.html.

This list is great. The implementation in the ST module solves the problem 
and I understand how it works. 

Shawn


-- 
You're in a maze of twisty little statements, all alike.
Public Key available from http://www.garbett.org/public-key
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: State Transformer

2002-01-11 Thread Jorge Adriano

[Obs: most answers I got end up in my pvt e-mail and not in the mailing 
list... I replyed in pvt to those. I do feel it some cases that is probably 
accidental as I do it all the time :), and the discussion ends leaving the 
mailing list. So i'd just like to let you know that I for one am in favour of 
having 'reply' to the mailing list as default :) ]

  Monads! (right?)

 Well, I suppose so.  Generally speaking.

 But, you might want to consider using the standard random generation
 routines from the (IO) top level of your program, and just split the
 random generator for each function that uses it.  IOW, passing each
 function its own random generator, instead of worrying about returning
 the rest of a global random sequence.

 (I don't have any good example code, I'm afraid, but at leat have a
 look at the chapter on Random in the library report on http://haskell.org)

 -kzm

I did checked the Random library. My first idea was that, but I thought 
infinite lists of random numbers would be more elegant, anyway that is 
subjective. Both aproches suffer from the same problem, they reflect 
themselves on the type signatures. If I decide to try a deterministic 
approach to 'selection of individuals', signatures will change.
The problem is more general, it's not just about the random numbers. If I 
want keep track of the best individuals, or the average fitness, or the 
evolution of some schemata... etc... I'll have to change the type signature.
And this doesn't even changes the 'algorithm behaviour' in anyway...I'm just 
talking about keeping track of data.
So my guess is that monads is the only elegant way out of this.

J.A.


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



State Transformer

2002-01-07 Thread Jorge Adriano

Hi,
I'm studying, among other things, Genetic Algorithms and Neural Networks and 
I decided I'd use haskell to code some simple GAs and NNs along with my study.
Well, maybe it was not such a good idea after all, because I've been spending 
way more time learning more Haskell then GAs and NNs :(

Anyway, I was coding some simple GA, and as you probably know I need to use 
random values. The most elegant way I could think of was to generate some 
infinite list of random values and pass them around as arguments to the 
functions that need those values. I called data which wraped this list 
Environment, and at first it seemed a nice way to solve the problem.
Well, now I think it gets kind of weird because some functions will end up to 
have typesomething - (otherthing, Environment), to update those lists... 
it's just ugly. 
Beside those lists I'd also like to control some statistics like the number 
of mutations, n. of crossovers, best fitness value in each generation, etc... 
I figured out that there should be a better way to do this then just chaging 
all the signatures and passing all this values around.

Monads! (right?)
Till then I had just read what I needed to be able to use the IO Monad. 
Seems to me like having a State Transformer monad its the best way to do it.
Now I've read a great deal of Richard Birds Book chap 10 (Monads), as well as 
the Monads for the Haskell Working Programmer[1] by Theodore Norvell.

I was going to try to make my own simple examples using a ST.
A State Monad seemed something like would most probably be in some Standard 
Library, or at least in some GHC library.
And it was (section 4.31.ST in the hslibs documentation)
I wanted to use this ST, but then I noticed it was different from the one 
described in tutorial[1].

I was expecting the ST Monad ghc module to provide an apply function, 
analogue to the 
 applyST :: StateTrans s a - s - (s, a)
 applyST (ST p) s = p s
in the tutorial.
I also expected to have general functions to access and change State. I can't 
implement them myself since the ST constructor is (obviously) not exported.
But this ST module seems to work in a completely diferent way.
From what I can tell it is not suposed to be applyed to an initial state, 
instead it starts with an 'empty' state...
State is controled with Referencies (mutable variables).

Ok, now my problem, how do I use this?
I can't really see how to change this referencies from within some function. 
(Got an example in the end to explain better waht I mean with that [Example1])

I'd also appreciate  some coments on:
Using a ST monad (good idea, bad?)
Using the Ghc ST monad?
Chromosomes defined as arrays? - either IArray or Diff array got to give it 
some more thought... (don't want Ints + bitwise operations right now...)

Well, any other comments or hints that you think that might be usefully are 
welcome. I've already checked out the paper from the TAIGA project[2], it's 
not exactly done the way I'm thinking about doing it, but I got some usefull 
tips from there, like the use of a Monad to control statistics.
One of my main problems so far as been *knowing what do I need to know*!
I don't know anyone that codes in haskell, not having anyone to talk to and 
share ideas doesn't helps much either.
Things get complicated where you (you - the guy that comes from the 
imperative paradigm) less expects it too... the space leaks, using monads to 
control state... if you still have not read about this stuff, IMO, it is easy 
to feel like you already know enough to do some solve some kind of problems 
when you actually don't. 
Any newbie to C or Pascal can make a few randoms here and there, and keep 
track of statistics... when you already spent some time with haskell you 
don't even question whether you already know enough to do something like 
*that*. Only when you start to work, and thing start to get messy, you begin 
to think that *maybe you need something you still don't know about*, and then 
you got to find out what it is...
Documentation, I also feel like it could be more and better... the ST module 
in ghc for instance... would it be that hard to put at least some simple 
example there? No, just the type signatures...
Well, this is just my opinion anyway.

Thanks for your atention, and happy 2002 ;-)
J.A.


[Example1]
How can I do this for instance, with the Ghc ST Monad:


-- the State Trans defined as in the tutorial
newtype StateTrans s a = ST( s - (s, a) )

instance Monad (StateTrans s)
  where
-- (=) :: StateTrans s a - (a - StateTrans s b) - StateTrans s b
(ST p) = k  =  ST( \s0 - let (s1, a) = p s0
(ST q) = k a
in q s1 )

-- return :: a - StateTrans s a
return a = ST( \s - (s, a) )

applyST :: StateTrans s a - s - (s, a)
applyST (ST p) s = p s


-- just change the state
putST

Re: State Transformer

2002-01-07 Thread Ketil Z Malde

Jorge Adriano [EMAIL PROTECTED] writes:

 Anyway, I was coding some simple GA, and as you probably know I need to use 
 random values. The most elegant way I could think of was to generate some 

[...]

 Monads! (right?)

Well, I suppose so.  Generally speaking.

But, you might want to consider using the standard random generation
routines from the (IO) top level of your program, and just split the
random generator for each function that uses it.  IOW, passing each
function its own random generator, instead of worrying about returning
the rest of a global random sequence.

(I don't have any good example code, I'm afraid, but at leat have a
look at the chapter on Random in the library report on http://haskell.org)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: newbie: running a state transformer in context of a state reader

2001-02-20 Thread Konst Sushenko

Marcin,

thanks for your help.

to implement the lift functionality i added these well
known definitions:


class (Monad m, Monad (t m)) = TransMonad t m where
lift   :: m a - t m a

instance (Monad m, Monad (State s m)) = TransMonad (State s) m where
lift m  = ST (\s - m = (\a - return (a,s)))



but my lookahead function

lookahead p = do { s - fetch
 ; lift (evalState p s)
 }

is typed as

lookahead :: State MyState Maybe a - State MyState Maybe (a,MyState)

but i need

lookahead :: State MyState Maybe a - State MyState Maybe a

apparently, the (=) and return used in the definition of lift above are
for the monad (State s m), and not monad m...

everything works if i do not use the TransMonad class, but define lift
manually as:

lift :: Parser a - Parser a
lift m = ST (\s - unST m s = (\(a,_) - return (a,s)))

but this looks like a special case of the lift above, except the right hand
side of
'bind' is executed in the right context.

i am still missing something

konst


-Original Message-
From: Marcin 'Qrczak' Kowalczyk [mailto:[EMAIL PROTECTED]]
Sent: Tuesday, February 20, 2001 10:17 AM
To: [EMAIL PROTECTED]
Subject: Re: newbie: running a state transformer in context of a state
reader


Mon, 19 Feb 2001 18:07:17 -0800, Konst Sushenko [EMAIL PROTECTED] pisze:

 now i am curious if it is possible to run the given parser (state
 transformer) in a context of a state reader somehow, so as the state
 gets preserved automatically. something that would let me omit the
 calls to fetch and set methods.

It should be possible to do something like this:

lookahead:: Parser a - Parser a
lookahead p = do { s - fetch
 ; lift (evalState p s)
 }

where evalState :: Monad m = State s m a - s - m a
  lift  :: Monad m = m a - State s m a
are functions which should be available or implementable in a monad
transformer framework. I don't have the Hutton/Meijer's paper at hand
so I don't know if they provided them and under which names. Such
functions are provided e.g. in the framework provided with ghc (by
Andy Gill, inspired by Mark P Jones' paper "Functional Programming
with Overloading and Higher-Order Polymorphism").

This definition of lookahead uses a separate state transformer thread
instead of making changes in place and undoing them later. I don't
think that it could make sense to convert a state transformer to
a state reader by replacing its internals, because p does want to
transform the state locally; a value of type Parser a represents
a state transformation. The changes must be isolated from the main
parser, but they must happen in some context.

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


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe