Re: Control.Exception

2008-11-03 Thread Simon Marlow

Jason Dagit wrote:

On Wed, Oct 8, 2008 at 1:19 AM, Simon Marlow [EMAIL PROTECTED] wrote:

Johannes Waldmann wrote:

with 6.10, the following does not typecheck:

foo `Control.Exception.catch` \ _ - return bar

Ambiguous type variable `e' in the constraint:
 `Control.Exception.Exception e'

It is probably bad programming style anyway but what is the workaround?

As long as you're aware that it is bad programming style.  We deliberately
didn't include an easy way to do this, because we want people to think about
why they need to catch *all* exceptions (most of the time it's a bug).


Since the above is bad form, what should I be doing?  Could someone
please provide some examples or point me at the list of exceptions
that I can catch?  What about catching multiple types of exceptions?


Let's distinguish two kinds of exception handling:

1. Cleaning up.  If you want to catch errors in order to clean up - release 
resources, remove temporary files, that sort of thing - then use bracket or 
finally.  Behind the scenes, these catch all exceptions, but crucially they 
re-throw the exception after cleaning up, and they do the right 
block/unblock stuff for asynchronous exceptions.


2. Recovery.  You want to catch certain kinds of exception in order to 
recover and do something else, e.g. when calling getEnv.  In that case, I 
recommend using try or tryJust.


   tryJust (guard . isDoesNotExistError) $ getEnv HOME

it's good practice to separate the filter (the kinds of exception you're 
catching) from the code to handle them, and that's what tryJust does. 
There's some subtelty here to do with whether you need to be in blocked 
mode to handle the exception or not: if you're handling an exception you 
expect to be thrown asynchronously, then you probably want to use catch 
instead of try, because then the handler will run in blocked mode.  But be 
careful not to tail-call out of the handler, because then the thread will 
stay in blocked mode, which will lead to strange problems later.  A bit 
more background is here:


http://hackage.haskell.org/trac/ghc/ticket/2558

(hmm, perhaps exception handlers should be STM transactions.  Then you 
wouldn't be able to accidentally tail-call out of the exception handler 
back into IO code, but you would be able to re-throw exceptions.  Just a 
thought.)


As for the kinds of exception you can catch, nowadays you can catch any 
type that is an instance of Exception.  A good place to start is the list 
of instances of Exception in the docs:


http://www.haskell.org/ghc/dist/stable/docs/libraries/base/Control-Exception.html#t%3AException

although that only contains types defined by the base package.

Others have commented on the backwards-compat issues, I don't have anything 
to add there.


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


Re: ANNOUNCE: GHC 6.10.1 RC 1

2008-11-03 Thread Simon Marlow

Paul Jarc wrote:

Ian Lynagh [EMAIL PROTECTED] wrote:

I thought all your problems boiled down to binaries not being able to
find libgmp.so at runtime? So I think this should fix them all.


Yes, but then I wouldn't be able to find and fix the commands that are
missing SRC_HC_OPTS. :)  So I'm holding off on that for now.  Below is
a patch for the ones I've found so far.  With those changes, and
without setting LD_LIBRARY_PATH, the build stops here:


Technically speaking, we should pass $(HC_OPTS) to any Haskell 
compilations.  That includes $(SRC_HC_OPTS), but also a bunch of other things.


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


Re: No atomic read on MVar?

2008-11-03 Thread Simon Marlow

Philip K.F. Hölzenspies wrote:


I ran face first into an assumption I had made on MVar operations (in 
Control.Concurrent); I had assumed there to be an atomic read (i.e. 
non-destructive read, as opposed to destructive consume/take). The following 
program illustrates what I had in mind.


testAtomic :: IO ()
testAtomic = do
var - newMVar 0
putStrLn(Fork)
forkIO (putMVar var 1  putStrLn X)
yield
r1 - readMVar var
putStrLn(1)
r2 - takeMVar var
putStrLn(2)
r3 - takeMVar var
putStrLn(Result:  ++ show [r1,r2,r3])

If readMVar had been atomic, the result would be program termination with a 
result of [0,0,1] being output. However, readMVar simply combines takeMVar 
and putMVar, so the reading of r1 blocks after the takeMVar, because upon 
taking the MVar, the blocked thread wakes up, puts 1 in var and prints X. 
readMVar does not terminate for r1 (i.e. 1 is never printed).


I have now implemented my variable as a pair of MVars, one of which serves as 
a lock on the other. Both for performance reasons and for deadlock analysis, 
I would really like an atomic read on MVars, though. Does it exist? If not, 
why not?


It would be slightly annoying to implement, because it needs changes in 
putMVar too: if there are blocked readMVars, then putMVar would have to 
wake them all up.  Right now an MVar can only have one type of blocked 
thread attached to it at a time, either takeMVars or putMVars, and putMVar 
only has to wake a single thread.


Perhaps you should be using STM?

I suppose the answer to why doesn't atomic readMVar exist is that MVar is 
intended to be a basic low-level synchronisation abstraction, on which you 
can build larger abstractions (which you have indeed done).  On other other 
hand, we're always interested in getting good value out of the building 
blocks, so when there are useful operations we can add without adding 
distributed complexity, that's often a good idea.  I'm not sure that atomic 
readMVar falls into this category, though.


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


Re: Control.Exception

2008-11-03 Thread Jason Dagit
On Mon, Nov 3, 2008 at 6:24 AM, Simon Marlow [EMAIL PROTECTED] wrote:
 Jason Dagit wrote:

 On Wed, Oct 8, 2008 at 1:19 AM, Simon Marlow [EMAIL PROTECTED] wrote:

 Johannes Waldmann wrote:

 with 6.10, the following does not typecheck:

 foo `Control.Exception.catch` \ _ - return bar

 Ambiguous type variable `e' in the constraint:
 `Control.Exception.Exception e'

 It is probably bad programming style anyway but what is the workaround?

 As long as you're aware that it is bad programming style.  We
 deliberately
 didn't include an easy way to do this, because we want people to think
 about
 why they need to catch *all* exceptions (most of the time it's a bug).

 Since the above is bad form, what should I be doing?  Could someone
 please provide some examples or point me at the list of exceptions
 that I can catch?  What about catching multiple types of exceptions?

 Let's distinguish two kinds of exception handling:

Thanks.  This helps a lot.  Mind if I put it somewhere, such as on the wiki?

 As for the kinds of exception you can catch, nowadays you can catch any type
 that is an instance of Exception.  A good place to start is the list of
 instances of Exception in the docs:

 http://www.haskell.org/ghc/dist/stable/docs/libraries/base/Control-Exception.html#t%3AException

 although that only contains types defined by the base package.

 Others have commented on the backwards-compat issues, I don't have anything
 to add there.

Ah, but I had one more question that I don't think anyone has answered
yet.  That is, how to deal with multiple types of exceptions.
Suppose, as a concrete example, that I was looking out for both
ExitCode and PatternMatchFail exceptions.  Maybe I'm being naive, but
it seems like I'm in that situation again where I have to catch all
and then check if fromException succeeds on either PatternMatchFile or
ExitCode types.  And then throw if it both give Nothing?

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


No atomic read on MVar?

2008-11-03 Thread Philip K.F. Hölzenspies
Dear GHCers,

I ran face first into an assumption I had made on MVar operations (in 
Control.Concurrent); I had assumed there to be an atomic read (i.e. 
non-destructive read, as opposed to destructive consume/take). The following 
program illustrates what I had in mind.

testAtomic :: IO ()
testAtomic = do
var - newMVar 0
putStrLn(Fork)
forkIO (putMVar var 1  putStrLn X)
yield
r1 - readMVar var
putStrLn(1)
r2 - takeMVar var
putStrLn(2)
r3 - takeMVar var
putStrLn(Result:  ++ show [r1,r2,r3])

If readMVar had been atomic, the result would be program termination with a 
result of [0,0,1] being output. However, readMVar simply combines takeMVar 
and putMVar, so the reading of r1 blocks after the takeMVar, because upon 
taking the MVar, the blocked thread wakes up, puts 1 in var and prints X. 
readMVar does not terminate for r1 (i.e. 1 is never printed).

I have now implemented my variable as a pair of MVars, one of which serves as 
a lock on the other. Both for performance reasons and for deadlock analysis, 
I would really like an atomic read on MVars, though. Does it exist? If not, 
why not?

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


Re: could ghci debugger search for free variables better?

2008-11-03 Thread Simon Marlow

Peter Hercek wrote:

Simon Marlow wrote:
We thought about this when working on the debugger, and the problem is 
that to make the debugger retain all the variables that are in scope 
rather than just free in the expression adds a lot of overhead, and it 
fundamentally changes the structure of the generated code: everything 
becomes recursive, for one thing.  Well, perhaps you could omit all 
the recursive references (except the ones that are also free?), but 
there would still be a lot of overhead due to having to retain all 
those extra references.


It also risks creating serious space leaks, by retaining references to 
things that the program would normally discard.


Fortunately it's usually easy to work around the limitation, just by 
adding extra references to your code, e.g. in a let expression that 
isn't used.


Yes, Pepe pointed this to me too along with the Step inside
 GHCi debugger paper in monad reader. The problem is that
 I mostly can find out what is wrong when I look at values of
 some important variables when some important place in my code
 is hit. Using the trick with const function to manually add
 references is not that much better than simple printf
 debugging (adding Debug.Trace.trace calls to the code).
 Tracing the execution history is nice too but it provides
 much more than what is needed and obscures the important parts.

OK, It is frustrating that I find printf debugging often more
 productive than ghci debugger.

I see that it is not a good idea to keep references to all the
 variables in scope but maybe few improvements are possible:

1) As there is :steplocal, there should be also :tracelocal.
   It would keep history of evaluations within given function
   then when user asks for a variable it would be searched
   first in the selected expression and if not found in the
   expressions from the tracelocal history. If the result
   would be printed from tracelocal history it should be indicated
   so in the output. This would avoid the tedious task of
   searching the trace history manually and moreover it would
   limit the history to the interesting parts (so hopefully
   the depth of 50 would be enough). The results from the
   tracelocal history may not be from the expected scope
   sometimes but the same problem is with printf debugging.


Good suggestion - please submit it via the bugtracker,

http://hackage.haskell.org/trac/ghc/newticket?type=feature+request


2) I noticed only now that I do not know how to script
   breakpoints. I tried
   :set stop if myFreeVar == 666 then :list else :continue
   ... and it did not work. My goal was to create a conditional
   breakpoint. I also wanted to use it instead of printf
   debugging using something like
   :set stop { :force myFreeVar; :continue }
   Ideally it should be possible to attach
   different script for each breakpoint and the functions
   for controlling debugger should be available in the
   Haskell. I would expect this is already partially possible
   now (using :set stop) and possibly some functions from
   ghci api which correspond to ghci commands (like :set etc.).
   But I do not know how, any pointers from experienced ghci
   debugger users?


I think you want :cmd.  e.g.

:set stop :cmd if myFreeVar == 666 then return :list else return :continue


Ghci debugger did not know some functions in my code which
 I would expect it to know; e.g. field selection functions
 from a record which is not exported from the module but
 which are available withing module. Is this expected?
 (I did not have any *.hi *.o files around when ghci did run
 the code.)


It could be a bug, if you could figure out how to reproduce it and submit a 
bug report that would be great.



Och and sometimes it did not recognize a free variable in
 the selected expression. The code looked like
 let myFn x = x `div` getDivisor state  100 in
 if myFn xxx then ...
 the expression myFn xxx was selected while browsing trace
 history but xxx was not recognized, but when I browsed into
 myFn definition in the trace log the x (which represented
 the same value) was recognized. Is this expected?


Again, please submit a bug report.  The debugger is supposed to give you 
access to all of the free variables of the current expression.


Cheers,
Simon

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


Re: Control.Exception

2008-11-03 Thread Antoine Latter
On Mon, Nov 3, 2008 at 9:34 AM, Jason Dagit [EMAIL PROTECTED] wrote:

 Ah, but I had one more question that I don't think anyone has answered
 yet.  That is, how to deal with multiple types of exceptions.
 Suppose, as a concrete example, that I was looking out for both
 ExitCode and PatternMatchFail exceptions.  Maybe I'm being naive, but
 it seems like I'm in that situation again where I have to catch all
 and then check if fromException succeeds on either PatternMatchFile or
 ExitCode types.  And then throw if it both give Nothing?


I haven't tried this, so it may not work:


data MyException = MyArithException ArithException  | MyIOException
IOException deriving Typeable

instance Exception MyExcpetion where
  toException (MyArithException e) = toException e
  toException (MyIOExcpetion e) = toException e

  fromException se = case fromException se of
   Just e - Just $ MyArithException e
   Nothing - case fromException se of
 Just e - Just $ MyIOException e
 _ - Nothing


Then anyone can catch your exceptions by catching the ArithException
or IOException as normal, and you can catch IOExceptions and
ArithExceptions into your own custom type.

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


Re: Control.Exception

2008-11-03 Thread Duncan Coutts
On Mon, 2008-11-03 at 09:26 -0800, Sigbjorn Finne wrote:
 On 11/3/2008 07:34, Jason Dagit wrote:
  
 
  Ah, but I had one more question that I don't think anyone has answered
  yet.  That is, how to deal with multiple types of exceptions.
  Suppose, as a concrete example, that I was looking out for both
  ExitCode and PatternMatchFail exceptions.  Maybe I'm being naive, but
  it seems like I'm in that situation again where I have to catch all
  and then check if fromException succeeds on either PatternMatchFile or
  ExitCode types.  And then throw if it both give Nothing?
 

 One way to do this now is to use Control.Exception.catches:
 
  catches :: IO a - [Handler a] - IO a
  data Handler a where
 Handler :: forall a e. (Exception e) = (e - IO a) - Handler a

ie:

action
  `catches`
[ \(e :: ExitCode) - ...
, \(e :: PatternMatchFail) - ...
]

or just by using multiple catch clauses:

action
  `catch` (\(e :: ExitCode) - ...)
  `catch` (\(e :: PatternMatchFail) - ...)


Duncan

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


Re: Dilemma: DiffArray non-performance vs STArray non-readability

2008-11-03 Thread Simon Marlow

Claus Reinke wrote:

I keep wanting to use DiffArray as the natural functional solution to
single-threaded array use. But everytime I try, I get smacked over
the head with the actual performance figures. Sometimes, even plain
arrays are faster in a loop doing array updates, in spite of all the 
copying involved. And when copying on update dominates the runtime, 
using IntMap tends to be faster - the indirections are the wrong way

round, but don't pile up, just that array lookups aren't quite constant
time.

But when I really need to avoid the updates, and need constant
time lookup, I'm stuck: DiffArray tends to slow everything down
(I vaguely recall locks and threads being at the heart of this, but
I haven't checked the code recently), so my only option seems to
be to transform my nice functional code into not-nice sequential code 
and use STArray.


Is there any way out of this dilemma? What do other Ghc users use?

If locks really are the issue, perhaps using STM instead of MVars
in the DiffArray implementation could help. As long as my array uses are 
single-threaded, STM optimism might be able to avoid

waiting/scheduler issues? Or am I on the wrong track?


It needs to be thread-safe, but I imagine that using atomicModifyIORef 
rather than STM or MVars is the way to get good performance here.



PS Btw, I thought the DiffArray performance issue was ancient,
   but I can't find a ticket for it, nor does the haddock page for
   Data.Array.Diff mention this little hickup. Should I add a ticket?


I see there is one now, thanks.

Cheers,
Simon

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


Re: Control.Exception

2008-11-03 Thread Sigbjorn Finne

On 11/3/2008 07:34, Jason Dagit wrote:



Ah, but I had one more question that I don't think anyone has answered
yet.  That is, how to deal with multiple types of exceptions.
Suppose, as a concrete example, that I was looking out for both
ExitCode and PatternMatchFail exceptions.  Maybe I'm being naive, but
it seems like I'm in that situation again where I have to catch all
and then check if fromException succeeds on either PatternMatchFile or
ExitCode types.  And then throw if it both give Nothing?

  

One way to do this now is to use Control.Exception.catches:

catches :: IO a - [Handler a] - IO a
data Handler a where
   Handler :: forall a e. (Exception e) = (e - IO a) - Handler a

--sigbjorn

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


Re: Control.Exception

2008-11-03 Thread David Menendez
On Mon, Nov 3, 2008 at 12:53 PM, Duncan Coutts
[EMAIL PROTECTED] wrote:
 On Mon, 2008-11-03 at 09:26 -0800, Sigbjorn Finne wrote:
 One way to do this now is to use Control.Exception.catches:

  catches :: IO a - [Handler a] - IO a
  data Handler a where
 Handler :: forall a e. (Exception e) = (e - IO a) - Handler a

 ie:

 action
  `catches`
[ \(e :: ExitCode) - ...
, \(e :: PatternMatchFail) - ...
]

 or just by using multiple catch clauses:

 action
  `catch` (\(e :: ExitCode) - ...)
  `catch` (\(e :: PatternMatchFail) - ...)

I don't think those are equivalent. In the second case, the
PatternMatchFail handler scopes over the ExitCode handler.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: No atomic read on MVar?

2008-11-03 Thread David Menendez
On Mon, Nov 3, 2008 at 6:29 AM, Philip K.F. Hölzenspies
[EMAIL PROTECTED] wrote:

 I have now implemented my variable as a pair of MVars, one of which serves as
 a lock on the other. Both for performance reasons and for deadlock analysis,
 I would really like an atomic read on MVars, though. Does it exist? If not,
 why not?

Have you considered using STM? All the operations on TMVars are atomic.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Control.Exception

2008-11-03 Thread shelarcy
On Tue, 04 Nov 2008 07:40:50 +0900, David Menendez [EMAIL PROTECTED] wrote:
 ie:

 action
  `catches`
[ \(e :: ExitCode) - ...
, \(e :: PatternMatchFail) - ...
]

 or just by using multiple catch clauses:

 action
  `catch` (\(e :: ExitCode) - ...)
  `catch` (\(e :: PatternMatchFail) - ...)

 I don't think those are equivalent. In the second case, the
 PatternMatchFail handler scopes over the ExitCode handler.

I think Duncan forgot to write parens. According to Ian's example,
here is an equivalent code.

(action
  `catch` (\(e :: ExitCode) - ...))
  `catch` (\(e :: PatternMatchFail) - ...)

http://www.haskell.org/pipermail/libraries/2008-July/010095.html


Best Regards,

-- 
shelarcy shelarcyhotmail.co.jp
http://page.freett.com/shelarcy/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Control.Exception

2008-11-03 Thread David Menendez
On Mon, Nov 3, 2008 at 7:27 PM, shelarcy [EMAIL PROTECTED] wrote:
 On Tue, 04 Nov 2008 07:40:50 +0900, David Menendez [EMAIL PROTECTED] wrote:
 ie:

 action
  `catches`
[ \(e :: ExitCode) - ...
, \(e :: PatternMatchFail) - ...
]

 or just by using multiple catch clauses:

 action
  `catch` (\(e :: ExitCode) - ...)
  `catch` (\(e :: PatternMatchFail) - ...)

 I don't think those are equivalent. In the second case, the
 PatternMatchFail handler scopes over the ExitCode handler.

 I think Duncan forgot to write parens. According to Ian's example,
 here is an equivalent code.

 (action
  `catch` (\(e :: ExitCode) - ...))
  `catch` (\(e :: PatternMatchFail) - ...)

 http://www.haskell.org/pipermail/libraries/2008-July/010095.html

That's equivalent to the code without the parentheses, but it isn't
equivalent to the code using catches.

Assume we have exitCodeHandler :: ExitCode - IO () and
pattternMatchHandler :: PatternMatchFail - IO (),

1. action `catches` [ Handler exitCodeHandler, Handler patternMatchHandler ]
2. (action `catch` exitCodeHandler) `catch` patternMatchHandler

Let's further assume that action throws an ExitCode exception and
exitCodeHandler throws a PatternMatchFail exception. In example 1,
the PatternMatchFail exception thrown by exitCodeHandler is not
caught by patternMatchHandler, but it in example 2 it is caught.

In other words, patternMatchHandler is active during the evaluation of
exitCodeHandler in example 2, but not in example 1.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users