Re: [HOpenGL] Re: OpenGL/GLUT examples crashing: known problem?

2005-04-09 Thread Glynn Clements

Claus Reinke wrote:

 Btw, is there a way to reset the opengl system to a sane state in 
 software? Or are there some invalid assumptions about default 
 state in the other examples?

If OpenGL is getting stuck in a non-functional state, that indicates
a bug in the driver.

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


RE: Process library and signals

2005-02-07 Thread Glynn Clements

Simon Marlow wrote:

  I think this covers most of the useful situations.  If you want to do
  the same thing in both parent and child, or handle in the parent and
  SIG_DFL in the child: use runProcess.  If you want to ignore in the
  parent and SIG_DFL in the child: use System.Cmd.{system,rawSystem}. 
  To handle in the parent and ignore in the child: unfortunately not
  directly supported.
  
  As it stands, you can have whatever behaviour you want in the parent:
  set the desired handling before calling system/rawSystem/runProcess
  then set it back afterwards.
  
  However, this will cease to be true for system/rawSystem if you change
  them so that the child restores the handlers to their state upon
  entry.
 
 I don't understand...  is there a typo somewhere above?  Perhaps you
 meant child in the first paragraph?

Sorry; I wasn't thinking straight. That part of my message is
incorrect; changing the signal handling before calling
system/rawSystem won't help, because they force both cases.

If they were changed to behave like system(), the caller could
determine the *child* behaviour, but that's prone to a race condition,
so I doubt that it would be useful in practice.

 system/rawSystem now behave almost exactly like system() in C.  The only
 difference is that you can't ignore SIGINT/SIGQUIT in the child, but I
 can fix that if necessary.

I'm not sure how much it matters; system() isn't really of much use
for real programs anyhow.

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


Re: Bug in touchForeignPtr?

2004-11-22 Thread Glynn Clements

Keean Schupke wrote:

  C exit routines aren't responsible for freeing OS resources; the OS
  is.
  
  The fact that the SysV IPC objects aren't freed on exit is
  intentional; they are meant to be persistent. For the same reason, the
  OS doesn't delete upon termination any files which the process
  created.

  
 Right, which is why if you want to clean up temporary files, or
 temporary semaphores the OS doesn't do it for you, and you
 need to put some routine inplace to do it (using at_exit)... It
 seems this is the only way to guarantee something gets run when
 a program exits for whatever reason.

There isn't any way to *guarantee* that something is run upon
termination. The program may be terminated due to SIGKILL (e.g. due to
a system-wide lack of virtual memory). If you run out of stack, you
may not be able to call functions to perform clean-up.

Also, if the program crashes, handling the resulting SIGSEGV (etc) is
likely to be unreliable, as the memory containing the resource
references may have been trashed. Calling remove() on a filename which
might have been corrupted is inadvisable.

Also, at_exit() isn't standard. atexit() is ANSI C, but that is only
supposed to be called for normal termination (exit() or return from
main()), not for _exit() or fatal signals.

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


Re: Is it safe to call getProcessExitCode more than once?

2004-10-28 Thread Glynn Clements

David Brown wrote:

Both [waitForProcess and getProcessExitCode] will throw
an exception if the process terminated on a signal.
  
  So if I terminate a process manually, I'll have to wait for
  the ExitCode to avoid a zombie process, and waiting for the
  ExitCode invariably throws an exception.
 
 It's just the way that Unix process management works.  I guess you have to
 catch the exception to handle it well.  This is part of the aspect that
 makes writing shells so complicated.

I think that Peter was referring primarily to the fact that the
Haskell interface to waitpid() throws an exception if the process
terminated due to a signal, not the fact that you have to reap
children to prevent the accumulation of zombies.

The C interface is that waitpid() (and similar) return a status code;
you can then use the macros from sys/wait.h to determine whether the
process terminated normally (e.g. via exit()) or abnormally (due to a
fatal signal), and to obtain either the exit code or the signal number
as appropriate.

The Haskell interface oversimplifies matters, making it easier to get
the exit code in the case of normal termination, but complicating the
handling of abnormal termination.

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


RE: Process library and signals

2004-10-27 Thread Glynn Clements

Simon Marlow wrote:

 So basically you're saying that if runProcess is to be used in a
 system()-like way, that is the parent is going to wait synchronously for
 the child, then the parent should be ignoring SIGQUIT/SIGINT.  On the
 other hand, if runProcess is going to be used in a popen()-like way,
 then the parent should not be ignoring SIGQUIT/SIGINT.

Exactly.

 The current
 interface doesn't allow for controlling the behaviour in this way.

Yep.

 So the current signal handling in runProcess is wrong, and should
 probably be removed.  What should we have instead?  We could implement
 the system()-like signal handling for System.Cmd.system only, perhaps.

Well, probably for system and rawSystem.

The problem, as I see it, is that the Process library is meant to be
both flexible and portable. If you don't need the portability, you
already have the primitives in System.Posix, and separate fork/exec
will inevitably provide more flexibility than an all-in one version.

If you provide system/rawSystem and runInteractive{Command,Process},
that's covered the most common cases (i.e. system() and popen()). So
what is runProcess for? If it doesn't do the signal handling, it's
only really suitable for popen-style usage.

Which is unfortunate; I can imagine a use for an intermediate
semi-raw system, which supports e.g. file redirection or even
command pipelines, but without using the shell (i.e. accepts the
argv[] individually). In particular, using the shell is risky if you
want to use untrusted data in the argument list (e.g. CGI programs).

If runProcess doesn't do the signal handling between the fork and the
exec, you can't change the child's signal handling after the exec. You
could change the signal handling of the parent (i.e. the current
process) before calling runProcess, let the child inherit it, then
change it back again after runProcess returns, but that gives rise to
a potential race condition.

One possibility would be to allow an extra argument of type IO () (or
Maybe (IO ()), where Nothing is shorthand for Just $ return ()) which
would be executed between the fork and the exec on Unix and ignored on
Windows. AFAICT, that would expose the full functionality available on
Unix without interfering with Windows usage or adding complexity.

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


Re: Is it safe to call getProcessExitCode more than once?

2004-10-27 Thread Glynn Clements

Peter Simons wrote:

   Both [waitForProcess and getProcessExitCode] will throw
   an exception if the process terminated on a signal.
 
 So if I terminate a process manually, I'll have to wait for
 the ExitCode to avoid a zombie process, and waiting for the
 ExitCode invariably throws an exception.
 
 Or do I misunderstand something?

No, that seems correct.

Although, depending upon the OS, setting SIGCHLD to SIG_IGN may cause
processes to be reaped automatically (i.e. not become zombies), so
that's a possible alternative.

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


Re: Is it safe to call getProcessExitCode more than once?

2004-10-26 Thread Glynn Clements

Peter Simons wrote:

 John Goerzen writes:
 
   Assuming it is based on wait() or one of its derivatives,
   and I suspect it is, you cannot call it more than once
   for a single process.
 
 That's what I _assume_, too, but a definite answer would be
 nice. 
 
 In the meanwhile, I have found out that it might not be safe
 to call it once, even:
 
   CaughtException waitForProcess: does not exist (No child processes)
 
 That's a child I _did_ start and which apparently terminated
 before I called waitForProcess. Shouldn't I be getting the
 exit code of that process rather than an exception?

I can think of two reasons why this might be happening:

1. SIGCHLD is being ignored (SIG_IGN); the Process library doesn't
appear to be doing this, but something else might.

2. Something else (e.g. the RTS) is handling SIGCHLD and reaping the
process automatically.

 Do waitForProcess and getProcessExitCode differ in their
 behavior other than that one blocks and other doesn't?

Both call waitpid(); getProcessExitCode uses WNOHANG, while
waitForProcess doesn't.

They differ in their handling of errors. waitForProcess will throw an
exception if waitpid() indicates any error (except EINTR, where it
just retries the waitpid() call), whereas getProcessExitCode will
return Nothing. Both will throw an exception if the process terminated
on a signal.

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


Process library and signals

2004-10-26 Thread Glynn Clements

Having looked at the latest version of the Process library, it appears
that my earlier comments about signal handling may have been
misinterpreted.

First, my comments regarding the handling of SIGINT/SIGQUIT were
specific to system(). The C system() function ignores these signals in
the parent while the child is executing. However, this doesn't
necessarily apply to other functions; e.g. popen() doesn't ignore
these signals, and runProcess probably shouldn't either.

With system(), the parent blocks until the child is finished, so if
the user presses Ctrl-C to kill the currently executing process,
they probably want to kill the child. If the parent wants to die on
Ctrl-C, it can use WIFSIGNALED/WTERMSIG to determine that the child
was killed and terminate itself.

OTOH, with popen(), the parent continues to run alongside the child,
with the child behaving as a slave, so the parent will normally want
to control the signal handling.

Ideally, system() equivalents (e.g. system, rawSystem) would ignore
the signals in the parent, popen() equivalents (e.g. 
runInteractiveProcess) wouldn't, and lower-level functions (e.g. 
runProcess) would give you a choice.

Unfortunately, there is an inherent conflict between portability and
generality, as the Unix and Windows interfaces are substantially
different. Unix has separate fork/exec primitives, with the option to
execute arbitrary code between the two, whilst Windows has a single
primitive with a fixed set of options.

Essentially, I'm not sure that a Windows-compatible runProcess would
be sufficiently general to accurately implement both system() and
popen() equivalents on Unix. Either system/rawSystem should be
implemented using lower-level functions (i.e. not runProcess) or
runProcess needs an additional option to control the handling of
signals in the child.

Also, my comment regarding the signals being reset in the child was
inaccurate. system() doesn't reset them in the sense of SIG_DFL. It
sets them to SIG_IGN before the fork(), recording their previous
handlers. After the fork, it resets them in the child to the values
they had upon entry to the system() function (i.e. to the values they
had before they were ignored). The effect is as if they had been set
to SIG_IGN in the parent after the fork(), but without the potential
race condition.

Thus, if they were originally ignored in the parent before system()
was entered, they will be ignored in the child. If they were at their
defaults (SIG_DFL) before system() was entered, they will be so in the
child. If they had been set to specific handlers, system() will
restore those handlers in the child, but then execve() will reset them
to SIG_DFL, as the handler functions won't exist after the execve().

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


Re: ANNOUNCE: GHC version 6.2.2

2004-10-15 Thread Glynn Clements

Simon Marlow wrote:

=
 The (Interactive) Glasgow Haskell Compiler -- version 6.2.2
=
 
 The GHC Team is pleased to announce the latest patchlevel release of
 GHC, 6.2.2.  This is a bugfix release only, there are no new features.
 Code that worked with 6.2.1 will work unchanged with 6.2.2.

Should it be possible to obtain this via CVS? My attempts to update
from 6.2.1 with cvs update -r ghc-6-2-2 ... fail with:

cvs [server aborted]: cannot write /cvs/CVSROOT/val-tags: Read-only file system

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


Re: newCString -- to 'free' or not?

2004-09-25 Thread Glynn Clements

Peter Simons wrote:

 When I create a CString with Foreign.C.String.newCString, do
 I have to 'free' it after I don't need it anymore? Or is
 there some RTS magic taking place?
 
 How about Foreign.Marshal.Utils.new and all those other
 newXYZ functions? 

Yes. The new* functions allocate the memory with malloc, and you have
to free it yourself. OTOH, the with* functions allocate the memory
with alloca, and it is freed automatically.

Also, a ForeignPtr includes a finaliser which will free the data
automatically when it is no longer referenced.

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


RE: Network, sClose

2004-08-13 Thread Glynn Clements

Simon Marlow wrote:

  OTOH, the core problem with Network.recvFrom is essentially that it
  appears to be a misguided attempt to provide a symmetric counterpart
  to Network.sendTo. While the low-level sendTo/recvFrom functions may
  be roughly symmetric, at a higher level, the client and server ends of
  a connection aren't at all symmetric.
 
 Yes, I'm sure that's the reason for it.  Proposals for a replacement are
 welcome...

What would be the intended purpose of a replacement?

If you want a simpler interface for writing servers, it would probably
look something like:

doServer :: PortID - (Handle - IO ()) - IO ()
doServer port handler = do
s - listenOn port
let doIt = do
~(s', _)  -  Socket.accept s
h - socketToHandle s' ReadWriteMode
forkIO $ handler h  hClose h
sequence_ $ repeat doIt

Ultimately, you either need to create a separate thread/process per
connection, or manually service multiple connections (select/poll). A
server which processed connections sequentially wouldn't be of much
practical use (and a one-shot server probably wouldn't even be of use
for toy programs).

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


RE: Network, sClose

2004-08-11 Thread Glynn Clements

Bayley, Alistair wrote:

  However, even if sClose was exported, that wouldn't be of any 
  help in Jon's case, as neither of the sockets which recvFrom 
  creates are visible outside of recvFrom.
 
 Ahh, OK. I haven't used recvFrom/sendTo yet... (trying it now) ... When I
 try Jon's example with 6.2.1 (Win XP) I don't get the same error; it works
 twice and then hangs (my networking code would hang if I tried to re-use a
 socket that hadn't been properly closed).

Odd.

 Is recvFrom meant to be a one-shot function i.e. the socket is only closed
 when the process exits?

The implementation is:

 recvFrom host port = do
  ip  - getHostByName host
  let ipHs = hostAddresses ip
  s   - listenOn port
  let 
   waiting = do
  ~(s', SockAddrInet _ haddr)  -  Socket.accept s
  he - getHostByAddr AF_INET haddr
  if not (any (`elem` ipHs) (hostAddresses he))
   then do
  sClose s'
  waiting
   else do
   h - socketToHandle s' ReadMode
 msg - hGetContents h
 return msg
 
  message - waiting
  return message

Note that the listening socket s is passed to accept then forgotten
about. If it was accessible, it would be possible to either accept
further connections on it, or to close it. As it stands, it will
remain open and unused for the duration of the calling process.

A subsequent call to recvFrom would call listenOn again, attempting to
create another listening socket on the same address and port. 
Obviously, that should fail so long as the original socket still
exists (the kernel doesn't know that the original socket can't ever be
used again).

 Jon's second example uses listenOn/accept and handles, which is also what I
 used:
 
 do sock - listenOn$PortNumber 7607; (hdl,host,port)- accept sock; 
  s-IO.hGetContents hdl; putStr$s; IO.hClose hdl; Network.Socket.sClose 
  sock
 
 Network.Socket.sClose is obviously useful here, so don't you think it would
 be a good idea to put it in Network? I don't see why including sClose would
 imply that you should start exposing other low-level stuff. AFAICT, it is
 the one little thing that's missing from Network that makes writing simple
 networking code possible.
 
 There's a lack of symmetry (closure?): you can create a socket with
 Network.listenOn, but there is no corresponding close function in Network.

Right. If listenOn and accept are in Network, sClose should be in
there too. That would at least provide an API which is usable for the
simplest programs.

OTOH, the core problem with Network.recvFrom is essentially that it
appears to be a misguided attempt to provide a symmetric counterpart
to Network.sendTo. While the low-level sendTo/recvFrom functions may
be roughly symmetric, at a higher level, the client and server ends of
a connection aren't at all symmetric.

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


Re: Network, sClose

2004-08-11 Thread Glynn Clements

Jon Fairbairn wrote:

   Is recvFrom meant to be a one-shot function i.e. the socket is only closed
   when the process exits?
  
  The implementation is:
  
   recvFrom host port = do
ip  - getHostByName host
let ipHs = hostAddresses ip
s   - listenOn port
let 
 waiting = do
~(s', SockAddrInet _ haddr)  -  Socket.accept s
he - getHostByAddr AF_INET haddr
if not (any (`elem` ipHs) (hostAddresses he))
 then do
sClose s'
waiting
 else do
 h - socketToHandle s' ReadMode
   msg - hGetContents h
   return msg
   
message - waiting
return message
 
 This is rather more powerful than recvFrom in C, isn't it?

Yes, very much so.

 Perhaps it's misnamed: C's recvFrom deals with finite
 messages, but with the above I can receive an infinite list,
 which is the source of the problem, even if rather cool.

Well, C's recvfrom is normally only used with UDP, where you deal with
individual packets rather than connections. It's essentially recv()
but with the ability to retrieve the packet's source IP+port as well
as its payload. And recv() is just read() with some flags.

  Note that the listening socket s is passed to accept then
  forgotten about. If it was accessible, it would be
  possible to either accept further connections on it, or to
  close it. As it stands, it will remain open and unused for
  the duration of the calling process.
 
 So the problem is the same as with hGetContents in general,
 compounded by the calling programme not having access to the
 socket, so it can't close it even if it knows it's finished
 with the data.

No, it's worse than that. There are two sockets involved (the
listening socket plus the connection-specific socket), and you don't
get access to either of them.

AFAIK, you can live without the connection socket, provided that you
consume all of the data, and the connection is purely one-way (i.e. 
the client sends the data then closes the connection; it doesn't
expect the recipient to close its end).

The real problem is that the listening socket hangs around, tying up
the port. Actually, recvFrom should be able to close the listening
socket as soon as it has accepted the connection.

  Right. If listenOn and accept are in Network, sClose should be in
  there too. That would at least provide an API which is usable for the
  simplest programs.
 
 Agreed, and recvFrom seems to need to be something else,
 though the problem could be ameliorated by making
 withSocketsDo close
 any leftover sockets. You'd then have to use it for both
 Linux and Windows.

It would have to only close the sockets which were created via the
Haskell networking code. You wouldn't want it to close e.g. an X11
connection which Gtk+Hs/GLUT/etc were using, or stdin if that happened
to be a socket.

  OTOH, the core problem with Network.recvFrom is
  essentially that it appears to be a misguided attempt to
  provide a symmetric counterpart to Network.sendTo. While
  the low-level sendTo/recvFrom functions may be roughly
  symmetric, at a higher level, the client and server ends
  of a connection aren't at all symmetric.
 
 Given that, recvFrom could :: HostName - Socket - IO
 String.  We'd have to call listenOn to get the socket, but
 that seems a small hardship compared to losing the use of
 the port.

If anything, it should probably just be:

recvFrom :: Socket - IO String

The behaviour of discarding connections until it gets one from the
specified hostname seems rather arbitrary, IMHO.

The more I think about it, the more that Network.recvFrom looks like
someone was hell-bent on producing a complement to Network.sendTo,
regardless of the benefit (or even sanity) of doing so.

Actually, if someone desperately wants a complement to sendTo, a
recvTo function would be more useful than recvFrom. I.e. connect to a
server and read data until the server closes the connection (usable
with services such as systat, netstat, daytime etc).

Similarly, sendFrom (i.e. accept a connection and send data) would be
just as useful as recvFrom.

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


Re: Network, sClose

2004-08-10 Thread Glynn Clements

Jon Fairbairn wrote:

 I just got myself a copy of ghc-6.2.1 and was idly
 experimenting with Network in ghci.

 Unfortunately a second attempt is not so happy:
 
Prelude System.Posix Network do r - recvFrom localhost$ PortNumber 9090; 
 putStr r
*** Exception: bind: resource busy (Address already in use)
 
 According to the documentation there's some mention of
 Address already in use on this mailing list, but I
 couldn't find it -- I thought there used to be searchable
 archives of the mailing lists, but I couldn't find those
 either and resorted to google.
 
 A little experimentation revealed that:
 
do sock - listenOn$PortNumber 7607; (hdl,host,port)- accept sock; 
 s-IO.hGetContents hdl; putStr$s; IO.hClose hdl; Network.Socket.sClose sock
 
 is nicely repeatable. The following questions arise:
 
 * Shouldn't recvFrom call sClose itself?

recvFrom can't close the socket until the data has been consumed.

 * If not, how should one clean up after using recvFrom?

You can't; once recvFrom returns, there's no way to get at the
listening socket (or, for that matter, the connection socket).

 * Shouldn't sClose be reexported from Network?

Once you start down that route, you end up at the inevitable
conclusion that everything from the raw syscall imports upwards needs
to be re-exported.

 * is there a general way to get ghci out of a state where
   it's got stuff open on inaccessible sockets?

The solution to most problems with the Network module is not to use
the Network module, but to use Network.Socket instead.

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


RE: Socket Options

2004-06-28 Thread Glynn Clements

Simon Marlow wrote:

 The Linux socket(7) man page seems to say that you can't set SO_RCVTIMEO
 or SO_SNDTIMEO on Linux (but perhaps you can with a 2.6 kernel?).

I suspect that the manual page may be outdated. 2.4 implements those
options; at least, setsockopt stores the value in the struct sock,
and getsockopt reads it from there, although I haven't checked whether
specific protocols honour those settings.

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


Re: Socket Options

2004-06-25 Thread Glynn Clements

Peter Simons wrote:

 the Network module provides the data type SocketOption. I am
 particularly interested in setting the RecvTimeOut and
 SendTimeOut values, but I wonder how to set them. The
 function
 
   setSocketOption :: Socket - SocketOption - Int - IO ()
 
 allows me only 'Int' parameters, but the kernel expects a
 struct timeval here -- or more accurately, a pointer to one.
 Do I really have to engage in FFI pointer wizardry here, or
 is there a simpler way to set these values?

You can't set the send/receive timeouts using that function; it always
passes a C int (with the optlen parameter set to sizeof(int)). You
would have to re-write it with a more flexible interface, e.g.:

 import Foreign
 import Foreign.C
 import Network.Socket hiding (setSocketOption)
 
 foreign import CALLCONV unsafe setsockopt
   c_setsockopt :: CInt - CInt - CInt - Ptr () - CInt - IO CInt
 
 setSocketOption :: (Storable a) = Socket 
   - SocketOption -- Option Name
   - a-- Option Value
   - IO ()
 setSocketOption (MkSocket s _ _ _ _) so v = do
with v $ \ptr_v - do
throwErrnoIfMinus1_ setSocketOption $
c_setsockopt s (socketOptLevel so) (packSocketOption so) (castPtr ptr_v)
 (fromIntegral (sizeOf v))
return ()

Note: neither socketOptLevel nor packSocketOption are exported from
Network.Socket, so you would need to copy those (or just pass a pair
of integers instead of the SocketOption).

 Am I even supposed to set them, or is there a better way to
 specify general I/O timeouts than on the socket level?

Non-blocking I/O and select/poll; although I don't know how well that
is supported.

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


Re: Glasgow Haskell on different versions of Linux

2004-06-09 Thread Glynn Clements

Volker Stolz wrote:

   What is ctype.h good for?
 
  A good question.  Its only use seems to be in
  ghc/rts/RtsFlags.c where it is used for functions
  like isdigit and isspace for decoding the RTS flags.
  Maybe it should be retired altogether.
 
  I'm rather puzzled how this works if ctype.h isn't
  there at all, as it seems to.
 
 The functions are C89, so they should be present *somewhere* in libc
 anywhere.

Actually, in GNU libc, isspace, isdigit etc are usually macros which
read a flag word from the __ctype_b array then and it with the
corresponding attribute mask.

  extern __const unsigned short int *__ctype_b; /* Characteristics.  */
  ...
  #define   __isctype(c, type) \
(__ctype_b[(int) (c)]  (unsigned short int) type)
  ...
  # define isdigit(c)   __isctype((c), _ISdigit)
  ...
  # define isspace(c)   __isctype((c), _ISspace)

However, glibc does export functions with those names, and you can
disable the macros by defining the __NO_CTYPE macro, with the result
that the binary depends upon isspace, isdigit etc rather than
__ctype_b.

I don't have glibc 2.3 here, but presumably __ctype_b has changed in
an incompatible manner (maybe there are more than 16 flags in 2.3, in
which case an unsigned short would no longer be sufficient).

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


Re: Statically linked binary?

2004-05-21 Thread Glynn Clements

Jochen L. Leidner wrote:

 sorry for an urgent newbie question: how can I create a statically 
 compiled version of a Haskell program on Linux with GHC that does not rely 
 on external shared libs (also for any of its libraries it uses)?

Possibly with a great deal of difficulty, depending upon which
functions you need to use.

GNU libc 2.x dynamically loads shared libraries (with dlopen()) for
various database lookups (passwd, group, hosts etc). This applies
even when using a static libc (libc.a).

If you need to call (directly or indirectly) any of the functions
which use this mechanism, then you have to either:

a) have (the correct versions of) the relevant libnss_*.so libraries
installed on the target system, or

b) you have to compile your own libc.a using the --enable-static-nss
switch.

The most common functions which require this mechanism are those which
access the passwd database (getpwnam, getpwuid, etc) and those which
perform hostname/domain lookups (gethostbyname etc). Even if you don't
use these functions directly from your program, the libraries which
you use might use them. E.g.:

+ X needs to resolve the hostname part of $DISPLAY, so anything
which uses X is affected.

+ Anything which supports the ~user syntax to refer to a specific
user's home directory will need to use getpwnam().

+ Anything which needs to translate between UIDs and usernames will
need to use getpwnam() and/or getpwuid().

+ Etc.

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


Re: Problem with ghc on Windows ME

2004-01-29 Thread Glynn Clements

C.Reinke wrote:

 Therefore, my suggestion would be to keep the rawSystem from
 ghc-6.0.1 (which doesn't seem to do any interpretation?), and
 to provide a system-specific escape function
 
   System.Cmd.escape :: String - String - String
   -- (System.Cmd.escape chars string) escapes occurrences of 
   -- chars in string, according to convention on the current
   -- system
 
 If really necessary, there could be a convenience function
 somewhat like:
 
   -- try to do the right thing
   System.Cmd.rawSystem' :: String - [String] - IO ExitCode
   System.Cmd.rawSystem' path args =
 rawSystem $ concat (path:[' ':(escape \\\ a) | a - args])

That sounds is if it makes sense, but it doesn't. At least, not on
Unix. On Unix, there are two basic options for invoking another
program:

1. Use the shell, i.e. system(). Pass a single string which will
undergo all of the various forms of processing which the shell
performs.

2. Don't use the shell. Pass a list of strings which become the
argv[i] of the called program.

If you don't want any processing, the correct solution is to bypass
the shell altogether, *not* to attempt to subject the string to an
inverse transformation in the hope that the shell will eventually end
up passing the desired argv[i] to the called program.

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


Re: POpen, opening lots of processes

2004-01-10 Thread Glynn Clements

Mark Carroll wrote:

Your code looks great, but where do you find the library documentation,
 like what the arguments for executeFile are all about? (I'd guessed the
 Maybe thing was an environment, but what's the Bool?) I've been trying to
 do similar stuff, but have been stumbling in the dark rather.

Source code (hslibs/posix/PosixProcPrim.lhs):

executeFile :: FilePath -- Command
- Bool -- Search PATH?
- [String] -- Arguments
- Maybe [(String, String)] -- Environment
- IO ()
executeFile path search args Nothing = do
[snip]
if search 
   then throwErrnoIfMinus1_ executeFile (c_execvp s arr)
   else throwErrnoIfMinus1_ executeFile (c_execv s arr)

executeFile path search args (Just env) = do
[snip]
if search 
   then throwErrnoIfMinus1_ executeFile (c_execvpe s arg_arr env_arr)
   else throwErrnoIfMinus1_ executeFile (c_execve s arg_arr env_arr)

IOW:

search  env function

False   Nothing execv
TrueNothing execvp
False   Just _  execve
TrueJust _  execvpe [*]

[*] execvpe() isn't a standard library function; it is implemented in
hslibs/posix/cbits/execvpe.c using execve().

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


Re: POpen, opening lots of processes

2004-01-08 Thread Glynn Clements

Hal Daume III wrote:

 I'm using POpen to shell out to a command several hundreds or thousands of 
 times per call (none of them simultaneous, though, this is completely 
 serial).  After running my program for a while, I get:
 
 Fail: resource exhausted
 Action: forkProcess
 Reason: Resource temporarily unavailable
 
 which basically seems to be telling me that the program hasn't been 
 closing the old processes, even though they're definitely not in use 
 anymore.
 
 Does anyone have any suggestions how to get around this?

I note two facts regarding POpen.popen:

1. There is no corresponding pclose function.
2. It uses lazy I/O (hGetContents).

Also, I can't see wait/waitpid getting called anywhere (although there
might be other mechanims involved, e.g. SIGCHLD handlers; I haven't
looked that closely).

What does the output from ps indicate?

If you have any live processes (S or R state), it's probably because
the process' output hasn't been consumed, so the program hasn't
exit()ed yet. OTOH, if you have zombies (Z state), the program has
terminated but the parent (your program) hasn't called wait/waitpid
(the Haskell interface is getProcessStatus, getProcessGroupStatus or
getAnyProcessStatus).

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


Re: POpen, opening lots of processes

2004-01-08 Thread Glynn Clements

Hal Daume III wrote:

  What does the output from ps indicate?
 
 It lists all the processes as defunct:
 
 19981 pts/5Z  0:00 [suffixtree defunct]
 19982 pts/5Z  0:00 [suffixtree defunct]
 19983 pts/5Z  0:00 [suffixtree defunct]
 19984 pts/5Z  0:00 [suffixtree defunct]
 19985 pts/5Z  0:00 [suffixtree defunct]
 ...
 
  If you have any live processes (S or R state), it's probably because
  the process' output hasn't been consumed, so the program hasn't
  exit()ed yet. OTOH, if you have zombies (Z state), the program has
  terminated but the parent (your program) hasn't called wait/waitpid
  (the Haskell interface is getProcessStatus, getProcessGroupStatus or
  getAnyProcessStatus).
 
 I don't mind evaluating the contents returned strictly, but I can't figure 
 out how to force the process into a dead state...I don't see how any of 
 these three functions accomplishes that...what am I missing?

A zombie process (such as the above) is a process which has
terminated but which can't actually be removed from the system's
process table until the parent has retrieved its exit status.

That's where getProcessStatus etc (wait/waitpid at the C level) come
in; these functions block until a suitable[1] process has terminated,
and return its exit status. After which, the process can finally be
deleted (this is termed reaping).

[1] getProcessStatus waits for a specific process,
getProcessGroupStatus waits for any process in a specific process
group, and getAnyProcessStatus waits for any child process.

So, you probably want something like:

do
(stdout, stderr, pid) - popen cmd args (Just input)
-- consume stdout + stderr, e.g.:
writeFile /dev/null stdout
writeFile /dev/null stderr
getProcessStatus True False pid

You need to ensure that the output is consumed before calling
getProcessStatus, otherwise getProcessStatus will block indefinitely
(i.e. deadlock).

IMNSHO, this is one area where lazy I/O sucks even more than usual. 
It's bad enough having it tie up descriptors, let alone processes.

It probably works fine for simple, stupid programs, which spawn a
handful of child processes (which they don't bother to reap) and then
terminate shortly thereafter (a process whose parent has terminated is
adopted by the init process, which can be relied upon to reap it
when it terminates).

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


Re: DiffArray Performance

2003-11-07 Thread Glynn Clements

Stefan Reich wrote:

  DiffArray is an example of a good use for unsafePerformIO: it uses
  imperative operations to implement a pure API.  The DiffArray is made of
  mutable objects under the hood, but as far as the programmer is
  concerned it behaves just like a pure Array.
 
 I'd like to ask a general question about unsafePerformIO: What exactly 
 does unsafe mean? Just impure or rather may lead to all kinds of 
 problems, you better don't use this?

Essentially both. Haskell assumes purity (referential transparency),
so impurity is likely to result in all kinds of problems.

If you think of the IO monad as a state transformer, i.e.

IO a = World - (World, a)

unsafePerformIO basically applies the transformation to whichever
World value happens to be available at the time (i.e. the current
system state, where current is unspecified), and that depends upon
the details of the evaluation mechanism.

Using unsafePerformIO is safe if the transformer generates the same
result result for all possible World values. If it generates different
results for different World values, you risk running into problems.

Note: even if you are willing to accept one of many possible valid
values, you need to allow for the fact that the expression may be
evaluated multiple times. E.g. if you have:

let x = unsafePerformIO foo

where foo may produce different values, you could find that x /= x.

The opposite problem is also possible, i.e. that distinct occurrences
of the same expression could be merged. A common example is in
attempting to create global variables:

x, y :: IORef Int
x = unsafePerformIO $ newIORef 0
y = unsafePerformIO $ newIORef 0

Due to optimisation, x any y may end up referring to the same IORef.

In short: Haskell assumes referential transparency; if you break it,
all bets are off.

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


Re: Transmitting Haskell values

2003-10-29 Thread Glynn Clements

Peter Simons wrote:

 Joachim Durchholz writes:
 
   What sent me first into deep confusion is that I found all of
   {Text,GHC}.{Read,Show} first, and the Read classes marked as
   nonportable GHC extensions.
 
 Then you will surely love the Foreign.* hierarchy, most notably
 Foreign.Storable. If you want to do binary I/O within standard
 Haskell, this is the place to look at. I found [1] to be a pretty good
 introduction to the subject.

The problem with Storable is that the representation is
architecture-specific. It isn't suitable for implementing a
commodity protocol which can be used for communication between
different architectures.

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


Re: Transmitting Haskell values

2003-10-29 Thread Glynn Clements

Joachim Durchholz wrote:

  The problem with Storable is that the representation is
  architecture-specific. It isn't suitable for implementing a
  commodity protocol which can be used for communication between
  different architectures.
 
 Just endianness issues, or are there deeper differences?

There could also be differences in the sizes of integral types
(particularly CLong) or other format differences (e.g. use of
something other than IEEE 754 format for FP types).

 If it's just endianness, it should be relatively easy to get that sorted 
 out, either via wrappers around the networking functions, or by 
 extending Storable itself (well, it's probably a bit too early for me to 
 try this, but there's a good chance that it will be at least one of 
 generally useful and instructive *g*).

The problem there is that you can't write a generic function which
handles any instance of Storable. Each specific type would have to be
handled separately, depending upon whether swapping is required and,
if so, whether bytes are swapped in blocks of 2, 4, or 8 bytes. Also a
32-bit float might use a different byte order to a 32-bit int (so says
a comment in glibc's endian.h).

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


Re: passing a Handle to a C function

2003-07-09 Thread Glynn Clements

Hal Daume wrote:

 I have a C function that, for simplicity, has its definition as
 something like:
 
  void myCFun(FILE *fd);
 
 I have a Handle I've opened in Haskell using openFileEx and would like
 to pass this to the function.

GHC's Handle type is based upon a descriptor rather than a FILE*, so
you will have to manufacture the FILE*, e.g. with fdopen().

 I've tried a bunch of things, the most
 recent being:
 
  foreign import ccall myHFile.h myCFun c__myCFun :: Ptr CInt - IO ()
  myCFun :: Handle - IO ()
  myCFun (FileHandle handleMV) = do
h__ - readMVar handleMV
ptr - malloc
poke ptr (toCInt $ haFD h__)
c__initVars ptr
 
 i've also tried it with just CInt - IO (), without the ptr, but that
 doesn't work either.
 
 Surely someone has done this at some point...or is it even possible
 (please say it is)...

For Unix, use Posix.handleToFd to get a descriptor, then fdopen() (in
C, or write a foreign import) to get a FILE*.

Also, don't forget about synchronisation issues between the C and
Haskell interfaces to the descriptor (e.g. buffering).

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


Re: Sending wide characters over the network socket

2003-07-05 Thread Glynn Clements

Dimitry Golubovsky wrote:

 I have tried to send a string of Unicode characters over a socket (or to 
 write it into a file handle). The result is strange: it looks like 
 characters are truncated down to their least significant bytes.

Yep.

 Honestly, I expected that 20 bytes were sent (or something smaller if 
 they were sent in UTF), and Received be identical to Source was. The 
 last string of output is just to check whether those are indeed lower 
 bytes shown, not some garbage.
 
 I am using a binary distribution of GHC 6.0 on Linux - are there any 
 special conditions I have to enable for the source distribution to be 
 able to send/receive Unicode characters?

No, it just isn't supported. All of the Haskell I/O functions take the
bottom octet and discard the top bits.

 To be more general: how would I send arbitrary binary data (stream of 
 octets) over a socket or a file handle? Should I always assume that only 
 lower bytes would be sent, and this will be forever in ghc?

Yes. Well, maybe not forever, but for the forseeable future.

 Or is it a bug?

No. It's just a fundamental design flaw in Haskell. Presumably someone
thought that wide-character support was just a question of defining
Char, and forgot about a minor issue called I/O.

 The problem is, Handle/Socket functions require a String to be the type 
 of data to exchange; not a, say [Int8]. Therefore, I need to be able to 
 coerce my binary data buffer to a String.

Correct. IOW, lots of messing around with ord and chr and either
mod/div or the Bits library.

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


Re: emacs haskell-ghci mode hook

2003-01-08 Thread Glynn Clements

Christian Maeder wrote:

  C-x ` is jump to next compile error which can be used to navigate through
  errors produced from tests (depending on the error format).
 
 This looks like some work or am I missing some .el files? I'm no ELisp 
 programmer.

This functionality is provided by compile.el:

C-x ` runs `next-error'

`next-error' is an interactive compiled Lisp function
  -- loaded from compile

  Also, haskell-mode has several useful extensions like fume that aren't
  immediately obvious before reading the docs or using C-h m (or C-h b).
 
 What is fume? C-h m did not reveal any surprises to me.I only use the 
 recommended setup:

AKA func-menu.el:

`function-menu' is an interactive autoloaded Lisp function
  -- autoloads from func-menu

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



Re: re-opening a closed stdin?

2002-11-21 Thread Glynn Clements

Bernard James POPE wrote:

 There's probably a really obvious answer to this, but I can't find it.
 
 Is there any way in GHC to reopen stdin if it has been closed?
 
 You may wonder why I'd want this. Well I'm writing a debugger
 for Haskell 98 (*) and my debugger wants to do some interaction on the terminal
 _after_ the user's program has run. If the user's program puts stdin into
 a closed or semi-closed state then that causes trouble for my debugger.
 
 What I'd like to do is close stdin after the end of the user's program,
 flush any input waiting in the buffer, then reopen it fresh for reading.
 
 If this can't be easily done perhaps there is another solution you can think
 of.

As others have pointed out, you can (on Unix at least) duplicate the
underlying descriptor. However, this may affect the semantics of
closing that descriptor (e.g. a TCP socket isn't closed at the TCP
layer until *all* corresponding descriptors have been closed).

Also, you can't (AFAICT) re-assign Haskell's stdin globally operation
in the manner of ANSI C's freopen(), although you can re-assign it
locally using IOExts.withStdin.

If you need to really close stdin (i.e. you can't duplicate the
descriptor), it may not be possible to reopen it, e.g. if it is an
unnamed pipe, a file which has since been deleted, a socket etc. Even
if it is technically possible, you may not always be able to determine
exactly how to reopen it, e.g. if it was a file, what was its
pathname? However, for the specific case of a terminal on Unix, you
can use Posix.getTerminalName; re-opening that will typically work.

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



Re: Problem with Data.Dynamic

2002-10-25 Thread Glynn Clements

Martin Sjögren wrote:

 I have a problem with Data.Dynamic. The problem is probably that I don't
 understand it. From my understanding, the following program should work:
 
 -8
 import Data.Dynamic
 
 data Foo = Foo { x :: Int }
 deriving Show
 
 instance Typeable Foo where
 typeOf _ = mkAppTy (mkTyCon Foo.Foo) []
 
 
 main = do
 let dynObj = toDyn $ Foo 42
 print dynObj
 let Just obj = fromDynamic dynObj :: Maybe Foo
 print obj
 -8
 
 But when I compile it (ghc Foo.hs) and run it (./a.out) I get:
 
 Foo.Foo
 
 Fail: Foo.hs:13: Irrefutable pattern failed for pattern (Data.Maybe.Just
 obj)
 
 Which indicates that fromDynamic returned Nothing. What is the problem
 here? Do I have to employ special trickery to use Dynamic with records?

You have to ensure that the TyCon is unique. A comment in Dynamic.hs
says:

-- | Builds a 'TyCon' object representing a type constructor.  An
-- implementation of Data.Dynamic should ensure that the following holds:
--
--   mkTyCon a == mkTyCon a
--
-- NOTE: GHC\'s implementation is quite hacky, and the above equation
-- does not necessarily hold.  For defining your own instances of
-- 'Typeable', try to ensure that only one call to 'mkTyCon' exists
-- for each type constructor (put it at the top level, and annotate the
-- corresponding definition with a @NOINLINE@ pragma).

If you use:

fooTc = mkTyCon Foo.Foo

instance Typeable Foo where
typeOf _ = mkAppTy fooTc []

or compile with -O, your program works.

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



RE: IO-System

2002-09-17 Thread Glynn Clements


Simon Marlow wrote:

  I'd settle for that kind of indiscriminate flushing -- as is, 
  trivial I/O examples such as
  
  main = do
 putStr What is your name? 
 ls - getLine
 putStrLn (Hello  ++ ls ++ !)
  
  fail to behave as expected.
 
 That depends on what you expect... :-)  The Haskell report says nothing
 about triggering a flush on stdout when reading from stdin.
 
 I disagree that introducing this ad-hoc flush would be the right thing.
 A workaround for a common misconception, yes; but not the right thing in
 general.  IMHO, it's better that programmers learn about buffering early
 because they'll get bitten by it later on anyhow.
 
 Suppose we were to implement this, when exactly should it be enabled?
 All the time?  When stdin is a terminal?  When stdin and stdout are both
 connected to the same terminal?  For every output handle connected to
 the same terminal as stdin?  Should it happen for a socket too?  (if
 not, won't that be confusing for users?)

AFAICS, the only non arbitrary policies would be:

a) never, and

b) whenever the equivalent ANSI C functions would flush; i.e. flush
all buffered output streams whenever a read from an input stream
cannot be satisfied from the buffer and is passed down to the OS. For
unbuffered input streams, this applies to all reads.

Either of these approaches will confuse some set of users. Anything
other than disabling buffering altogether will confuse users who are
completely unaware of buffering.

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



Re: instances of Typable

2002-07-25 Thread Glynn Clements


Hal Daume III wrote:

 if I have
 
 newtype Foo = Foo Int
 
 and i want to make it an instance of typeable, how do I create a TypeRep
 object?

fooTc :: TyCon
fooTc = mkTyCon Foo

instance Typeable Foo where
typeOf _ = mkAppTy fooTc []

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