RE: turn off let floating

2004-04-30 Thread Simon Marlow
On 29 April 2004 10:17, David Sabel wrote:

 You could try out that theory by copying the definition of
 unsafePerformIO into your code, and putting an INLINE pragma on it. 
 I think it's safe to do this in your case (it's not safe in general).
 
 That's interesting for me, in which situations isn't it safe to inline
 the definition of unsafePerformIO?

We try to maintain the invariant that the IO action that is the argument
to unsafePerformIO is atomic, in the sense that it is either completely
performed or not performed when the application of unsafePerformIO is
evaluated (ignoring exceptions).  If we let the compiler inline
unsafePerformIO, then the compiler would sometimes be able to share part
of the IO computation amongst multiple instances, because it can see
that the first action is applied to the realWorld# constant.

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


Re: turn off let floating

2004-04-29 Thread David Sabel
Hi,


  Results:
  
 method  runtime (s)
 ---
 pure0.7
 ffi 3.2
 fastMut 15
 ioref   23
 
 I very strongly suspect that it is the unsafePerformIO that hurts
 performance in the fastMut case.  Otherwise this case would be around
 the same speed as the FFI example, perhaps faster.
 
 You could try out that theory by copying the definition of
 unsafePerformIO into your code, and putting an INLINE pragma on it.  I
 think it's safe to do this in your case (it's not safe in general).

That's interesting for me, in which situations isn't it safe to inline
the definition of unsafePerformIO? 

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


Re: turn off let floating

2004-04-20 Thread Bernard James POPE
On Thu, Apr 15, 2004 at 10:43:22AM -0700, Carl Witty wrote:
   However, if you have any suggestions about how to make a FAST 
   global counter
   I would be very glad to hear it. From profiling it seems like 
   this code
   is a little expensive (also it is called quite frequently).
  
  You could try the FastMutInt module from GHC
  (ghc/compiler/utils/FastMutInt.hs) to speed things up.  Unfortunately
  unsafePerformIO has some unavoidable overhead: it can't be inlined
  because we don't want the compiler to see its definition.
 
 What happens if you use the FFI to call a C function like
 int getCount() { static int x; return x++; }
 and mark the function pure (outside the IO monad) and noinline? 
 (Probably all the calls get commoned up and it only gets called once;
 but it might be worth a try).

Hi all,

To test out the various possible ways of implementing a global counter
I wrote some test cases (shown below). I hope the test cases are
useful, and provide some indication of the relative performance.
However, if you spot something bogus please let me know.

Each program computes the equivalent of:

sum ([1..1] :: [Int]) 

There are four different ways that I tried:

   1) pure: this is just pure functional code and should be fast. 
  This test case is only here as a control example, it is not
  a candidate solution because I need a global counter.
 
   2) ioref: this uses a global mutable counter using IORefs and
  unsafePerformIO

   3) fastMut: this uses the fast mutable integer library from GHC
  that was suggested by Simon Marlow.

   4) ffi: this implements the counter in C using the FFI.

They all run in a reasonable amount of memory so I won't report the
memory information here, just total runtime, as computed by the
unix time command.

Results:

   method  runtime (s)
   ---
   pure0.7
   ffi 3.2
   fastMut 15
   ioref   23  

Note each program was compiled with ghc 6.2 with -O2 on debian linux.

One caveat is that the ffi code keeps the counter in C until the very end
of the program. This doesn't reflect the fact that I want to put each
value of the counter into a Haskell data structure, so there should be
an additional cost of turning the C int back into a Haskell Int for every
increment. I'll need to write a different test case for this aspect.

Here are the programs in the same order that they appear in the results table:



   {- pure -}

   module Main where

   main = print $ loop 1 0

   loop :: Int - Int - Int
   loop 0 acc = acc
   loop n acc = loop (n-1) $! (acc + n)



   /* ffi Haskell code */ 

   {-# OPTIONS -fglasgow-exts #-}

   module Main where

   -- the use of unsafe makes a big difference in runtime
   foreign import ccall unsafe incC inc :: Int - ()
   foreign import ccall getCounterC getCounter :: Int - IO Int

   printCounter :: IO ()
   printCounter
  = do val - getCounter 0 -- the 0 is bogus
   print val

   main :: IO ()
   main = seq (loop 1) printCounter

   loop :: Int - ()
   loop 0 = ()
   loop n = seq (inc n) (loop $! n - 1)

   /* ffi C code */

   #include inc.h

   int counter = 0;

   void incC (int howmuch)
   {
  counter+=howmuch;
   }

   int getCounterC (int bogus)
   {
  return counter;
   }
 


   {- fastMut -}

   module Main where

   import System.IO.Unsafe (unsafePerformIO)
   import FastMutInt

   {-# NOINLINE counter #-}
   counter :: FastMutInt
   counter = unsafePerformIO newFastMutInt

   {-# NOINLINE inc #-}
   inc :: Int - ()
   inc n = unsafePerformIO $
  do incFastMutIntBy counter n
 return ()

   printCounter :: IO ()
   printCounter
  = do val - readFastMutInt counter
   print val

   main :: IO ()
   main = do writeFastMutInt counter 0
 seq (loop 1) printCounter

   loop :: Int - ()
   loop 0 = ()
   loop n = seq (inc n) (loop $! n - 1)



   {- ioref -}

   module Main where
   
   import System.IO.Unsafe (unsafePerformIO)
   import Data.IORef (newIORef, readIORef, writeIORef, IORef)
   
   counter :: IORef Int
   {-# NOINLINE counter #-}
   counter = unsafePerformIO (newIORef 0)
   
   {-# NOINLINE inc #-}
   inc :: Int - ()
   inc n = unsafePerformIO $
  do old - readIORef counter
 writeIORef counter $! old + n
   
   printCounter :: IO ()
   printCounter
  = do val - readIORef counter
   print val
   
   main :: IO ()
   main = seq (loop 1) printCounter
   
   loop :: Int - ()
   loop 0 = ()
   loop n = seq (inc n) (loop $! n - 1)  


Re: turn off let floating

2004-04-20 Thread Ketil Malde
Bernard James POPE [EMAIL PROTECTED] writes:

 Note each program was compiled with ghc 6.2 with -O2 on debian linux.
:
   main = print $ loop 1 0

Isn't this going to be optimized away to a constant with -O2?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: turn off let floating

2004-04-20 Thread Simon Marlow
On 20 April 2004 12:48, Bernard James POPE wrote:

 Results:
 
method  runtime (s)
---
pure0.7
ffi 3.2
fastMut 15
ioref   23

I very strongly suspect that it is the unsafePerformIO that hurts
performance in the fastMut case.  Otherwise this case would be around
the same speed as the FFI example, perhaps faster.

You could try out that theory by copying the definition of
unsafePerformIO into your code, and putting an INLINE pragma on it.  I
think it's safe to do this in your case (it's not safe in general).

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


Re: turn off let floating

2004-04-20 Thread Andre Pang
On 20/04/2004, at 9:48 PM, Bernard James POPE wrote:

To test out the various possible ways of implementing a global counter
I wrote some test cases (shown below). I hope the test cases are
useful, and provide some indication of the relative performance.
However, if you spot something bogus please let me know.
Each program computes the equivalent of:

sum ([1..1] :: [Int])

There are four different ways that I tried:

   1) pure: this is just pure functional code and should be fast.
  This test case is only here as a control example, it is not
  a candidate solution because I need a global counter.
   2) ioref: this uses a global mutable counter using IORefs and
  unsafePerformIO
   3) fastMut: this uses the fast mutable integer library from GHC
  that was suggested by Simon Marlow.
   4) ffi: this implements the counter in C using the FFI.
There's another way which you missed: using implicit parameters.  I 
remember reading a paper a while ago called Global Variables in Haskell 
(sorry, don't remember the author -- Jones, perhaps?) which did similar 
benchmarking to yours, and carrying around the global variable with an 
implicit parameter was faster than using a global mutable counter via 
unsafePerformIO $ newIORef 

--
% Andre Pang : trust.in.love.to.save
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: turn off let floating

2004-04-20 Thread Bernard James POPE
Hi Andre,

 There's another way which you missed: using implicit parameters.  I 
 remember reading a paper a while ago called Global Variables in Haskell 
 (sorry, don't remember the author -- Jones, perhaps?) which did similar 
 benchmarking to yours, and carrying around the global variable with an 
 implicit parameter was faster than using a global mutable counter via 
 unsafePerformIO $ newIORef 

Thanks for the note. That was in the paper by John Hughes. The
performance difference between unsafePerformIO and implicit parameters
is not significant in his test case. I think he was surprised that 
implicit parameters worked so well (I am too). 

That doesn't mean I should rule it out completely. I'll have a look into
it.

Also, implicit parameters are less convenient for the program transformation
that I use in buddha, whereas a truly global variable is ideal.

On the other hand the FFI approach looks a lot faster already, and Simon
has suggested that I can inline unsafePerformIO.

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


Re: turn off let floating

2004-04-20 Thread Bernard James POPE
On Tue, Apr 20, 2004 at 02:56:36PM +0200, Ketil Malde wrote:
 Bernard James POPE [EMAIL PROTECTED] writes:
 
  Note each program was compiled with ghc 6.2 with -O2 on debian linux.
 :
main = print $ loop 1 0
 
 Isn't this going to be optimized away to a constant with -O2?

Here's the final stg code, obtained by:

   ghc -ddump-stg -O2 --make MainPure.hs -o pure

 STG syntax: 
Main.$wloop =
\r [ww ww1]
case ww of ds {
  __DEFAULT -
  case +# [ww1 ds] of sat_s2pI {
__DEFAULT -
case -# [ds 1] of sat_s2pE {
  __DEFAULT - Main.$wloop sat_s2pE sat_s2pI;
};
  };
  0 - ww1;
};
SRT(Main.$wloop): []
Main.loop =
\r [w w1]
case w of w2 {
  GHC.Base.I# ww -
  case w1 of w3 {
GHC.Base.I# ww1 -
case Main.$wloop ww ww1 of ww2 { __DEFAULT - GHC.Base.I# [ww2]; };
  };
};
SRT(Main.loop): []
Main.eta =
\u []
case Main.$wloop 1 0 of ww {
  __DEFAULT - GHC.Base.I# [ww];
};
SRT(Main.eta): []
Main.lvl =
\u srt:(0,*bitmap*) []
case Main.eta of w {
  GHC.Base.I# ww - GHC.Show.$wshowSignedInt 0 ww GHC.Base.[];
};
SRT(Main.lvl): [Main.eta]
Main.main =
\r srt:(0,*bitmap*) [s]
case GHC.IO.hGetLine GHC.Handle.stdin s of wild {
  GHC.Prim.(#,#) new_s a41 -
  case GHC.IO.hPutStr GHC.Handle.stdout Main.lvl new_s of wild1 {
GHC.Prim.(#,#) new_s1 a411 -
GHC.IO.$whPutChar GHC.Handle.stdout '\n' new_s1;
  };
};
SRT(Main.main): [GHC.Handle.stdout, GHC.IO.$whPutChar,
 GHC.IO.hPutStr, GHC.Handle.stdin, GHC.IO.hGetLine, Main.lvl]
:Main.main =
\r srt:(0,*bitmap*) [eta1]
catch# [Main.main GHC.TopHandler.topHandler eta1];
SRT(:Main.main): [Main.main, GHC.TopHandler.topHandler]

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


Re: turn off let floating

2004-04-20 Thread Bernard James POPE
On Tue, Apr 20, 2004 at 01:59:33PM +0100, Simon Marlow wrote:
 On 20 April 2004 12:48, Bernard James POPE wrote:
 
  Results:
  
 method  runtime (s)
 ---
 pure0.7
 ffi 3.2
 fastMut 15
 ioref   23
 
 I very strongly suspect that it is the unsafePerformIO that hurts
 performance in the fastMut case.  Otherwise this case would be around
 the same speed as the FFI example, perhaps faster.
 
 You could try out that theory by copying the definition of
 unsafePerformIO into your code, and putting an INLINE pragma on it.  I
 think it's safe to do this in your case (it's not safe in general).

The time for fastMut with unsafePerformIO inlined is:

   3.6 sec

The code is below. Note I dropped the NOINLINE pragmas on counter and inc.
This was necessary to get the fast time (is this safe?, it gives the right
answer here but ...). Also I removed the constant 1 from the code 
(though it doesn't make any difference).

Thanks to all who have chipped in.

Cheers,
Bernie.



{-# OPTIONS -fglasgow-exts #-}
module Main where

import GHC.IOBase hiding (unsafePerformIO)
import FastMutInt
import GHC.Base

counter :: FastMutInt
counter = unsafePerformIO newFastMutInt

inc :: Int - ()
inc n = unsafePerformIO $
   do incFastMutIntBy counter n
  return ()

printCounter :: IO ()
printCounter
   = do val - readFastMutInt counter
print val

main :: IO ()
main = do line - getLine
  writeFastMutInt counter 0
  seq (loop (read line)) printCounter

loop :: Int - ()
loop 0 = ()
loop n = seq (inc n) (loop $! n - 1)

{-# INLINE unsafePerformIO #-}
unsafePerformIO :: IO a - a
unsafePerformIO (IO m) = case m realWorld# of (# _, r #) - r
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: turn off let floating

2004-04-15 Thread Tomasz Zielonka
On Thu, Apr 15, 2004 at 01:52:38PM +1000, Bernard James POPE wrote:
 
 However, if you have any suggestions about how to make a FAST global counter
 I would be very glad to hear it. From profiling it seems like this code
 is a little expensive (also it is called quite frequently).

Well, I'm not Simon, but I would suggest to change the line with
writeIORef to:

   writeIORef count $! newCount

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: turn off let floating

2004-04-15 Thread Simon Marlow
 So I have code like:
 
{-# NOINLINE count #-}
count :: IORef Int
count = unsafePerformIO $ newIORef 0
 
{-# NOINLINE getCount #-}
getCount :: (Int - a) - a
getCount f
   = let nextCount
  = (unsafePerformIO $
   do oldCount - readIORef count
  let newCount = oldCount + 1
  writeIORef count newCount
  return oldCount)
 in seq nextCount (f nextCount)
 
 It seems to work okay.
 
 However, if you have any suggestions about how to make a FAST 
 global counter
 I would be very glad to hear it. From profiling it seems like 
 this code
 is a little expensive (also it is called quite frequently).

You could try the FastMutInt module from GHC
(ghc/compiler/utils/FastMutInt.hs) to speed things up.  Unfortunately
unsafePerformIO has some unavoidable overhead: it can't be inlined
because we don't want the compiler to see its definition.

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


RE: turn off let floating

2004-04-15 Thread Carl Witty
  However, if you have any suggestions about how to make a FAST 
  global counter
  I would be very glad to hear it. From profiling it seems like 
  this code
  is a little expensive (also it is called quite frequently).
 
 You could try the FastMutInt module from GHC
 (ghc/compiler/utils/FastMutInt.hs) to speed things up.  Unfortunately
 unsafePerformIO has some unavoidable overhead: it can't be inlined
 because we don't want the compiler to see its definition.

What happens if you use the FFI to call a C function like
int getCount() { static int x; return x++; }
and mark the function pure (outside the IO monad) and noinline? 
(Probably all the calls get commoned up and it only gets called once;
but it might be worth a try).

You mentioned that you're trying to get a new counter value for every
function application; maybe something like an FFI call to
int getCount(void *f, void *a) { static int x; return x++; }
where you have getCount :: (a - b) - a - Int; then you pass the
function and its argument to getCount.  This should prevent any unwanted
common subexpression elimination.

Carl Witty

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


Re: turn off let floating

2004-04-14 Thread Bernard James POPE
On Tue, Apr 13, 2004 at 02:03:21PM +0100, Simon Marlow wrote:
  
  On Fri, Apr 09, 2004 at 03:27:01PM +0200, David Sabel wrote:
  
   you can turn off let-floating by compiling without optimizations,
   i.e. without using a -O flag or using -O0 explicitly. 
   The disadvantage is that most of all other optimizations 
   are turned off too.
  
  That is exactly what I'm doing at the moment. The module that has the
  nasty impure bits in it is not compiled with optimisations. 
  I will improve this when GHC regains the non-let floating flag.
 
 If you need -ffull-laziness to force a certain behaviour when using
 unsafePerformIO, I say that what you're doing is at the very least
 unsupported ;-)  However, there are occasoinally good uses for this:
 HOOD is one; I imagine your case is similar?

Hi Simon,

What I am trying to do is implement a global (mutable) integer counter.
I'm using a combination of IORefs and unsafePerformIO.

The reason I want to do this is that I'm experimenting with a new 
design of buddha. Each function call in a program being debugged gets a 
new number by reading and incrementing the global counter. 

Thus the counter is read and incremented from within pure code 
(no IO monad).

Of course this is not what you are supposed to do in a pure language :)
Nonetheless, a global mutable counter is exactly what I want for this
job - I don't want to thread anything through the code.

So I have code like:

   {-# NOINLINE count #-}
   count :: IORef Int
   count = unsafePerformIO $ newIORef 0

   {-# NOINLINE getCount #-}
   getCount :: (Int - a) - a
   getCount f
  = let nextCount
 = (unsafePerformIO $
  do oldCount - readIORef count
 let newCount = oldCount + 1
 writeIORef count newCount
 return oldCount)
in seq nextCount (f nextCount)

It seems to work okay.

However, if you have any suggestions about how to make a FAST global counter
I would be very glad to hear it. From profiling it seems like this code
is a little expensive (also it is called quite frequently).

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


RE: turn off let floating

2004-04-13 Thread Simon Marlow
 
 On Fri, Apr 09, 2004 at 03:27:01PM +0200, David Sabel wrote:
 
  you can turn off let-floating by compiling without optimizations,
  i.e. without using a -O flag or using -O0 explicitly. 
  The disadvantage is that most of all other optimizations 
  are turned off too.
 
 That is exactly what I'm doing at the moment. The module that has the
 nasty impure bits in it is not compiled with optimisations. 
 I will improve this when GHC regains the non-let floating flag.

If you need -ffull-laziness to force a certain behaviour when using
unsafePerformIO, I say that what you're doing is at the very least
unsupported ;-)  However, there are occasoinally good uses for this:
HOOD is one; I imagine your case is similar?

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


Re: turn off let floating

2004-04-10 Thread Bernard James POPE
On Fri, Apr 09, 2004 at 03:27:01PM +0200, David Sabel wrote:

 you can turn off let-floating by compiling without optimizations,
 i.e. without using a -O flag or using -O0 explicitly. 
 The disadvantage is that most of all other optimizations 
 are turned off too.

That is exactly what I'm doing at the moment. The module that has the
nasty impure bits in it is not compiled with optimisations. 
I will improve this when GHC regains the non-let floating flag.

 Another possibility would be to compile your program with HasFuse 
  
 http://www.ki.informatik.uni-frankfurt.de/~sabel/hasfuse/
  
 which is a modification of GHC, that performs only such transformations
 that are compatible with the use of unsafePerformIO.
 (no common subexpression elimination,
  no let-floating out,
  more restrictive inlining)

That is a possibility, but the code is part of buddha, my debugger.
I would have to require the user of buddha also to have HasFuse.

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


Re: turn off let floating

2004-04-09 Thread David Sabel
Hi,
 
you can turn off let-floating by compiling without optimizations,
i.e. without using a -O flag or using -O0 explicitly. 
The disadvantage is that most of all other optimizations 
are turned off too.
 
Another possibility would be to compile your program with HasFuse 
 
http://www.ki.informatik.uni-frankfurt.de/~sabel/hasfuse/
 
which is a modification of GHC, that performs only such transformations
that are compatible with the use of unsafePerformIO.
(no common subexpression elimination,
 no let-floating out,
 more restrictive inlining)
 
In fact, HasFuse guarantees more than compiling SAFE uses of 
unsafePerformIO correctly (it fulfills the FUNDIO-semantics),
but HasFuse can also be used to compile 'normal' Haskell programs.
 
David
--
JWGU Frankfurt, Germany


- Original Message - 
From: Bernard James POPE [EMAIL PROTECTED]
To: [EMAIL PROTECTED]
Cc: Bernard James POPE [EMAIL PROTECTED]
Sent: Tuesday, April 06, 2004 10:24 AM
Subject: turn off let floating


 Hi all,
 
 In the documentation for System.IO.Unsafe
 it says:
 
Make sure that the either you switch off let-floating, 
or that the call to unsafePerformIO cannot float outside a lambda.  
 
 My question is how can you turn off let floating? I can't seem to
 find a flag that suggests this behaviour.
 
 Cheers,
 Bernie.
 ___
 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: turn off let floating

2004-04-06 Thread Simon Peyton-Jones
Strangely (and bogusly) there is no such flag in GHC6.2.  Someone must
have noticed this already because it's there in the HEAD
(-fno-full-laziness), and has been since Feb 2004.  Strange.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Bernard James POPE
| Sent: 06 April 2004 09:24
| To: [EMAIL PROTECTED]
| Cc: Bernard James POPE
| Subject: turn off let floating
| 
| Hi all,
| 
| In the documentation for System.IO.Unsafe
| it says:
| 
|Make sure that the either you switch off let-floating,
|or that the call to unsafePerformIO cannot float outside a lambda.
| 
| My question is how can you turn off let floating? I can't seem to
| find a flag that suggests this behaviour.
| 
| Cheers,
| Bernie.
| ___
| 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: turn off let floating

2004-04-06 Thread Bernard James POPE
On Tue, Apr 06, 2004 at 09:38:38AM +0100, Simon Peyton-Jones wrote:
 Strangely (and bogusly) there is no such flag in GHC6.2.  Someone must
 have noticed this already because it's there in the HEAD
 (-fno-full-laziness), and has been since Feb 2004.  Strange.

Thanks,

I think it would be good for the docs for System.IO.Unsafe
(in future releases that have this flag) to mention the actual flag name.

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