Re: Summary so far (was: HOpenGL and --enable-threaded-rts)

2002-06-20 Thread Wolfgang Thaller
Simon Marlow wrote:
This discussion is getting rather long, so I thought I'd summarise (as
much for my benefit as everyone else's).  Please let me know if I get
anything wrong.

I haven't found anything wrong.

I'm pretty sure (1) and (2) aren't viable, though.

I basically agree. In the presence (3) or (4) [or (5) ;-) ], my own hack looks like - well - a hack. I'll definitely use it as a short term solution for my own toy projects, though. I won't commit any code, but if anyone else needs a short-term solution for HOpenGL, they can ask me.

Personally I can't decide whether (3) or (4) is the better solution.

I'd say, let's go for (5) - that is, some blend between (3) or (4). (4) almost sounds like (3) could be implemented on top of it. The simplicity of (3) is needed in most cases, the power of something like (4) in some.

Some other random thoughts:

Does the "OS-thread"-binding have to be a permanent attribute of a thread, or can we also have something like:

inOSThread theGLUTThread $ do
...

This could be useful for finalizers, or when some thread-sensitive API is used only "some of the time". The problem is that the haskell thread in question could be blocked indefinitely until the OS thread decides to return to Haskell code.
I do also like the idea of a forkHeavyIOThread primitive. 
If something like (4) is implemented, it should still be possible to say that a Haskell thread can run in any OS thread. We never know what new ways of juggling threads (SMP, distributed systems?) will be supported in the future for code that "doesn't mind" being executed in different threads. The current limitations of the RTS (i.e. haskell code can only run in one OS thread at one time) should be a well-documented implementation detail, not a fundamental assumption for the threading primitives. The "don't care" thread group could still support features like the current threaded rts. The documentation will just have to make clear that it can't be predicted which OS thread those haskell threads will be run in, and that some libraries don't like that.

CU,

Wolfgang

Re: HOpenGL and --enable-threaded-rts

2002-06-19 Thread Wolfgang Thaller

On Mittwoch, Juni 19, 2002, at 01:43 , Andrew J Bromage wrote:

> I don't mean to detract from the fine work which the HOpenGL people
> have achieved, but I think that binding to the C implementation of GLUT
> was, in retrospect, a mistake.

The problem here is with OpenGL, not with GLUT. OpenGL requires some 
thread-local state to be set correctly in order to operate. Surely you 
wouldn't suggest reimplementing OpenGL (plus all OpenGL video drivers 
for every platform/OS/graphics card combination out there) in Haskell?

> Binding to foreign language-specific
> frameworks in general is a mistake, IMO.

I agree that it is difficult, and it can cause headaches. But in order 
to write "real-world" applications in Haskell, there is no way around 
it. In order to write GUI applications, I need a binding to Win32 (a 
"C-specific" framework) for Windows, to Carbon (C-specific) or Cocoa 
(Objective-C or Java) for MacOS X, and to some toolkit for X11 (Gtk, for 
example). Most of those use callbacks of some sort.
It cannot be a "mistake" because it is the _only_ option for achieving a 
certain goal (writing "native" GUI applications for any platform in 
Haskell).

> Today it's only threads which
> you may be able to hack around, but tomorrow, your called-back function
> will want to throw an exception, or something even hairier will turn up
> and you'll be back where you started.

Exceptions just require a little more marshaling, I think. As for the 
even hairier things, I don't think "they" are going to add many more 
crazy things to the C language family, so C-specific frameworks 
shouldn't hold too many surprises in store for us...

> Sorry for the pessimism, but this is bitter experience talking.

Sorry for the optimism, that's just my determination to use OpenGL from 
Haskell talking :-)


Cheers,
Wolfgang

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



Re: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Andrew J Bromage

G'day all.

On Tue, Jun 18, 2002 at 05:58:15PM +0100, Alastair Reid wrote:

> A further piece of what one might call thread local state is
> 'recursive locks' like those found in Java.

Recursive locks arguably should be part of the lock abstraction, not
"thread local state ".  Since all it costs is another counter, it's
almost trivial for the lock implementation (usually the OS) to
implement it, of only as an option.

For comparison: all Win32 built-in locks (Win32 confusingly
differentiates "mutexes" and "critical sections" even though they are
essentially the same thing) are recursive.  Under all pthreads
implementations that I'm aware of, THREAD_MUTEX_RECURSIVE is supported.
I don't know enough about any other platforms to comment, but my bet is
you'll find it pretty much everywhere.

I think you need to look no further than the thread id itself for
"thread local state".  As soon as you want to do anything with the
thread id other than compare equality (even Ord-type comparison is not
supported under pthreads), you have thread local state.

I don't mean to detract from the fine work which the HOpenGL people
have achieved, but I think that binding to the C implementation of GLUT
was, in retrospect, a mistake.  Binding to foreign language-specific
frameworks in general is a mistake, IMO.  Today it's only threads which
you may be able to hack around, but tomorrow, your called-back function
will want to throw an exception, or something even hairier will turn up
and you'll be back where you started.

Sorry for the pessimism, but this is bitter experience talking.

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



Re: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Wolfgang Thaller

I have implemented a hack that makes HOpenGL work with 
--enable-threaded-rts. It currently contains 3 lines of MacOS X-specific 
code, and it needs cleaning up. More about that later.

 > Simon and I don't understand GLUT's requirements at all clearly.
 > Why is the context thread-local?

OpenGL is a state based API. All operations are defined in terms of how 
they affect global state. All global state used by OpenGL is contained 
in a so called "context". Every OpenGL command implicitly operates on a 
"current context". If a program draws to two different windows, it uses 
two different contexts.
In order to allow programs to use OpenGL draw into two different 
contexts in two different threads, the "current context" pointer has to 
be made thread-local. Most OpenGL implementations do this by now, 
although there may be a few outdated ones left.
Context creation and management is _not_ part of the OpenGL standard. 
There is a different API for every platform. GLUT is a cross-platform 
"utility toolkit" for creating simple OpenGL applications. It is 
supposed to isolate its user from all this context buisiness by always 
setting up the correct context before calling back to the program. But 
even if don't use GLUT, OpenGL requires the current context to be set 
_in the current OS thread_ in order to operate.

We cannot rely on OpenGL implementations to use any known general 
mechanism for thread-local storage.
Making OS threads correspond directly to Haskell threads is probably an 
extensive change to the RTS that has lots of disadvantages.

My proposal is to leave dealing with thread-local state to the library 
binding (in this case, HOpenGL). This requires just a little support 
from the RTS. The library binding would have to include C-language 
routines that get called by the RTS at certain points:
* when the RTS starts executing Haskell code in an OS thread 
(grabCapability)
* when the RTS stops executing Haskell code in an OS thread 
(releaseCapability)
* when the RTS is about to spawn a new thread in response to a callback 
(scheduleThread_).
HOpenGL would just need to have about 3 platform-specific lines of code. 
This would effectively make OpenGL's thread local state global again. 
For real multithreaded use of OpenGL we would need some more RTS support.
We'd just need to agree on a nice little addition to the RTS API .
All libraries that currently can't be used because they rely on 
thread-local state could then be made to work using a few lines of C 
code.

The problems with recursive locks are, of course, not solved by this, 
but I don't see a "perfect" all-round solution anywhere on the horizon. 
(...and apart from that, I don't need recursive locks right now :-) )

Cheers,

Wolfgang

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



Re: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Alastair Reid


> Yes, these are all problems.  However, there is a nice abstraction
> of the OS thread API in GHC's RTS, thanks to Sigbjorn.  So I'm sure
> this API could be extended to include some thread-local state
> operations.

A further piece of what one might call thread local state is
'recursive locks' like those found in Java.  With normal locks, if a
thread executes this:

   take(lock);
   take(lock);
   ...
   release(lock);
   release(lock);

then the 2nd call to take will block because a thread already has the lock.

With recursive locks, the implementation of take records who has the
lock and just increments a counter if the same thread takes the lock
again.  Likewise, release decrements the counter and only releases the
lock when the counter reaches 0.

And arbitrary user code and libraries are free to implement all kinds
of code that depends on the current thread id.  I'll bet you're going
to see a lot of cases like this.

>> The only viable solution I can see is to provide a way to capture
>> the calling thread (as a first class entity) when you call into
>> Haskell and to explicitly specify whcih thread to use when you call
>> out from Haskell.  (Hmmm, sounds like callcc for C :-))

> The trouble is, that is *way* too much overhead for a C call.
> HOpenGL does lots of these, and I strongly suspect that adding a
> full OS-thread context switch (well two, including the return) for
> each one would be a killer.

So don't do it for every foreign function call - only do it for the
ones that request it.  Here's the implementation I imagine:

For foreign imports and exports that have not requested any special
thread behaviour, do exactly what GHC currently does.  Overhead == 0.

For foreign exports that have requested thread capture, the call goes
like this:

  1) Get a thread from GHC's thread pool

  2) Allocate a first-class C-thread object on the Haskell heap.
 and fill in the details for this thread.

  3) Add the normal foreign export function arguments plus a pointer
 to the C thread object to the GHC thread and make it runnable.

  4) Block this thread so that it is ready to use later.

  5) When C function returns, do so in the first-class C-thread object.

For foreign imports that have requested explicit thread choice, the
call goes like this:

  1) Get the C-thread object (it's an argument to the Haskell function
 so this is easy), perform suitable sanity checks (i.e., not
 already in use).

  2) Marshall argumens to C function into the C-thread.

  3) Unblock the C thread, block the Haskell thread waiting for
 response.

  4) When C function returns, context switch back to a GHC thread.

Overhead for foreign export is higher.  Overhead for foreign import is
not much different from existing safe foreign imports.  Overhead only
occurs if you request this feature.


-- 
Alastair Reid[EMAIL PROTECTED]http://www.cs.utah.edu/~reid/
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Simon Peyton-Jones

Simon and I have discussed this multi-threading question a bit.
This message tries to summarise the story as we understand it.


GHC's approach to threading

Make certain you read the "Supporting multi-threaded inter-operation"
section of the GHC commentary

http://www.cse.unsw.edu.au/~chak/haskell/ghc/comm/rts-libs/multi-thread.
html


The current GHC model has the basic assumption that OS threads
are inter-changeable.  One Haskell thread may be executed by one
OS thread or by many; you just can't tell.

There is a good reason for this: the current OS thread may block
in some I/O call (getChar, say), and we don't want that to block 
all Haskell threads.

If you want all Haskell threads executed by a single OS thread,
then you don't want --enable-threaded-rts, and your I/O calls may
block all Haskell threads.

There is no notion of a Haskell-thread-local location right now.
We don't know how to make it type-safe.  If you want that, you have
to define your own environment monad, which isn't too hard.  Or
use implicit parameters, also not hard.


GLUT's approach to threading
~
Simon and I don't understand GLUT's requirements at all clearly.
Why is the context thread-local?  Because different threads can have
different contexts?  Do you really need that?  If not, would it suffice
to
make all the threads have (a pointer to) the same context)?

Much the tidiest thing is to make the context an explicit parameter
to GLUT calls.  Or, if there is only one context of interest, keep it in
a process-global location (not thread-local) and, sigh, heave it into
the thread-local location before every GLUT call.


In short, we don't understand GLUT well enough to be able to
propose a solution.   I hope that the above remarks may help the
GLUT experts understand GHC well enough to write down a summary
of what is going on.  Try not to rely on someone having read all the
past mail! 


Simon



| -Original Message-
| From: Sven Panne [mailto:[EMAIL PROTECTED]] 
| Sent: 18 June 2002 15:06
| To: [EMAIL PROTECTED]
| Cc: GHC List
| Subject: Re: [HOpenGL] HOpenGL and --enable-threaded-rts
| 
| 
| Simon Marlow wrote:
| > [...] a given Haskell thread can even migrate from one OS thread to 
| > another during its execution.
| 
| Uh, oh!  %-(  Under which circumstances exactly? I fear this 
| will give loads of fun with many C libraries out there, so 
| it's important to know...
| 
| Cheers,
|S.
| ___
| 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: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Glynn Clements


Simon Marlow wrote:

> The trouble is that there isn't a single object representing the whole
> thread-local state.  Does OpenGL use pthread_getspecific() and
> pthread_setspecific() to access its thread-local state?

The libGL supplied with XFree86 uses xthread_{get,set}_specific. These
are macros which expand to the appropriate native function, one of:

thr_{set,get}specific
Tls{Set,Get}Value
tis_{set,get}specific
pthread_{set,get}specific

The XFree86 libGL source code carries SGI copyright notices, so it's a
good bet that that other Unix OpenGL implementations are similar.

Mesa's libGL has a similar abstraction, _glthread_{Get,Set}TSD. These
are functions which call the appropriate native function. Mesa
supports the thr_*, pthread_* and Tls* functions, but not the tis_*
functions; however, it also has versions which use the xthread_*
macros.

I have no idea as to the situation on Windows.

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



Re: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Dean Herington

Let me ask a naive question concerning the implementation of threading in
the GHC RTS.  Would it be feasible to support an alternative strategy for
mapping Haskell threads onto OS threads, namely that the two sets are kept
in one-to-one correspondence?  The thread multiplexing and migration that
GHC now supports sounds very cool, but it seems to violate assumptions of
potentially many threaded libraries.  If the 1-1 model is as
straightforward as it seems it should be, it might not be too complicated
to support both.  The 1-1 model could be selected for the entire process,
or preferably for each thread on its creation, if this is feasible.

An aside about performance: It seems the reason for thread multiplexing and
migration is performance, to allow Haskell threads to be lighter weight
than their OS counterparts.  While I agree with this point, there have
been, perhaps are, and most probably will be threading systems where OS
threads are light enough in weight to support the 1-1 model with good
performance.  So I don't think that concern over performance is by itself
enough to invalidate the usefulness of the 1-1 model.

Dean


Simon Marlow wrote:

> There are two problems with this approach, I think.  The situation is
> like this (correct me if I'm wrong):
>
> - Haskell thread H1 running on OS thread O1 registers a
>   callback C.
>
> - Haskell thread H1/O1 makes a blocking call into HOpenGL.
> This call is made also in O1.  The RTS allocates another
>   OS worker thread O2, and continues running Haskell threads.
>
> - HOpenGL, running in O1, invokes the callback C.  The RTS
>   stops O1, creates a new Haskell thread H2 in which to run C,
> and eventually runs H2 in O2.
>
> Problem #1 is the call-in: our current implementation *always* runs the
> callback in a different OS thread from the calling thread.  It was
> simpler this way, but perhaps this can change.
>
> Problem #2 is that we would have to add some extra machinery to
> guarantee that a given Haskell thread executes in a particular OS
> thread, and somehow do it in a way that was "fair" (i.e. the Haskell
> thread with a preference for its OS thread doesn't get starved, and
> doesn't starve other threads).  The RTS currently doesn't make any
> distinction between OS threads; a given Haskell thread can even migrate
> from one OS thread to another during its execution.

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



Re: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Sven Panne

Simon Marlow wrote:
> [...] a given Haskell thread can even migrate from one OS thread to
> another during its execution.

Uh, oh!  %-(  Under which circumstances exactly? I fear this will give
loads of fun with many C libraries out there, so it's important to know...

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



RE: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Simon Marlow

> I'm slowly losing track of this discussion...

so am I :-(

> My initial suggestion
> was that it is guaranteed that the same OS thread which created the
> f.i.w. thunk is used to call back to Haskell for *this* 
> wrapped function.
> There is no overhead for calls Haskell->C, only for the comparatively
> rare case of C->Haskell. What's wrong with this?

There are two problems with this approach, I think.  The situation is
like this (correct me if I'm wrong):

- Haskell thread H1 running on OS thread O1 registers a
  callback C.

- Haskell thread H1/O1 makes a blocking call into HOpenGL.
This call is made also in O1.  The RTS allocates another
  OS worker thread O2, and continues running Haskell threads.

- HOpenGL, running in O1, invokes the callback C.  The RTS
  stops O1, creates a new Haskell thread H2 in which to run C,
and eventually runs H2 in O2.

Problem #1 is the call-in: our current implementation *always* runs the
callback in a different OS thread from the calling thread.  It was
simpler this way, but perhaps this can change.

Problem #2 is that we would have to add some extra machinery to
guarantee that a given Haskell thread executes in a particular OS
thread, and somehow do it in a way that was "fair" (i.e. the Haskell
thread with a preference for its OS thread doesn't get starved, and
doesn't starve other threads).  The RTS currently doesn't make any
distinction between OS threads; a given Haskell thread can even migrate
from one OS thread to another during its execution.

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



Re: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Sven Panne

I'm slowly losing track of this discussion... My initial suggestion
was that it is guaranteed that the same OS thread which created the
f.i.w. thunk is used to call back to Haskell for *this* wrapped function.
There is no overhead for calls Haskell->C, only for the comparatively
rare case of C->Haskell. What's wrong with this?

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



RE: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Simon Marlow


> This sounds like a lot of work and a porting nightmare (what do you
> mean Linux/Win32/HPUX/... doesn't have thread manipulation function X,
> it's available on FreeBSD/Win32/...  What if there are other forms
> of thread-local state (e.g., errno)?  What about setjmp/longjmp?). 

Yes, these are all problems.  However, there is a nice abstraction of
the OS thread API in GHC's RTS, thanks to Sigbjorn.  So I'm sure this
API could be extended to include some thread-local state operations.

> The only viable solution I can see is to provide a way to capture the
> calling thread (as a first class entity) when you call into Haskell
> and to explicitly specify whcih thread to use when you call out from
> Haskell.  (Hmmm, sounds like callcc for C :-))

The trouble is, that is *way* too much overhead for a C call.  HOpenGL
does lots of these, and I strongly suspect that adding a full OS-thread
context switch (well two, including the return) for each one would be a
killer.

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



Re: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Alastair Reid


SimonM:
> Yes, my guess is that this will probably have to be done by
> manipulating the thread-local state in the RTS - grab the current
> thread-local state whenever a call is made into Haskell, and
> whenever we run a Haskell thread we have to set the appropriate
> thread-local state.  Perhaps it should be stored in the TSO and
> inherited by child threads too.

> The trouble is that there isn't a single object representing the
> whole thread-local state.  Does OpenGL use pthread_getspecific() and
> pthread_setspecific() to access its thread-local state?

This sounds like a lot of work and a porting nightmare (what do you
mean Linux/Win32/HPUX/... doesn't have thread manipulation function X,
it's available on FreeBSD/Win32/...  What if there are other forms
of thread-local state (e.g., errno)?  What about setjmp/longjmp?). 

The only viable solution I can see is to provide a way to capture the
calling thread (as a first class entity) when you call into Haskell
and to explicitly specify whcih thread to use when you call out from
Haskell.  (Hmmm, sounds like callcc for C :-)) Off the top of my head,
this might look like this:

  foreign export "static capture_thread" mycallback :: HsThread -> Int -> Char

which would provide a C function with this prototype:

  HsChar mycallback(HsInt);

and, on the callout side:

  foreign import "static with_thread" foo :: HsThread -> Float -> IO Double

which would invoke a C function with this type:

   HsDouble foo(HsFloat);



-- 
Alastair Reid[EMAIL PROTECTED]http://www.cs.utah.edu/~reid/
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: [HOpenGL] HOpenGL and --enable-threaded-rts

2002-06-18 Thread Simon Marlow


> Has anyone already thought about how to solve this problem?
> I'm thinking about adding hooks to the RTS (in grabCapability, 
> releaseCapability and scheduleThread_) which would be used 
> for setting 
> up the correct thread-local state whenever Haskell execution 
> "switches" 
> to a different OS thread. Those hook routines would have to 
> be written 
> in C and would be platform-specific most of the time. It's not a nice 
> solution, but it's the only one I can think of at this time.
> Unless someone comes up with a better idea _quickly_, I'll try it out 
> and then report how ugly it really is... :-)

I can't see a nice solution to this problem - it really invalidates one
of the key assumptions in the threaded implementation of the RTS, namely
that it doesn't matter which OS thread we use to execute Haskell code.

I suspect that a "safe" foreign import could be made to switch threads
to the right OS thread before entering C land, but that's way too much
overhead to impose on every single FFI call from Haskell.

Yes, my guess is that this will probably have to be done by manipulating
the thread-local state in the RTS - grab the current thread-local state
whenever a call is made into Haskell, and whenever we run a Haskell
thread we have to set the appropriate thread-local state.  Perhaps it
should be stored in the TSO and inherited by child threads too.

The trouble is that there isn't a single object representing the whole
thread-local state.  Does OpenGL use pthread_getspecific() and
pthread_setspecific() to access its thread-local state?

Cheers,
Simon

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



HOpenGL and --enable-threaded-rts

2002-06-16 Thread Wolfgang Thaller

In short, it doesn't work :-( .
OpenGL (at least on MacOS) keeps track of the "current context" on a 
per-thread basis. The GLUT library sets the current context and calls 
back to the program. With GHC 5.03 compiled with --enable-threaded-rts, 
the callback gets executed in a different thread. There is no OpenGL 
context set up for that thread, so the first OpenGL call crashes.
This might also be a problem for other state-based interfaces that use 
thread-local state.

Has anyone already thought about how to solve this problem?
I'm thinking about adding hooks to the RTS (in grabCapability, 
releaseCapability and scheduleThread_) which would be used for setting 
up the correct thread-local state whenever Haskell execution "switches" 
to a different OS thread. Those hook routines would have to be written 
in C and would be platform-specific most of the time. It's not a nice 
solution, but it's the only one I can think of at this time.
Unless someone comes up with a better idea _quickly_, I'll try it out 
and then report how ugly it really is... :-)

Cheers,

Wolfgang

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