[GHC] #7411: Exceptions are optimized away in certain situations

2012-11-13 Thread GHC
#7411: Exceptions are optimized away in certain situations
+---
Reporter:  SimonHengel  |  Owner:   
 
Type:  bug  | Status:  new  
 
Priority:  normal   |  Component:  Compiler 
 
 Version:  7.6.1|   Keywords:  seq, deepseq, 
evaluate, exceptions
  Os:  Linux|   Architecture:  x86_64 (amd64)   
 
 Failure:  Incorrect result at runtime  |  Blockedby:   
 
Blocking:   |Related:   
 
+---
 The issue came up in [http://www.haskell.org/pipermail/glasgow-haskell-
 users/2012-November/023027.html this thread on glasgow-haskell-users].

 == Steps to reproduce: ==

 {{{
 -- file Foo.hs
 import Control.Exception
 import Control.DeepSeq
 main = evaluate (('a' : undefined) `deepseq` return () :: IO ())
 }}}
 {{{
 $ ghc -fforce-recomp -fpedantic-bottoms -O Foo.hs
 }}}

 === Expected result: ===
 The program should fail with:
 {{{
 Foo: Prelude.undefined
 }}}

 === Actual result: ===

 The program succeeds.

 Compiling the program with {{{-fno-state-hack}}} helps.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7411
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #6153: writeChan not properly protecting again async exceptions

2012-06-11 Thread GHC
#6153: writeChan not properly protecting again async exceptions
---+
  Reporter:  klao  |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  libraries/base|Version:  7.4.1   
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonmar):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = fixed


Comment:

 Thanks, this is actually already fixed, see
 [http://www.haskell.org/pipermail/cvs-libraries/2012-March/015116.html]

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6153#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


[GHC] #6153: writeChan not properly protecting again async exceptions

2012-06-08 Thread GHC
#6153: writeChan not properly protecting again async exceptions
--+-
 Reporter:  klao  |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  libraries/base  
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 In the current code of writeChan from Control.Concurrent.Chan:

 {{{
 writeChan (Chan _ writeVar) val = do
   new_hole - newEmptyMVar
   modifyMVar_ writeVar $ \old_hole - do
 putMVar old_hole (ChItem val new_hole)
 return new_hole
 }}}

 if an async exception arrives between putMVar old_hole and return, the
 channel will be left in inconsistent state: the writeVar will be reverted
 to its original value, but old_hole would remain filled in. Thus all
 subsequent writers will block on this Chan indefinitely.

 The proper solution is to just mask the whole operation. And it's OK, as
 'putMVar old_hole' cannot ever block. I attach a patch for this.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6153
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #6153: writeChan not properly protecting again async exceptions

2012-06-08 Thread GHC
#6153: writeChan not properly protecting again async exceptions
--+-
 Reporter:  klao  |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  libraries/base  
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-

Comment(by klao):

 Also, I'm attaching small program that demonstrates this issue. If you
 compile it with -O0 in a way that Control.Concurrent.Chan is ''also''
 compiled with -O0 (for example by copying Control/Concurrent/Chan.hs and
 uncommenting import Chan instead for Control.Concurrent.Chan), then the
 deadlock is consistently reproduced.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/6153#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #3997: Lazy I/O and asynchronous exceptions don't mix well

2012-02-27 Thread GHC
#3997: Lazy I/O and asynchronous exceptions don't mix well
--+-
  Reporter:  simonmar |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  7.0.1   
 Component:  libraries/base   |Version:  6.12.1  
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonmar):

  * difficulty:  = Unknown


Comment:

 another instance of this bug: #5866

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3997#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5475: Unthrown exceptions

2011-11-09 Thread GHC
#5475: Unthrown exceptions
--+-
Reporter:  daniel.is.fischer  |Owner:  simonpj 
Type:  bug|   Status:  new 
Priority:  high   |Milestone:  7.4.1   
   Component:  Compiler   |  Version:  7.3 
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-
Changes (by igloo):

  * owner:  = simonpj
  * priority:  normal = high
  * milestone:  = 7.4.1


Comment:

 Hmm, with `q.hs`:
 {{{
 module Main (main) where

 main :: IO ()
 main = do local - testPackage
   case (local, False) of
([x], _) - putStrLn X
(_,   True)  - putStrLn Y
([],  False) - error A
(as,  bs)- error B

 testPackage :: IO [Int]
 testPackage = return []
 }}}
 and HEAD I get:
 {{{
 $ ghc -fforce-recomp -dcore-lint -dcmm-lint -O --make q
 [1 of 1] Compiling Main ( q.hs, q.o )
 Linking q ...
 $ ./q
 $ echo $?
 0
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5475#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5475: Unthrown exceptions

2011-11-09 Thread GHC
#5475: Unthrown exceptions
--+-
Reporter:  daniel.is.fischer  |Owner:  simonpj 
Type:  bug|   Status:  new 
Priority:  high   |Milestone:  7.4.1   
   Component:  Compiler   |  Version:  7.3 
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by igloo):

 (and expected `q: A` on stderr, and exit code 1)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5475#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5475: Unthrown exceptions

2011-11-09 Thread GHC
#5475: Unthrown exceptions
--+-
Reporter:  daniel.is.fischer  |Owner:  simonpj 
Type:  bug|   Status:  new 
Priority:  high   |Milestone:  7.4.1   
   Component:  Compiler   |  Version:  7.3 
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by simonpj@…):

 commit b8abb31f649f0b3eeb691f92a8310b73c520658e
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Wed Nov 9 21:56:50 2011 +

 Fix Trac #5475: another bug in exprArity

 As usual it was to do with the handling of bottoms,
 but this time it wasn't terribly subtle; I was using
 andArityType (which is designed for case branches) as
 a cheap short cut for the arity trimming needed with
 a cast.  That did the Wrong Thing for bottoming
 expressions.  Sigh.

  compiler/coreSyn/CoreArity.lhs|   27 ---
  compiler/simplCore/SimplUtils.lhs |2 +-
  2 files changed, 17 insertions(+), 12 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5475#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5475: Unthrown exceptions

2011-11-09 Thread GHC
#5475: Unthrown exceptions
--+-
Reporter:  daniel.is.fischer  |Owner:  igloo   
Type:  bug|   Status:  new 
Priority:  high   |Milestone:  7.4.1   
   Component:  Compiler   |  Version:  7.3 
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-
Changes (by simonpj):

  * owner:  simonpj = igloo


Comment:

 Nice bug thank you.  I'm travelling with a slow laptop so I can't do a
 full validate, but I'm pretty sure this fix will be fine.  Ian can you
 check?

 Also can you add a regression test?  I wasn't sure how to add one that
 expects a non-zero exit code.  Moreover Windows prints T5475.exe: A
 whereas presumably Unix will not print the exe part.  thanks

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5475#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5475: Unthrown exceptions

2011-11-09 Thread GHC
#5475: Unthrown exceptions
--+-
Reporter:  daniel.is.fischer  |Owner:  igloo   
Type:  bug|   Status:  new 
Priority:  high   |Milestone:  7.4.1   
   Component:  Compiler   |  Version:  7.3 
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by daniel.is.fischer):

 `cgrun059` passes now all ways, `stm060` passed already before.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5475#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5475: Unthrown exceptions

2011-11-09 Thread GHC
#5475: Unthrown exceptions
+---
  Reporter:  daniel.is.fischer  |  Owner:  igloo   
  Type:  bug| Status:  closed  
  Priority:  high   |  Milestone:  7.4.1   
 Component:  Compiler   |Version:  7.3 
Resolution:  fixed  |   Keywords:  
  Testcase: |  Blockedby:  
Difficulty: | Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed


Comment:

 passes here too, and `cgrun059` already tests this bug, so no need to add
 a new testcase.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5475#comment:6
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5561: assertion overriden by other exceptions

2011-10-19 Thread GHC
#5561: assertion overriden by other exceptions
--+-
  Reporter:  MikolajKonarski  |  Owner:
  Type:  bug  | Status:  new   
  Priority:  normal   |  Milestone:
 Component:  Compiler |Version:  7.3   
Resolution:   |   Keywords:
  Testcase:   |  Blockedby:
Difficulty:   | Os:  Linux 
  Blocking:   |   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  |  
--+-

Comment(by simonmar):

 Tricky one, but I think we should fix it with `lazy` as suggested, and
 put a comment pointing to this ticket next to the fix.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5561#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5561: assertion overriden by other exceptions

2011-10-19 Thread GHC
#5561: assertion overriden by other exceptions
--+-
  Reporter:  MikolajKonarski  |  Owner:
  Type:  bug  | Status:  new   
  Priority:  normal   |  Milestone:
 Component:  Compiler |Version:  7.3   
Resolution:   |   Keywords:
  Testcase:   |  Blockedby:
Difficulty:   | Os:  Linux 
  Blocking:   |   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  |  
--+-

Comment(by simonpj):

 I agree with Simon.  It's true that
   `(throw this  throw that)`
 should be allowed to return either exception `this` or `that`, but
`assert False (throw this)`
 should really report the assertion failure, not throw the exception.

 Putting an example like this with the modification to `assertError`, plus
 a pointer to the ticket, would be good. Ian can you do?

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5561#comment:6
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5561: assertion overriden by other exceptions

2011-10-19 Thread GHC
#5561: assertion overriden by other exceptions
--+-
  Reporter:  MikolajKonarski  |  Owner:
  Type:  bug  | Status:  closed
  Priority:  normal   |  Milestone:
 Component:  Compiler |Version:  7.3   
Resolution:  fixed|   Keywords:
  Testcase:  assert   |  Blockedby:
Difficulty:   | Os:  Linux 
  Blocking:   |   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by igloo):

  * status:  new = closed
  * testcase:  = assert
  * resolution:  = fixed


Comment:

 Done:
 {{{
 commit cc4774d8b1e2736c4b9171db05451ba6355c98b6
 Author: Ian Lynagh ig...@earth.li
 Date:   Wed Oct 19 22:23:19 2011 +0100

 If an assertion fails, through it rather than a deeper error; fixes
 #5561

 An expression like
 assert False (throw e)
 should throw the assertion failure rather than e
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5561#comment:7
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5561: assertion overriden by other exceptions

2011-10-18 Thread GHC
#5561: assertion overriden by other exceptions
--+-
  Reporter:  MikolajKonarski  |  Owner:
  Type:  bug  | Status:  new   
  Priority:  normal   |  Milestone:
 Component:  Compiler |Version:  7.3   
Resolution:   |   Keywords:
  Testcase:   |  Blockedby:
Difficulty:   | Os:  Linux 
  Blocking:   |   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  |  
--+-

Comment(by igloo):

 We've been debating this on IRC. I think we're all agreed that the current
 behaviour is correct, in the sense that that's how imprecise exceptions
 work. But we could fix ''this case'', as above, to behave as expected.

 The fixed version would still be correct in the sense of imprecise
 exceptions. It would behave differently to user-defined functions that
 aren't similarly fixed, although you can already get differences depending
 on whether GHC decides to inline assertError or not.

 Note that performance of optimised code won't generally suffer, as
 normally optimisations mean assert is disabled anyway.

 Mikolaj and I think it is worth fixing this case. Duncan thinks it will
 just add to the confusion. Any other opinions?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5561#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


[GHC] #5561: assertion overriden by other exceptions

2011-10-17 Thread GHC
#5561: assertion overriden by other exceptions
+---
Reporter:  MikolajKonarski  |   Owner: 
Type:  bug  |  Status:  new
Priority:  normal   |   Component:  Compiler   
 Version:  7.3  |Keywords: 
Testcase:   |   Blockedby: 
  Os:  Linux|Blocking: 
Architecture:  x86_64 (amd64)   | Failure:  Incorrect result at runtime
+---
 The attached file, containing

 {{{
 main = let e1 i = throw Overflow
in assert False (e1 5)
 }}}

 and compiled with

 {{{
 ghc --make -O1 -fno-ignore-asserts test.hs
 }}}

 produces

 {{{
 test: arithmetic overflow
 }}}

 and should produce

 {{{
 test: test.hs:25:11-16: Assertion failed
 }}}

 Works OK, if compiled with

 {{{
 ghc --make -O0 test.hs
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5561
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5561: assertion overriden by other exceptions

2011-10-17 Thread GHC
#5561: assertion overriden by other exceptions
--+-
  Reporter:  MikolajKonarski  |  Owner:
  Type:  bug  | Status:  closed
  Priority:  normal   |  Milestone:
 Component:  Compiler |Version:  7.3   
Resolution:  wontfix  |   Keywords:
  Testcase:   |  Blockedby:
Difficulty:   | Os:  Linux 
  Blocking:   |   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by igloo):

  * status:  new = closed
  * resolution:  = wontfix


Comment:

 This is by design: please see
 http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.4.0.0
 /Control-Exception.html#v:assert for more details.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5561#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5561: assertion overriden by other exceptions

2011-10-17 Thread GHC
#5561: assertion overriden by other exceptions
--+-
  Reporter:  MikolajKonarski  |  Owner:
  Type:  bug  | Status:  new   
  Priority:  normal   |  Milestone:
 Component:  Compiler |Version:  7.3   
Resolution:   |   Keywords:
  Testcase:   |  Blockedby:
Difficulty:   | Os:  Linux 
  Blocking:   |   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by igloo):

  * status:  closed = new
  * resolution:  wontfix =


Comment:

 Sorry, misread it.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5561#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #5561: assertion overriden by other exceptions

2011-10-17 Thread GHC
#5561: assertion overriden by other exceptions
--+-
  Reporter:  MikolajKonarski  |  Owner:
  Type:  bug  | Status:  new   
  Priority:  normal   |  Milestone:
 Component:  Compiler |Version:  7.3   
Resolution:   |   Keywords:
  Testcase:   |  Blockedby:
Difficulty:   | Os:  Linux 
  Blocking:   |   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  |  
--+-

Comment(by igloo):

 I think the fix will be to use `lazy` in `assertError`:
 {{{
 assertError :: Addr# - Bool - a - a
 assertError str predicate v
   | predicate = lazy v
   | otherwise = throw (AssertionFailed (untangle str Assertion failed))
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5561#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


[GHC] #5475: Unthrown exceptions

2011-09-09 Thread GHC
#5475: Unthrown exceptions
--+-
Reporter:  daniel.is.fischer  |   Owner:  
Type:  bug|  Status:  new 
Priority:  normal |   Component:  Compiler
 Version:  7.3|Keywords:  
Testcase: |   Blockedby:  
  Os:  Unknown/Multiple   |Blocking:  
Architecture:  Unknown/Multiple   | Failure:  None/Unknown
--+-
 With today's HEAD, I got five unexpected failures because some exceptions
 weren't thrown as they should've been:
 {{{
../../libraries/stm/tests  stm060 [bad stdout] (hpc)
codeGen/should_run cgrun059 [bad exit code]
 (hpc,optasm,threaded2,dyn)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5475
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)

2010-12-11 Thread GHC
#3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)
+---
  Reporter:  andersk|  Owner:  
  Type:  bug| Status:  closed  
  Priority:  normal |  Milestone:  
 Component:  libraries (other)  |Version:  6.8.2   
Resolution:  fixed  |   Keywords:  
  Testcase: |  Blockedby:  
Difficulty: | Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by ross):

  * type:  proposal = bug


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3931#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

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


Re: [GHC] #4400: Asynchronous exceptions in runInUnboundThread

2010-11-17 Thread GHC
#4400: Asynchronous exceptions in runInUnboundThread
-+--
  Reporter:  basvandijk  |  Owner:  simonmar
  Type:  proposal| Status:  closed  
  Priority:  high|  Milestone:  7.2.1   
 Component:  libraries/base  |Version:  6.12.3  
Resolution:  fixed   |   Keywords:  
  Testcase:  |  Blockedby:  
Difficulty:  | Os:  Unknown/Multiple
  Blocking:  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown|  
-+--
Changes (by simonmar):

  * status:  patch = closed
  * resolution:  = fixed


Comment:

 Pushed, thanks.

 {{{
 Thu Oct 14 22:05:46 BST 2010  Bas van Dijk v.dijk@gmail.com
   * Use throwIO instead of throw in runInBoundThread and
 runInUnboundThread
 Thu Oct 14 22:23:25 BST 2010  Bas van Dijk v.dijk@gmail.com
   * There's no need to explicitly check for blocked status in
 runInUnboundThread when we have mask
 Thu Oct 14 22:27:23 BST 2010  Bas van Dijk v.dijk@gmail.com
   * Catch exceptions in current thread and throw them to the forked thread
 in runInUnboundThread
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4400#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1036: Asynchronous exceptions improvements

2010-11-10 Thread GHC
#1036: Asynchronous exceptions improvements
-+--
  Reporter:  simonmar|  Owner:  simonmar
  Type:  task| Status:  closed  
  Priority:  normal  |  Milestone:  _|_ 
 Component:  Compiler|Version:  6.6 
Resolution:  fixed   |   Keywords:  
  Testcase:  |  Blockedby:  
Difficulty:  Moderate (less than a day)  | Os:  Unknown/Multiple
  Blocking:  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown|  
-+--

Comment(by simonmar):

 Replying to [comment:7 mitar]:
  And how will you allow unmasking in after computation without changing
 the interface of for example bracket? Or will this not be possible
 anymore?

 It won't be possible with the new API.  Can you give me an example where
 it's important to be able to do this?  I haven't come across one myself,
 and it usually helps to have a concrete example to focus on.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1036#comment:8
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1036: Asynchronous exceptions improvements

2010-11-10 Thread GHC
#1036: Asynchronous exceptions improvements
-+--
  Reporter:  simonmar|  Owner:  simonmar
  Type:  task| Status:  closed  
  Priority:  normal  |  Milestone:  _|_ 
 Component:  Compiler|Version:  6.6 
Resolution:  fixed   |   Keywords:  
  Testcase:  |  Blockedby:  
Difficulty:  Moderate (less than a day)  | Os:  Unknown/Multiple
  Blocking:  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown|  
-+--

Comment(by mitar):

 No, just asking because current documentation was explaining this as a
 possibility. So it just have to be explained that this lead to chicken and
 egg situations and was removed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1036#comment:9
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1036: Asynchronous exceptions improvements

2010-11-08 Thread GHC
#1036: Asynchronous exceptions improvements
-+--
  Reporter:  simonmar|  Owner:  simonmar
  Type:  task| Status:  closed  
  Priority:  normal  |  Milestone:  _|_ 
 Component:  Compiler|Version:  6.6 
Resolution:  fixed   |   Keywords:  
  Testcase:  |  Blockedby:  
Difficulty:  Moderate (less than a day)  | Os:  Unknown/Multiple
  Blocking:  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown|  
-+--

Comment(by simonmar):

 Thanks, that was already pointed out by Bas van Dijk on the libraries
 list, I'll push a fix.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1036#comment:6
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #4400: Asynchronous exceptions in runInUnboundThread

2010-11-08 Thread GHC
#4400: Asynchronous exceptions in runInUnboundThread
-+--
Reporter:  basvandijk|Owner:  simonmar
Type:  proposal  |   Status:  patch   
Priority:  high  |Milestone:  7.2.1   
   Component:  libraries/base|  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by simonmar):

  * owner:  = simonmar
  * priority:  normal = high
  * milestone:  = 7.2.1


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4400#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1036: Asynchronous exceptions improvements

2010-11-08 Thread GHC
#1036: Asynchronous exceptions improvements
-+--
  Reporter:  simonmar|  Owner:  simonmar
  Type:  task| Status:  closed  
  Priority:  normal  |  Milestone:  _|_ 
 Component:  Compiler|Version:  6.6 
Resolution:  fixed   |   Keywords:  
  Testcase:  |  Blockedby:  
Difficulty:  Moderate (less than a day)  | Os:  Unknown/Multiple
  Blocking:  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown|  
-+--

Comment(by mitar):

 And how will you allow unmasking in after computation without changing the
 interface of for example bracket? Or will this not be possible anymore?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1036#comment:7
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1036: Asynchronous exceptions improvements

2010-11-07 Thread GHC
#1036: Asynchronous exceptions improvements
-+--
  Reporter:  simonmar|  Owner:  simonmar
  Type:  task| Status:  closed  
  Priority:  normal  |  Milestone:  _|_ 
 Component:  Compiler|Version:  6.6 
Resolution:  fixed   |   Keywords:  
  Testcase:  |  Blockedby:  
Difficulty:  Moderate (less than a day)  | Os:  Unknown/Multiple
  Blocking:  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown|  
-+--
Changes (by mitar):

 * cc: mmi...@… (added)


Comment:

 In HEAD it is currently written:

 {{{
 If you need to unblock asynchronous exceptions again in the exception
 handler, just use 'unblock' as normal.
 }}}

 So unblock still works? Isn't the idea that mask does not allow that
 without restore function? But than standard Haskell bracket will be always
 masked/blocked in after computation? This part of documentation still
 mentions block few times. Probably this should be clarified?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1036#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #4400: Asynchronous exceptions in runInUnboundThread

2010-10-30 Thread GHC
#4400: Asynchronous exceptions in runInUnboundThread
-+--
Reporter:  basvandijk|   Owner:
Type:  proposal  |  Status:  patch 
Priority:  normal|   Component:  libraries/base
 Version:  6.12.3|Keywords:
Testcase:|   Blockedby:
  Os:  Unknown/Multiple  |Blocking:
Architecture:  Unknown/Multiple  | Failure:  None/Unknown  
-+--
Changes (by basvandijk):

  * status:  new = patch


Comment:

 The deadline for this proposal has passed. There was little interest but
 no objections so I'm moving the ticket to 'patch'.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4400#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #4400: Asynchronous exceptions in runInUnboundThread

2010-10-16 Thread GHC
#4400: Asynchronous exceptions in runInUnboundThread
-+--
Reporter:  basvandijk|   Owner:
Type:  proposal  |  Status:  new   
Priority:  normal|   Component:  libraries/base
 Version:  6.12.3|Keywords:
Testcase:|   Blockedby:
  Os:  Unknown/Multiple  |Blocking:
Architecture:  Unknown/Multiple  | Failure:  None/Unknown  
-+--

Comment(by basvandijk):

 [http://thread.gmane.org/gmane.comp.lang.haskell.libraries/14092 Thread]
 on the libraries list.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4400#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #4400: Asynchronous exceptions in runInUnboundThread

2010-10-14 Thread GHC
#4400: Asynchronous exceptions in runInUnboundThread
-+--
Reporter:  basvandijk|   Owner:
Type:  proposal  |  Status:  new   
Priority:  normal|   Component:  libraries/base
 Version:  6.12.3|Keywords:
Testcase:|   Blockedby:
  Os:  Unknown/Multiple  |Blocking:
Architecture:  Unknown/Multiple  | Failure:  None/Unknown  
-+--
 When you throw an asynchronous exception to a thread which is executing:
 `runInUnboundThread m`, `m` will keep executing and there's no way to kill
 it.

 I propose to catch asynchronous exceptions in `runInUnboundThread` and
 throw them to the thread which is executing `m`. `m` in turn can decide to
 catch or ignore them. In case `m` decides to ignore them or to rethrow
 them, the exception will be rethrown in the current thread:

 {{{
 runInUnboundThread :: IO a - IO a
 runInUnboundThread action = do
   bound - isCurrentThreadBound
   if bound
 then do
   mv - newEmptyMVar
   mask $ \restore - do
 tid - forkIO $ Exception.try (restore action) = putMVar mv
 let wait = takeMVar mv `Exception.catch` \(e :: SomeException) -
  Exception.throwTo tid e  wait
 wait = unsafeResult
 else action

 unsafeResult :: Either SomeException a - IO a
 unsafeResult = either Exception.throwIO return
 }}}

 The attached patch implements this behaviour.

 (Note there are two other bug-fix patches in the bundle that this patch
 depends on which can be independently applied.)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4400
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3944: Asynchronous exceptions and laziness bugs (with fixes) in Control.Concurrent.QSem/QSemN

2010-07-09 Thread GHC
#3944: Asynchronous exceptions and laziness bugs (with fixes) in
Control.Concurrent.QSem/QSemN
-+--
  Reporter:  basvandijk  |  Owner:  simonmar
  Type:  bug | Status:  closed  
  Priority:  normal  |  Milestone:  6.14.1  
 Component:  libraries/base  |Version:  6.12.1  
Resolution:  fixed   |   Keywords:  
Difficulty:  | Os:  Unknown/Multiple
  Testcase:  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown|  
-+--
Changes (by simonmar):

  * status:  patch = closed
  * resolution:  = fixed


Comment:

 Fixed:

 {{{
 Thu Jul  8 15:58:19 BST 2010  Simon Marlow marlo...@gmail.com
   * Async-exception safety, and avoid space leaks
   Patch submitted by: Bas van Dijk v.dijk@gmail.com
   Modified slightly by me to remove non-functional changes.

 M ./Control/Concurrent/QSem.hs -9 +12

 Thu Jul  8 11:31:54 BST 2010  Simon Marlow marlo...@gmail.com
   * Async-exception safety, and avoid space leaks
   Patch submitted by: Bas van Dijk v.dijk@gmail.com
   Modified slightly by me to remove non-functional changes.

 M ./Control/Concurrent/QSemN.hs -11 +13
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3944#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1036: Asynchronous exceptions improvements

2010-07-09 Thread GHC
#1036: Asynchronous exceptions improvements
-+--
  Reporter:  simonmar|  Owner:  simonmar
  Type:  task| Status:  closed  
  Priority:  normal  |  Milestone:  _|_ 
 Component:  Compiler|Version:  6.6 
Resolution:  fixed   |   Keywords:  
Difficulty:  Moderate (less than a day)  | Os:  Unknown/Multiple
  Testcase:  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown|  
-+--
Changes (by simonmar):

  * status:  new = closed
  * failure:  = None/Unknown
  * resolution:  = fixed


Comment:

 Done:

 {{{
 Thu Jul  8 16:27:35 BST 2010  Simon Marlow marlo...@gmail.com
   *  New asynchronous exception control API (base parts)

   As discussed on the libraries/haskell-cafe mailing lists
 http://www.haskell.org/pipermail/libraries/2010-April/013420.html

   This is a replacement for block/unblock in the asychronous exceptions
   API to fix a problem whereby a function could unblock asynchronous
   exceptions even if called within a blocked context.

   The new terminology is mask rather than block (to avoid confusion
   due to overloaded meanings of the latter).

   The following is the new API; the old API is deprecated but still
   available for the time being.

   Control.Exception
   -

   mask  :: ((forall a. IO a - IO a) - IO b) - IO b
   mask_ :: IO a - IO a

   uninterruptibleMask :: ((forall a. IO a - IO a) - IO b) - IO b
   uninterruptibleMask_ :: IO a - IO

   getMaskingState :: IO MaskingState

   data MaskingState
 = Unmasked
 | MaskedInterruptible
 | MaskedUninterruptible


   Control.Concurrent
   --

   forkIOUnmasked :: IO () - IO ThreadId

 M ./Control/Concurrent.hs -10 +13
 M ./Control/Concurrent/MVar.hs -8 +8
 M ./Control/Concurrent/QSem.hs -3 +3
 M ./Control/Concurrent/QSemN.hs -3 +3
 M ./Control/Concurrent/SampleVar.hs -5 +5
 M ./Control/Exception.hs -10 +17
 M ./Control/Exception/Base.hs -9 +15
 M ./Control/OldException.hs -19 +14
 M ./Data/HashTable.hs -1 +1
 M ./Data/Typeable.hs -2 +2
 M ./Foreign/Marshal/Pool.hs -3 +3
 M ./GHC/Conc.lhs -8 +20
 M ./GHC/IO.hs -12 +124
 M ./GHC/IO/Handle/Internals.hs -2 +2
 }}}

 and

 {{{
 Thu Jul  8 15:48:51 BST 2010  Simon Marlow marlo...@gmail.com
   * New asynchronous exception control API (ghc parts)

   As discussed on the libraries/haskell-cafe mailing lists
 http://www.haskell.org/pipermail/libraries/2010-April/013420.html

   This is a replacement for block/unblock in the asychronous exceptions
   API to fix a problem whereby a function could unblock asynchronous
   exceptions even if called within a blocked context.

   The new terminology is mask rather than block (to avoid confusion
   due to overloaded meanings of the latter).

   In GHC, we changed the names of some primops:

 blockAsyncExceptions#   - maskAsyncExceptions#
 unblockAsyncExceptions# - unmaskAsyncExceptions#
 asyncExceptionsBlocked# - getMaskingState#

   and added one new primop:

 maskUninterruptible#

   See the accompanying patch to libraries/base for the API changes.

 M ./compiler/prelude/primops.txt.pp -3 +10
 M ./includes/rts/storage/Closures.h -1 +1
 M ./includes/stg/MiscClosures.h -4 +7
 M ./rts/Exception.cmm -45 +111
 M ./rts/Linker.c -3 +4
 M ./rts/Prelude.h +1
 M ./rts/RaiseAsync.c -3 +6
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1036#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3944: Asynchronous exceptions and laziness bugs (with fixes) in Control.Concurrent.QSem/QSemN

2010-05-05 Thread GHC
#3944: Asynchronous exceptions and laziness bugs (with fixes) in
Control.Concurrent.QSem/QSemN
-+--
Reporter:  basvandijk|Owner:  simonmar
Type:  bug   |   Status:  patch   
Priority:  normal|Milestone:  6.14.1  
   Component:  libraries/base|  Version:  6.12.1  
Keywords:|   Difficulty:  
  Os:  Unknown/Multiple  | Testcase:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by simonmar):

  * owner:  = simonmar


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3944#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3944: Asynchronous exceptions and laziness bugs (with fixes) in Control.Concurrent.QSem/QSemN

2010-04-29 Thread GHC
#3944: Asynchronous exceptions and laziness bugs (with fixes) in
Control.Concurrent.QSem/QSemN
-+--
Reporter:  basvandijk|Owner:  
Type:  bug   |   Status:  patch   
Priority:  normal|Milestone:  6.14.1  
   Component:  libraries/base|  Version:  6.12.1  
Keywords:|   Difficulty:  
  Os:  Unknown/Multiple  | Testcase:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by igloo):

  * status:  new = patch
  * milestone:  = 6.14.1


Comment:

 Thanks for the patch, we'll take a look.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3944#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)

2010-04-25 Thread GHC
#3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)
+---
  Reporter:  andersk|  Owner:  
  Type:  proposal   | Status:  closed  
  Priority:  normal |  Milestone:  
 Component:  libraries (other)  |Version:  6.8.2   
Resolution:  fixed  |   Keywords:  
Difficulty: | Os:  Unknown/Multiple
  Testcase: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  Patch:  0   
+---
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed
  * patch:  = 0


Comment:

 Done:
 {{{
 Sun Apr 25 12:02:45 PDT 2010  Ian Lynagh ig...@earth.li
   * Revert changes that require Cabal-1.6 or later; fixes GHC trac #3931
   We want to remain compatible with older compilers, with older Cabals,
   for now.
 }}}
 and 0.1.1.2 is on hackage.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3931#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3997: Lazy I/O and asynchronous exceptions don't mix well

2010-04-21 Thread GHC
#3997: Lazy I/O and asynchronous exceptions don't mix well
--+-
  Reporter:  simonmar |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  6.14.1  
 Component:  libraries/base   |Version:  6.12.1  
Resolution:  fixed|   Keywords:  
Difficulty:   | Os:  Unknown/Multiple
  Testcase:   |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  |  Patch:  0   
--+-
Changes (by simonmar):

  * status:  new = closed
  * resolution:  = fixed
  * patch:  = 0


Comment:

 I've fixed this in the IO library:

 {{{
 Wed Apr 21 10:49:32 BST 2010  Simon Marlow marlo...@gmail.com
   * raise asynchronous exceptions asynchronously (#3997)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3997#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3997: Lazy I/O and asynchronous exceptions don't mix well

2010-04-20 Thread GHC
#3997: Lazy I/O and asynchronous exceptions don't mix well
-+--
Reporter:  simonmar  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  6.14.1 
   Component:  libraries/base|  Version:  6.12.1 
Keywords:|   Difficulty: 
  Os:  Unknown/Multiple  | Testcase: 
Architecture:  Unknown/Multiple  |  Failure:  Incorrect result at runtime
-+--
 This program:

 {{{
 import Control.Concurrent
 import Control.Exception

 main = do
   s - getContents
   t - forkIO $ evaluate (length s)  return ()
   threadDelay 1000
   killThread t
   print (length s)
 }}}

 results in

 {{{
 $ ./async
 async: thread killed
 }}}

 when really it should just wait for input.

 The problem is #2558, but since I'm not sure that #2558 has a general
 solution (see comments on that ticket) I thought I'd open a ticket for
 this specific case.  It's amazing nobody has complained about this before.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3997
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)

2010-04-15 Thread GHC
#3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)
-+--
Reporter:  andersk   |   Owner:   
Type:  proposal  |  Status:  new  
Priority:  normal|   Component:  libraries (other)
 Version:  6.8.2 |Keywords:   
  Os:  Unknown/Multiple  |Testcase:   
Architecture:  Unknown/Multiple  | Failure:  None/Unknown 
-+--

Comment(by andersk):

 Comments from the libraries list:

 Isaac Dupree: “And hmm, I think people using old GHC are nevertheless
 supposed to update their Cabal and cabal-install (if they want packages
 from Hackage).  But in this case, easier compatibility seems useful.”

 Ian Lynagh: “Reverting the change sounds like the right thing to me.”

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3931#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)

2010-03-24 Thread GHC
#3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)
-+--
Reporter:  andersk   |   Owner:   
Type:  proposal  |  Status:  new  
Priority:  normal|   Component:  libraries (other)
 Version:  6.8.2 |Keywords:   
  Os:  Unknown/Multiple  |Testcase:   
Architecture:  Unknown/Multiple  | Failure:  None/Unknown 
-+--
Changes (by andersk):

  * type:  bug = proposal


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3931#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)

2010-03-20 Thread GHC
#3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)
-+--
Reporter:  andersk   |   Owner:   
Type:  bug   |  Status:  new  
Priority:  normal|   Component:  libraries (other)
 Version:  6.8.2 |Keywords:   
  Os:  Unknown/Multiple  |Testcase:   
Architecture:  Unknown/Multiple  | Failure:  None/Unknown 
-+--
 With ghc 6.8.2 on Debian lenny, with Cabal-1.2.3.0 and cabal-
 install-0.4.0:

 {{{
 $ cabal install extensible-exceptions
 Downloading 'extensible-exceptions-0.1.1.1'...
 Warning: Unknown fields: bug-reports (line 6)
 Fields allowed in this section:
 name, version, cabal-version, build-type, license, license-file,
 copyright, maintainer, build-depends, stability, homepage,
 package-url, synopsis, description, category, author, tested-with,
 data-files, extra-source-files, extra-tmp-files
 Warning: Unknown section type: source-repository ignoring...
 Warning: Ignoring trailing declarations.
 cabal: cannot satisfy dependency Cabal=1.6
 }}}

 This is a regression from extensible-exceptions-0.1.1.0, which worked
 fine.  Since compatibility with GHC  6.10 is the entire point of the
 extensible-exceptions package, this should probably be fixed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3931
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)

2010-03-20 Thread GHC
#3931: extensible-exceptions 0.1.1.1 fails to build on GHC 6.8 (Cabal 1.2)
-+--
Reporter:  andersk   |   Owner:   
Type:  bug   |  Status:  new  
Priority:  normal|   Component:  libraries (other)
 Version:  6.8.2 |Keywords:   
  Os:  Unknown/Multiple  |Testcase:   
Architecture:  Unknown/Multiple  | Failure:  None/Unknown 
-+--

Comment(by andersk):

 extensible-exceptions 0.1.1.1 works fine if the Cabal dependency is
 lowered back to =1.2 and the source-repository section is moved to the
 bottom of the .cabal file.

 (However, Hackage will not currently accept a package like that, and
 instead requires the source-repository section to be removed entirely.
 See [http://hackage.haskell.org/trac/hackage/ticket/639].)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3931#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3628: exceptions reported to stderr when they propagate past forkIO

2009-10-30 Thread GHC
#3628: exceptions reported to stderr when they propagate past forkIO
-+--
Reporter:  duncan|  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  6.10.4|   Severity:  normal  
Keywords:|   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 It's not entirely obvious what to do with exceptions that do not get
 handled within a `forkIO` however reporting them on stderr (or on Windows
 popping up a message dialog) does not seem right.

 We do not have other cases where errors are logged to stderr. The only
 such case is an exception terminating Main.main (and that's special
 because it terminates the whole process). If it is vital that someone do
 something with exceptions in forkIO threads then they should be propagated
 to another thread, in the worst case the main thread.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3628
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3628: exceptions reported to stderr when they propagate past forkIO

2009-10-30 Thread GHC
#3628: exceptions reported to stderr when they propagate past forkIO
-+--
Reporter:  duncan|Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.14.1  
   Component:  Compiler  |  Version:  6.10.4  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = 6.14.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3628#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2655: Control.Exception's Haddock document drop instruction about Extensible Exceptions

2009-01-31 Thread GHC
#2655: Control.Exception's Haddock document drop instruction about Extensible
Exceptions
-+--
Reporter:  shelarcy  |Owner:  igloo   
Type:  bug   |   Status:  closed  
Priority:  high  |Milestone:  6.10.2  
   Component:  Documentation |  Version:  6.9 
Severity:  normal|   Resolution:  fixed   
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 Thanks for the report. I've updated the docs.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2655#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2910: throwTo can block indefinitely when target thread finishes with exceptions blocked

2009-01-11 Thread GHC
#2910: throwTo can block indefinitely when target thread finishes with 
exceptions
blocked
-+--
Reporter:  int-e |Owner:  igloo   
Type:  merge |   Status:  closed  
Priority:  normal|Milestone:  6.10.2  
   Component:  Runtime System|  Version:  6.10.1  
Severity:  normal|   Resolution:  fixed   
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 All 7 merged

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2910#comment:8
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2910: throwTo can block indefinitely when target thread finishes with exceptions blocked

2009-01-07 Thread GHC
#2910: throwTo can block indefinitely when target thread finishes with 
exceptions
blocked
-+--
Reporter:  int-e |Owner:  igloo   
Type:  merge |   Status:  new 
Priority:  normal|Milestone:  6.10.2  
   Component:  Runtime System|  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonmar):

 Replying to [comment:3 int-e]:
  As the patches I just attached suggest, this race is not completely
 fixed. (I'm pretty certain - Conal's TestRace program locks up without the
 first patch, but works fine so far with it. I also have a modified version
 that logs thread creation and throwTo and shows the program lock up with
 all threads finished except the main thread, which is blocked on an
 exception.)
 
  The second patch contains changes unrelated to this bug which I'm not
 100% certain about - but they felt necessary.

 Thanks - it's nice to have someone else looking at this code!

 In response to your patches:

 {{{
 hunk ./rts/RaiseAsync.c 418
 // Unblocking BlockedOnSTM threads requires the TSO to be
 // locked; see STM.c:unpark_tso().
 if (target-why_blocked != BlockedOnSTM) {
 +   unlockTSO(target);
 goto retry;
 }
 if ((target-flags  TSO_BLOCKEX) 
 }}}

 well spotted.

 {{{
 hunk ./rts/RaiseAsync.c 440
 // thread is blocking exceptions, and block on its
 // blocked_exception queue.
 lockTSO(target);
 +   if (target-why_blocked != BlockedOnCCall 
 +   target-why_blocked != BlockedOnCCall_NoUnblockExc) {
 +   unlockTSO(target);
 +   return;
 +   }
 blockedThrowTo(cap,source,target);
 *out = target;
 return THROWTO_BLOCKED;
 }}}

 again, well spotted - except that we want `goto retry` rather than
 `return`.

 {{{
 hunk ./rts/RaiseAsync.c 267
 target = target-_link;
 goto retry;
 }
 +   // The thread may also have finished in the meantime.
 +   if (target-what_next == ThreadKilled
 +   || target-what_next == ThreadComplete) {
 +   unlockTSO(target);
 +   return THROWTO_SUCCESS;
 +   }
 blockedThrowTo(cap,source,target);
 *out = target;
 return THROWTO_BLOCKED;
 }}}

 `lockTSO()` doesn't lock the `what_next` field, only the
 `blocked_exceptions` field, so I think this change is not necessary.

 {{{
 hunk ./rts/RaiseAsync.c 555
  void
  awakenBlockedExceptionQueue (Capability *cap, StgTSO *tso)
  {
 +lockTSO(tso);
 +// Taking the tso lock before the following check assures that we
 +// wait for any throwTo that may just be adding a new thread to the
 +// queue. This is essential, because we may not get another chance
 +// to wake up that thread.
  if (tso-blocked_exceptions != END_TSO_QUEUE) {
 hunk ./rts/RaiseAsync.c 561
 -   lockTSO(tso);
 awakenBlockedQueue(cap, tso-blocked_exceptions);
 tso-blocked_exceptions = END_TSO_QUEUE;
 hunk ./rts/RaiseAsync.c 563
 -   unlockTSO(tso);
  }
 hunk ./rts/RaiseAsync.c 564
 +unlockTSO(tso);
  }
 }}}

 This is not necessary.  However, while figuring out why, I did find the
 real bug.  Threads that fall through the cracks and end up on the
 blocked_exceptions list of a finished or blocked target thread are
 supposed to be caught by the GC (see comments at line 216 in
 `MarkWeak.c`).  However, this wasn't working in the case when the target
 thread had finished, because `maybePerformBlockedException()` wasn't
 handling the `ThreadComplete` or `ThreadKilled` case, so I've fixed that.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2910#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2910: throwTo can block indefinitely when target thread finishes with exceptions blocked

2009-01-07 Thread GHC
#2910: throwTo can block indefinitely when target thread finishes with 
exceptions
blocked
-+--
Reporter:  int-e |Owner:  igloo   
Type:  merge |   Status:  new 
Priority:  normal|Milestone:  6.10.2  
   Component:  Runtime System|  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by int-e):

 Replying to [comment:4 simonmar]:
  Thanks - it's nice to have someone else looking at this code!
 You're welcome.

  `lockTSO()` doesn't lock the `what_next` field, only the
 `blocked_exceptions` field, so I think this change is not necessary.

 Ah, I see. But I believe that the change still makes sense - see below.

  Threads that fall through the cracks and end up on the
 blocked_exceptions list of a finished or blocked target thread are
 supposed to be caught by the GC ...

 And that's the part I missed, although admittedly I'm a bit unhappy about
 waiting for the next GC. Does the RTS perform a GC when it finds no other
 work? In any case, there'll be some wait.

 Now I believe we can prevent this from happening, with those two hunks
 above. The key idea is that once the {{{what_next}}} field is set to
 {{{ThreadComplete}}} or {{{ThreadKilled}}}, it will not be modified again.

 As you wrote in the comment in {{{scheduleHandleThreadFinished}}},
 {{{what_next}}} has already been set when
 {{{awakenBlockedExceptionQueue}}} is called. So the only scenario we have
 to prevent is that a thread throwing an exception finds its target
 running, and then adds itself to the target's {{{blocked_exception}}}
 queue, with the target thread completing and running
 {{{awakenExceptionQueue}}} inbetween those two steps.

 This can be accomplished by making {{{awakenExceptionQueue}}} take the TSO
 lock every time, *and* checking whether the target has finished between
 taking the TSO lock and calling {{{blockedThrowTo}}} for all calls to
 {{{blockedThrowTo}}}, unless we can prove that the thread cannot finish in
 the meantime.

 My changes only covered the {{{NotBlocked}}} case. I believe that in the
 {{{Blocked*}}} cases, the thread cannot finish in the meantime (they lock
 the TSO, directly or indirectly, and then check that the thread is still
 blocked - which implies that it has not finished), but I'm 100% not
 certain.

 To summarize: We would not use the TSO lock to protect the {{{what_next}}}
 field - we'd use (or abuse?) it to prevent a specific race between
 {{{blockedThrowTo}}} and {{{awakenExceptionQueue}}}.

 I think the benefits are clear: We avoid one case of the RTS having to
 wait for a GC.

 The cost seems bearable: {{{awakenExceptionQueue}}} is only called when a
 thread finishes or when it returns from a C call (and in the latter case,
 we could continue to use the old variant). Both cases aren't exactly fast
 paths. Then there's a cost in code complexity (the reasoning is fairly
 tricky) - but that's your judgement call.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2910#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2910: throwTo can block indefinitely when target thread finishes with exceptions blocked

2009-01-07 Thread GHC
#2910: throwTo can block indefinitely when target thread finishes with 
exceptions
blocked
-+--
Reporter:  int-e |Owner:  igloo   
Type:  merge |   Status:  new 
Priority:  normal|Milestone:  6.10.2  
   Component:  Runtime System|  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonmar):

 Yes, I realise your patch was aimed at closing the race.  I was worried
 about the cost of doing an unconditional `lockTSO` on thread exit, and the
 complexity of the invariant.  However, I haven't been able to measure a
 difference in performance (yet!) so I'll probably go with your version
 (but also with my fixes, a little extra robustness won't hurt).

 The GC runs after 0.3 seconds of non-activity, BTW.  This is tunable with
 the `+RTS -I` flag.

 Also, while playing with Conal's TestRace program I found two more races,
 patches to follow.  yay!

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2910#comment:6
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2910: throwTo can block indefinitely when target thread finishes with exceptions blocked

2009-01-07 Thread GHC
#2910: throwTo can block indefinitely when target thread finishes with 
exceptions
blocked
-+--
Reporter:  int-e |Owner:  igloo   
Type:  merge |   Status:  new 
Priority:  normal|Milestone:  6.10.2  
   Component:  Runtime System|  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonmar):

 More patches to merge:

 {{{
 Wed Jan  7 11:20:26 GMT 2009  Simon Marlow marlo...@gmail.com
   * putMVar and takeMVar: add write_barrier() to fix race with throwTo

 Wed Jan  7 12:06:52 GMT 2009  Simon Marlow marlo...@gmail.com
   * fix a race where the timer signal could remain turned off, leading to
 deadlock

 Wed Jan  7 12:07:34 GMT 2009  Simon Marlow marlo...@gmail.com
   * maybePerformBlockedException() should handle
 ThreadComplete/ThreadKilled
   Part of the fix for #2910

 Wed Jan  7 12:08:08 GMT 2009  Bertram Felgenhauer in...@gmx.de
   * Fix two more locking issues in throwTo()

 Wed Jan  7 12:11:42 GMT 2009  Simon Marlow marlo...@gmail.com
   * add comment

 Wed Jan  7 14:05:07 GMT 2009  Simon Marlow marlo...@gmail.com
   * Close the races between throwTo and thread completion
   Any threads we missed were being caught by the GC (possibly the idle
   GC if the system was otherwise inactive), but that's not ideal.  The
   fix (from Bertram Felgenhauer) is to use lockTSO to synchronise,
   imposing an unconditional lockTSO on thread exit.  I couldn't measure
   any performance overhead from doing this, so it seems reasonable.
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2910#comment:7
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2910: throwTo can block indefinitely when target thread finishes with exceptions blocked

2009-01-06 Thread GHC
#2910: throwTo can block indefinitely when target thread finishes with 
exceptions
blocked
-+--
Reporter:  int-e |Owner:  simonmar
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.10.2  
   Component:  Runtime System|  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by simonmar):

  * owner:  = simonmar
  * difficulty:  = Easy (1 hr)
  * os:  Linux = Unknown/Multiple
  * architecture:  x86 = Unknown/Multiple
  * milestone:  = 6.10.2

Comment:

 Good bug.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2910#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2910: throwTo can block indefinitely when target thread finishes with exceptions blocked

2009-01-06 Thread GHC
#2910: throwTo can block indefinitely when target thread finishes with 
exceptions
blocked
-+--
Reporter:  int-e |Owner:  igloo   
Type:  merge |   Status:  new 
Priority:  normal|Milestone:  6.10.2  
   Component:  Runtime System|  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by simonmar):

  * owner:  simonmar = igloo
  * type:  bug = merge

Comment:

 Fixed:

 {{{
 Tue Jan  6 15:32:54 GMT 2009  Simon Marlow marlo...@gmail.com
   * wake up the blocked exception queue on ThreadFinished; fixes #2910
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2910#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2910: throwTo can block indefinitely when target thread finishes with exceptions blocked

2009-01-06 Thread GHC
#2910: throwTo can block indefinitely when target thread finishes with 
exceptions
blocked
-+--
Reporter:  int-e |Owner:  igloo   
Type:  merge |   Status:  new 
Priority:  normal|Milestone:  6.10.2  
   Component:  Runtime System|  Version:  6.10.1  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Easy (1 hr) 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by int-e):

 As the patches I just attached suggest, this race is not completely fixed.
 (I'm pretty certain - Conal's TestRace program locks up without the first
 patch, but works fine so far with it. I also have a modified version that
 logs thread creation and throwTo and shows the program lock up with all
 threads finished except the main thread, which is blocked on an
 exception.)

 The second patch contains changes unrelated to this bug which I'm not 100%
 certain about - but they felt necessary.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2910#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2910: throwTo can block indefinitely when target thread finishes with exceptions blocked

2009-01-03 Thread GHC
#2910: throwTo can block indefinitely when target thread finishes with 
exceptions
blocked
---+
Reporter:  int-e   |  Owner:
Type:  bug | Status:  new   
Priority:  normal  |  Component:  Runtime System
 Version:  6.10.1  |   Severity:  normal
Keywords:  |   Testcase:
  Os:  Linux   |   Architecture:  x86   
---+
 {{{throwTo}}} can block indefinitely when the target thread has exceptions
 blocked at thread creation time. The following test program demonstrates
 this problem.

 {{{
 import Control.Exception
 import GHC.Conc

 main = do
 t1 - block $ forkIO yield
 t2 - forkIO $ killThread t1
 threadDelay 100
 threadStatus t1 = print
 threadStatus t2 = print
 }}}
 can print (and does fairly reliably for me)
 {{{
 ThreadFinished
 ThreadBlocked BlockedOnException
 }}}
 See also
 http://www.haskell.org/pipermail/reactive/2009-January/000197.html

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2910
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2655: Control.Exception's Haddock document drop instruction about Extensible Exceptions

2008-12-07 Thread GHC
#2655: Control.Exception's Haddock document drop instruction about Extensible
Exceptions
-+--
Reporter:  shelarcy  |Owner:  igloo   
Type:  bug   |   Status:  new 
Priority:  high  |Milestone:  6.10.2  
   Component:  Documentation |  Version:  6.9 
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * owner:  = igloo

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2655#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2655: Control.Exception's Haddock document drop instruction about Extensible Exceptions

2008-11-11 Thread GHC
#2655: Control.Exception's Haddock document drop instruction about Extensible
Exceptions
--+-
 Reporter:  shelarcy  |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  high  |  Milestone:  6.10.2  
Component:  Documentation |Version:  6.9 
 Severity:  normal| Resolution:  
 Keywords:| Difficulty:  Unknown 
 Testcase:|   Architecture:  Unknown/Multiple
   Os:  Unknown/Multiple  |  
--+-
Changes (by igloo):

  * milestone:  6.10.1 = 6.10.2

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2655#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2655: Control.Exception's Haddock document drop instruction about Extensible Exceptions

2008-10-12 Thread GHC
#2655: Control.Exception's Haddock document drop instruction about Extensible
Exceptions
--+-
 Reporter:  shelarcy  |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  high  |  Milestone:  6.10.1  
Component:  Documentation |Version:  6.9 
 Severity:  normal| Resolution:  
 Keywords:| Difficulty:  Unknown 
 Testcase:|   Architecture:  Unknown/Multiple
   Os:  Unknown/Multiple  |  
--+-
Changes (by igloo):

  * priority:  normal = high
  * difficulty:  = Unknown
  * milestone:  = 6.10.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2655#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2655: Control.Exception's Haddock document drop instruction about Extensible Exceptions

2008-10-05 Thread GHC
#2655: Control.Exception's Haddock document drop instruction about Extensible
Exceptions
-+--
Reporter:  shelarcy  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Component:  Documentation   
 Version:  6.9   |Severity:  normal  
Keywords:|Testcase:  
Architecture:  Unknown/Multiple  |  Os:  Unknown/Multiple
-+--
 GHC 6.10.1 beta replaced old Control.Exception module by Extensible
 Exceptions. But Control.Exception module doesn't have any instruction
 about Extensible Exceptions now.

 Description doesn't have imformation about An Extensible Dynamically-
 Typed Hierarchy of Exceptions. There is no imformation and example about
 Extensible exception's new fuctions and types.

 So, people can't switch to new exception library easily.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2655
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2655: Control.Exception's Haddock document drop instruction about Extensible Exceptions

2008-10-05 Thread GHC
#2655: Control.Exception's Haddock document drop instruction about Extensible
Exceptions
-+--
Reporter:  shelarcy  |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Documentation |  Version:  6.9 
Severity:  normal|   Resolution:  
Keywords:| Testcase:  
Architecture:  Unknown/Multiple  |   Os:  Unknown/Multiple
-+--
Changes (by shelarcy):

 * cc: [EMAIL PROTECTED] (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2655#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2483: mapException type under extensible exceptions

2008-08-03 Thread GHC
#2483: mapException type under extensible exceptions
-+--
Reporter:  Isaac Dupree  |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Component:  libraries/base
 Version:  6.9   |Severity:  normal
Keywords:|Testcase:
Architecture:  Unknown   |  Os:  Unknown   
-+--
 The old type is {{{mapException :: (Exception - Exception) - a - a}}}

 e.g. you might map have mapped a !DivZeroError to a dynamic exception of
 some sort (gee, I don't know).  Of course the dynamic exception will be
 less of a hack when the code is converted to extensible exceptions.

 In any case that doesn't work with the 6.9-current signature
 {{{mapException :: (Exception e) = (e - e) - a - a}}}

 because !DivZeroErrors are not necessarily the same type as the exceptions
 you're throwing, obviously!

 The old signature is closer in meaning to {{{mapException ::
 (SomeException - SomeException) - a - a}}}

 which is isomorphic to {{{mapException :: (Exception e1, Exception e2) =
 (e1 - e2) - a - a}}}

 which I think is the inferred type, and ought to be the explicit type too.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2483
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2419: Extensible exceptions

2008-08-01 Thread GHC
#2419: Extensible exceptions
+---
 Reporter:  igloo   |  Owner: 
 Type:  proposal| Status:  closed 
 Priority:  normal  |  Milestone:  Not GHC
Component:  libraries/base  |Version:  6.8.3  
 Severity:  normal  | Resolution:  fixed  
 Keywords:  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 The concensus was that something should be done, although opinions
 differed on the finer points (e.g. whether to replace the old
 `Control.Exception` or add `Control.NewException`). I have applied more or
 less my original patches, although I will be further tweaking them shortly
 to incorporate some ideas from the thread (e.g. using `onException` rather
 than `catchAny`, and removing the `catchAny` function).

 There was also some discussion of the hierarchy, and of the difference
 between errors and exceptions. Designing (or evolving) a good hierarchy
 remains to be done.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2419#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2419: Extensible exceptions

2008-07-04 Thread GHC
#2419: Extensible exceptions
---+
Reporter:  igloo   |   Owner: 
Type:  proposal|  Status:  new
Priority:  normal  |   Milestone:  Not GHC
   Component:  libraries/base  | Version:  6.8.3  
Severity:  normal  |Keywords: 
  Difficulty:  Unknown |Testcase: 
Architecture:  Unknown |  Os:  Unknown
---+
 This is a proposal to replace the current exception mechanism in the
 base library with extensible exceptions.

 It also reimplements the existing exceptions on top of extensible
 exceptions, for legacy applications.

 Proposed deadline: 25th July.

 = What are extensible exceptions? =

 Simon's extensible extensions paper is very easy to read, and describes
 the problems and proposed solution very well:
 http://www.haskell.org/~simonmar/papers/ext-exceptions.pdf
 I won't try to reproduce everything the paper says here, but here is the
 list of what we want extracted from it:

  * A hierarchy of exception types, such that a particular catch can choose
 to catch only exceptions that belong to a particular subclass and re-throw
 all others.
  * A way to add new exception types at any point in the hierarchy from
 library or program code.
  * The boilerplate code required to add a new type to the exception
 hierarchy should be minimal.
  * Exceptions should be thrown and caught using the same primitives,
 regardless of the types involved.

 I heartily recommend having a read through of the paper.

 = Patches and examples =

 The patches are here:
 http://darcs.haskell.org/ext-excep/
 along with `Examples.hs`, which gives some examples of using it.

 The patches aren't polished; if this proposal is accepted then there is
 some more work to do, moving things around inside the base package to
 simplify the dependencies, and to maximise the amount of code that can
 be shared between all the impls. There's also some GHC-specific fiddling
 to be done, to make GHC.!TopHandler use the new exceptions. This can all
 be done without further library proposals, though.

 Also, currently it derives Data.Typeable, which is unportable, but we
 can easily work around that. The only extensions that I don't think that
 we can do without are !ExistentialQuantification and Rank2Types.
 !DeriveDataTypeable makes the implementation easier, and
 !DeriveDataTypeable and !PatternSignatures make using it easier.

 = Library function differences =

 As far as the library functions are concerned, here are the main
 differences:

 The old and new types for catch are:
 {{{
 Old: catch ::IO a - (Exception - IO a) - IO a
 New: catch :: Exception e = IO a - (e - IO a) - IO a
 }}}
 i.e. catch can now catch any type of exception; we don't have to force
 all the different types of extension into one fixed datatype.

 All the other exception functions are similarly changed to handle any
 type of extension, e.g. we now have
 {{{
 try :: Exception e = IO a - IO (Either e a)
 }}}

 Now that you can write handlers for different exception types, you might
 want to catch multiple different types at the same point. You can use
 catches for this. For example, the !OldException module needs to catch
 all the new exception types and put them into the old Exception type, so
 that the legacy handler can be run on them. It looks like this:
 {{{
 catch :: IO a - (Exception - IO a) - IO a
 catch io handler =
 io `catches`
 [Handler (\e - handler e),
  Handler (\exc - handler (ArithException exc)),
  Handler (\exc - handler (ArrayException exc)),
  ...]
 }}}
 where the first Handler deals with exceptions of type Exception, the
 second those of type !ArithException, and so on.

 If you want to catch all exceptions, e.g. if you want to cleanup and
 rethrow the exception, or just print the exception at the top-level, you
 can use the new function catchAny:
 {{{
 catchAny :: IO a - (forall e . Exception e = e - IO a) - IO a
 }}}
 You can happily write
 {{{
 `catchAny` \e - print e
 }}}
 where
 {{{
 `catch` \e - print e
 }}}
 would give you an ambiguous type variable error.

 There's also
 {{{
 ignoreExceptions :: IO () - IO ()
 }}}
 which can be used instead of try for things like
 {{{
 ignoreExceptions (hClose h)
 }}}
 (where we don't look at the result, so the exception type would be
 ambiguous if we used try). (I'm not sure if this is the best name for
 this function).

 All the build failures I've seen with the new exceptions library have
 been cases where you need to change a catch to catchAny, try to
 ignoreExceptions, or occassionally a different function, e.g.
 bracket or handle, is used to handle any extension, so adding a type
 signature involving the !SomeException type

Re: [GHC] #2419: Extensible exceptions

2008-07-04 Thread GHC
#2419: Extensible exceptions
+---
 Reporter:  igloo   |  Owner: 
 Type:  proposal| Status:  new
 Priority:  normal  |  Milestone:  Not GHC
Component:  libraries/base  |Version:  6.8.3  
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Comment (by igloo):

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

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2419#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #911: Better information about the location of exceptions

2008-01-24 Thread GHC
#911: Better information about the location of exceptions
-+--
 Reporter:  simonmar |  Owner: 
 Type:  feature request  | Status:  closed 
 Priority:  normal   |  Milestone:  _|_
Component:  Runtime System   |Version:  6.4.2  
 Severity:  normal   | Resolution:  fixed  
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Changes (by simonmar):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 The User's Guide has a section on Debugging Exceptions.

 I also improved the entry in the FAQ about head [] to point to the
 relevant part of the docs.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/911#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1171: GHC doesn't respect the imprecise exceptions semantics

2007-12-05 Thread GHC
#1171: GHC doesn't respect the imprecise exceptions semantics
--+-
 Reporter:  neil  |  Owner:  
 Type:  bug   | Status:  reopened
 Priority:  low   |  Milestone:  _|_ 
Component:  Compiler  |Version:  6.6 
 Severity:  normal| Resolution:  
 Keywords:| Difficulty:  Unknown 
 Testcase:  cg059 |   Architecture:  Multiple
   Os:  Multiple  |  
--+-
Comment (by Isaac Dupree):

 Stefan O'Rear happened to write in haskell-cafe a performance reason for
 allowing non-termination to throw any exception:

 When you see an expression of the form:

 f a

 you generally want to evaluate a before applying; but if a is _|_, this
 will only give the correct result if f a = _|_.  Merely 'guaranteed to
 evaluate' misses out on some common cases, for instance ifac:
 {{{
 ifac 0 a = a
 ifac n a = ifac (n - 1) (a * n)
 }}}
 ifac is guaranteed to either evaluate a, or go into an infinite loop -
 so it can be found strict, and unboxed.  Whereas 'ifac -1 (error moo)'
 is an infinite loop, so using a definition based on evaluation misses
 this case.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1171#comment:13
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1171: GHC doesn't respect the imprecise exceptions semantics

2007-03-02 Thread GHC
#1171: GHC doesn't respect the imprecise exceptions semantics
--+-
 Reporter:  neil  |  Owner:  
 Type:  bug   | Status:  reopened
 Priority:  low   |  Milestone:  _|_ 
Component:  Compiler  |Version:  6.6 
 Severity:  normal| Resolution:  
 Keywords:| Difficulty:  Unknown 
 Testcase:  cg059 |   Architecture:  Multiple
   Os:  Multiple  |  
--+-
Comment (by igloo):

 The below is from e-mail and IRC conversations that happened in parallel
 with this bug report.
 I've editted things slightly to make them flow better, but hopefully
 haven't changed any important meanings.

 

 __I said:``__

 In http://research.microsoft.com/~simonpj/Papers/imprecise-exn.htm
 I think you claim in section 4.3, in the rationale for the Bad case,
 that if we have
 {{{
 f x = case x of
   True  - error A
   False - error B
 }}}
 then the call
 {{{
 f (error X)
 }}}
 is allowed to raise B, as this permits transformations like
 {{{
 f' x = let b = error B
in b `seq` case x of
   True  - error A
   False - b
 }}}
 which in turn is justified because the case expression is strict in
 {{{
 error B
 }}}
 (as well as every other expression).

 However, the Ok case tells me that if I call
 {{{
 f True
 }}}
 then I can get the errors raised by the
 {{{
 True  - error A
 }}}
 branch only. Thus it must raise A. But with the above transformation f'
 raises B.


 I also think that this behaviour is very confusing to users; it makes
 sense that
 {{{
 error A + error B
 }}}
 needs to evaluate both values, so throwing either exception is
 reasonable, but in
 {{{
 f True
 }}}
 it is obvious that A is raised and B is not!



 Traditionally, we would say that e is strict in x if
 {{{
 x = _|_=e = _|_
 }}}
 However, with the set-based imprecise exceptions, in which we
 distinguish between different bottoms, it seems to me that a better
 definition would be that e is strict in x if
 {{{
 x = Bad xs=e = Bad ys  and  xs \subseteq ys
 }}}

 Thus, for example, a case can throw an exception if either the scrutinee
 can or /all/ the branches can, i.e. in the Bad case in 4.3 we take the
 big intersection rather than big union.

 So we wouldn't be allowed to pull
 {{{
 error B
 }}}
 out of the above case, but we would still be able to translate
 {{{
 case x of
 True - y
 False - y
 }}}
 into
 {{{
 y `seq` case x of
 True - y
 False - y
 }}}

 I am also unconvinced by a non-terminating program being allowed to
 throw anything it likes. It seems much nicer to permit it only to either
 not terminate or to throw a special exception, here-on written N.


 I haven't written a denotational semantics or anything, so perhaps this
 would all unravel if I tried, but here are some example definitions
 followed by what exceptions I think various expressions ought to be able
 to throw; are there any obvious nasty corners I have left unexplored?:

 {{{
 f x = case x of
   True  - error A
   False - error B

 g x = case x of
   True  - error C
   False - error C

 h () () = ()

 i = i

 j = error D + j

 -

 f True  A
 f (error E)   E
 g True  C
 g (error F)   C or F
 h (error G) (error H)   G or H
 i   N or non-termination
 j   D, N or non-termination
 }}}

 I also haven't looked into the performance implications, although
 personally I'd prefer a semantics that is more intuitive along with a
 few more bang patterns sprinkled around.

 

 __Simon PJ replied:``__

 I think you are basically right here.  Another way to say it is this. In
 4.5 we
 claim that GHC's transformations can reduce the set of possible exceptions
 from
 a term, but not increase it. But the (current) strictness analysis
 transformation increases it.  I agree that is undesirable.

 As I say on the Trac, we could change this at the cost of making fewer
 functions
 strict.  I can tell anyone how to do this, if you want.  It would be good
 to
 measure the performance impact of doing so.

 

 __Simon M__ has a memory that there is some problem, possibly related to
 monotonicity, with only allowing non-terminating programs to either not
 terminate or throw a special non-termination error, rather than allowing
 them to behave like any bottom they wish as the imprecise exceptions paper
 allows them to. However, he can't remember what the problem actually is;
 if anyone can then it would be good to have it documented.

 

 Regarding __Simon PJ__``'s earlier comment
 {{{
 It's easily stopped, too, by stopping GHC treating error like bottom;
 but that would make many

Re: [GHC] #1171: GHC doesn't respect the imprecise exceptions semantics

2007-02-28 Thread Neil Mitchell

Hi


 In response to Neil: why use `unsafePerformIO` rather than IO exceptions
 here?  I think you're asking for more trouble...


Are you referring to ioError? My knowledge of exceptions in Haskell is limited.

The error architecture is often a long way from the IO monad, so
whatever we do can't require the IO monad.

Thanks

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


Re: [GHC] #1171: GHC doesn't respect the imprecise exceptions semantics

2007-02-28 Thread Simon Marlow

Neil Mitchell wrote:

Hi


 In response to Neil: why use `unsafePerformIO` rather than IO exceptions
 here?  I think you're asking for more trouble...


Are you referring to ioError? My knowledge of exceptions in Haskell is 
limited.


The error architecture is often a long way from the IO monad, so
whatever we do can't require the IO monad.


Yes - the example was in the IO monad so I thought you could use IO exceptions. 
 In any case, I don't recommend using 'error' (or indeed 'unsafePerformIO') for 
errors you report to the user, purely because of its non-deterministic 
semantics.  If you use a suitable error monad or IO exceptions, you can be sure 
that you'll get the same behaviour regardless of compiler or optimisation settings.


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


Re: [GHC] #1171: GHC doesn't respect the imprecise exceptions semantics

2007-02-28 Thread Thorkil Naur
Hello,

The code in YHC is roughly if some list is empty then error No files found 
else error Many files found. If this code were changed to the equivalent 
of error (if some list is empty then No files found else Many files 
found), would there still be circumstances where the actual output produced 
could vary?

Thanks and best regards
Thorkil
On Wednesday 28 February 2007 12:31, Simon Marlow wrote:
 Neil Mitchell wrote:
  Hi
  
   In response to Neil: why use `unsafePerformIO` rather than IO exceptions
   here?  I think you're asking for more trouble...
  
  Are you referring to ioError? My knowledge of exceptions in Haskell is 
  limited.
  
  The error architecture is often a long way from the IO monad, so
  whatever we do can't require the IO monad.
 
 Yes - the example was in the IO monad so I thought you could use IO 
exceptions. 
   In any case, I don't recommend using 'error' (or indeed 'unsafePerformIO') 
for 
 errors you report to the user, purely because of its non-deterministic 
 semantics.  If you use a suitable error monad or IO exceptions, you can be 
sure 
 that you'll get the same behaviour regardless of compiler or optimisation 
settings.
 
 Cheers,
   Simon
 ___
 Glasgow-haskell-bugs mailing list
 Glasgow-haskell-bugs@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
 
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: [GHC] #1171: GHC doesn't respect the imprecise exceptions semantics

2007-02-28 Thread Simon Marlow
 The code in YHC is roughly if some list is empty then error No files
 found
 else error Many files found. If this code were changed to the
 equivalent
 of error (if some list is empty then No files found else Many files
 found), would there still be circumstances where the actual output
 produced could vary?

Maybe.  If GHC knows that error is strict (which it might well do) then you 
could be back where you started.

Cheers,
Simon

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


Re: [GHC] #1171: GHC doesn't respect the imprecise exceptions semantics

2007-02-28 Thread Simon Marlow

Simon Marlow wrote:

The code in YHC is roughly if some list is empty then error No files
found
else error Many files found. If this code were changed to the
equivalent
of error (if some list is empty then No files found else Many files
found), would there still be circumstances where the actual output
produced could vary?


Maybe.  If GHC knows that error is strict (which it might well do) then you 
could be back where you started.


Oops, error isn't strict, never mind.

Cheers,
Simon


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


Re: [GHC] #1171: GHC doesn't respect the imprecise exceptions semantics

2007-02-28 Thread Simon Marlow

Simon Marlow wrote:

Simon Marlow wrote:

The code in YHC is roughly if some list is empty then error No files
found
else error Many files found. If this code were changed to the
equivalent
of error (if some list is empty then No files found else Many files
found), would there still be circumstances where the actual output
produced could vary?


Maybe.  If GHC knows that error is strict (which it might well do) 
then you could be back where you started.


Oops, error isn't strict, never mind.


Ok, so error *is* strict.  Please ignore me, I have a cold and I'm having a bad 
day :-(


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


Re: [GHC] #911: Better information about the location of exceptions

2007-01-23 Thread GHC
#911: Better information about the location of exceptions
-+--
 Reporter:  simonmar |  Owner: 
 Type:  feature request  | Status:  new
 Priority:  normal   |  Milestone:  _|_
Component:  Runtime System   |Version:  6.4.2  
 Severity:  normal   | Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Changes (by igloo):

  * milestone:  = _|_
  * testcase:  =

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/911
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #911: Better information about the location of exceptions

2006-09-28 Thread GHC
#911: Better information about the location of exceptions
--+-
  Reporter:  simonmar |  Owner: 
  Type:  feature request  | Status:  new
  Priority:  normal   |  Milestone: 
 Component:  Runtime System   |Version:  6.4.2  
  Severity:  normal   | Resolution: 
  Keywords:   | Os:  Unknown
Difficulty:  Unknown  |   Architecture:  Unknown
--+-
Comment (by ekarttun):

 The new ghci debugging stuff could help with locating the error.

 The user's guide should probably have a note on locating failed pattern
 matches.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/911
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #911: Better information about the location of exceptions

2006-09-27 Thread GHC
#911: Better information about the location of exceptions
+---
Reporter:  simonmar |Owner: 
Type:  feature request  |   Status:  new
Priority:  normal   |Milestone: 
   Component:  Runtime System   |  Version:  6.4.2  
Severity:  normal   | Keywords: 
  Os:  Unknown  |   Difficulty:  Unknown
Architecture:  Unknown  |  
+---
From Frederik Eaton, on glasgow-haskell-bugs:

 I think it would be a good idea to print instructions for getting more
 information when a program fails with a pattern match or other error.

 Rather than
 {{{
 foo: Prelude.undefined
 }}}
 it should say
 {{{
 foo: Prelude.undefined
 For information about the location of this error, recompile with -prof
 -auto-all and run with +RTS -xc -RTS
 }}}
 Also, maybe these instructions aren't enough? When I do the above, it
 just prints
 {{{
 GHC.Err.CAFGHC.Err.CAFGHC.Err.CAFGHC.Err.CAFfoo: Prelude.undefined
 }}}
 which isn't what I was looking for... Am I forgetting an option or
 something?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/911
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Exceptions

2000-11-14 Thread Arjan van IJzendoorn

Hi there,

I just installed ghc-4.08.1 on a Win2k computer. Then I tried to compile a 
program that uses exceptions. Compilation succeeds, but running the program 
causes a "Application Error" dialog to appear. It says "The application 
failed to initialize properly (0xc005). Click on OK to terminate the 
application.". Here is the Haskell program:

--
module Main(main) where

import Exception

main = catchAllIO (putStrLn (head ([] :: [String])))
   (\e - putStrLn "hi" )

--

Compiled it with

ghc-4.08.1 -i/apps/ghc/lib/imports/lang -syslib lang Main.hs

Can you help me?

Arjan ([EMAIL PROTECTED])


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



Re: Exceptions

2000-11-14 Thread Reuben Thomas

 I just installed ghc-4.08.1 on a Win2k computer. Then I tried to compile a 
 program that uses exceptions. Compilation succeeds, but running the program 
 causes a "Application Error" dialog to appear. It says "The application 
 failed to initialize properly (0xc005). Click on OK to terminate the 
 application.". Here is the Haskell program:
 
 --
 module Main(main) where
 
 import Exception
 
 main = catchAllIO (putStrLn (head ([] :: [String])))
(\e - putStrLn "hi" )
 
 --
 
 Compiled it with
 
 ghc-4.08.1 -i/apps/ghc/lib/imports/lang -syslib lang Main.hs

This should be OK, but as Christian Lescher says, you can just say "-package
lang" rather than all the gumph you have.

The error message looks like a fairly typical Windows RTS problem. It could
be that I just missed something in my recent round of fixes. I'm afraid I'm
away at a DevLab in Redmond at the moment, so I'll check it next week when I
return. The only thing I can suggest for now is to reinstall GHC unless you
really have *just* installed it; I updated the InstallShield on about
November 6th.

-- 
http://sc3d.org/rrt/ | competent, a.  underpromoted


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