Re: [GHC] #367: Infinite loops can hang Concurrent Haskell

2012-11-21 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-
Changes (by bgamari):

 * cc: bgamari@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:35
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-26 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by simonpj):

 Great thanks Edward.  Is `-falways-yield` a good name?  Perhaps
 `-fguarantee-yield-points`?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:32
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-26 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by simonmar):

 Yes, thanks Edward.  I don't know why we didn't do this ages ago!

 Regarding the CPU-hogging primitives, we should rewrite them so that they
 include a regular yield check.  For example in `newArray#` we can do a
 yield check every 1000 iterations of the loop, which won't have a
 measurable impact on performance.

 Perhaps `-fno-omit-yields` for the flag?  Where `-fomit-yields` is an
 optimisation that we enable by default.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:33
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-26 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang@…):

 commit d3128bfc286002862e916296629a22f1ce987e4e
 {{{
 Author: Edward Z. Yang ezy...@mit.edu
 Date:   Mon Sep 17 18:28:49 2012 +0200

 Partially fix #367 by adding HpLim checks to entry with -fno-omit-
 yields.

 The current fix is relatively dumb as far as where to add HpLim
 checks: it will always perform a check unless we know that we're
 returning from a closure or we are doing a non let-no-escape case
 analysis.  The performance impact on the nofib suite looks like this:

 Min  +5.7% -0.0% -6.5% -6.4%-50.0%
 Max  +6.3% +5.8% +5.0% +5.5% +0.8%
  Geometric Mean  +6.2% +0.1% +0.5% +0.5% -0.8%

 Overall, the executable bloat is the biggest problem, so we keep the
 old
 omit-yields optimization on by default. Remember that if you need an
 interruptibility guarantee, you need to recompile all of your
 libraries
 with -fno-omit-yields.

 A better fix would involve only inserting the yields necessary to
 break
 loops; this is left as future work.

 Signed-off-by: Edward Z. Yang ezy...@mit.edu

  compiler/codeGen/StgCmmExpr.hs |4 +--
  compiler/codeGen/StgCmmHeap.hs |   57
 ++--
  compiler/main/DynFlags.hs  |4 +++
  docs/users_guide/using.xml |   18 
  4 files changed, 60 insertions(+), 23 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:34
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-25 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by simonmar):

 I think we could incorporate the patch, but not turn on the flag by
 default.  If you want to work on it further and see if you can get the
 code size penalty down that would be great - my suggestion would be to do
 as I mentioned earlier and omit the yield check for functions which are
 guaranteed to yield within a finite time, because they only call other
 functions which have that property.  You can assume that calling an
 arbitrary closure or a primop is guaranteed to yield.  As a first step you
 can do the analysis within a module, the next step would be to extend it
 across module boundaries.

 We should check the primops to make sure that none of them hog the CPU for
 a long time.  I think `newArray#` has this problem, because it fills in
 the array in a loop, so for a large array it won't yield quickly.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:29
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-25 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ganesh):

 Why can you assume that calling an arbitrary closure is guaranteed to
 yield?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:30
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-25 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 OK, once I get my validate running (failing, due to a certain someone,
 wink), I will push the patch, plus this docu patch:

 {{{
 varlistentry
   term
 option-falways-yield/option
 indextermprimaryoption-falways-
 yield/option/primary/indexterm
   /term
   listitem
   paraTells GHC to always emit a pre-emption check on entry
 points to functions. This means that threads that run in tight
 non-allocating loops will get preempted in a timely fashion;
 otherwise, GHC may never manage to interrupt such a loop.  This
 imposes a very slight performance impact but inflates binary sizes
 by about 5%, so it is not enabled by default.  Note that if you
 would like to guarantee that threads can always be interrupted,
 you will need to compile all libraries with this flag./para
   /listitem
 /varlistentry
 }}}

 What are we going to do with information about CPU hogging primitives?
 There are lots of unsafe primitives which can cause GHC to segfault or
 jump to arbitrary code, so mostly this information would have to be
 advisory for Safe Haskell implementors, who would know if one of these
 primitives were called it better be doing bounds checks, etc. We can't
 forcibly terminate the primops, since they're fat machine instructions and
 don't give up the capability?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:31
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-24 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by simonmar):

 What you've done here is omit the yield checks on (some) case
 alternatives.  Which is almost ok, because all loops will go through a
 function entry, except for let-no-escapes which use `altHeapCheck`.  So
 with this patch you won't catch non-allocating recursive let-no-escapes.

 To make this correct you need to ensure that let-no-escapes get a yield
 point too, but you could also omit the yield points from ordinary
 `altHeapCheck`s which should reduce the code size hit further.

 The confusion probably arose because of my naming scheme:
 `altHeapCheckReturnsTo` is the heap check for a case alternative where the
 case scrutinee made an external call, and hence had a returns to
 continuation that we can re-use for the heap check's continuation.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:26
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-24 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 For reference, here is an example of a non-allocating recursive let-no-
 escape:

 {{{
 {-# LANGUAGE MagicHash #-}

 import GHC.Conc
 import GHC.Prim
 import GHC.Exts

 main = numSparks = \x - f x `seq` return ()

 {-# NOINLINE f #-}
 f :: Int - Bool
 f i@(I# j) = let fail :: Int# - Bool
  fail i = fail (i +# 1#)
   in if (case i of
 0 - True
 _ - False) then fail j else False
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:27
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-24 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 This patch, plus the SpLim checks:

 {{{
 Min  +6.1% -0.1% -8.6% -8.0%-50.0%
 Max  +6.8% +5.8% +4.8% +5.5% +1.3%
  Geometric Mean  +6.7% +0.1% +0.0% +0.0% -0.7%
 }}}

 Good things for runtime, but not all that much difference for code size.

 This patch only (without SpLim checks)

 {{{
 Min  +5.7% -0.0% -6.5% -6.4%-50.0%
 Max  +6.3% +5.8% +5.0% +5.5% +0.8%
  Geometric Mean  +6.2% +0.1% +0.5% +0.5% -0.8%
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:28
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-21 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 Here is a variant of the patch that only does heap checks when not
 returning (since it's not possible to infinitely return.) We do much
 better on runtime and binary size; maybe good enough to ship by default!

 {{{
 diff --git a/compiler/codeGen/StgCmmHeap.hs
 b/compiler/codeGen/StgCmmHeap.hs
 index fb37391..4c53bc2 100644
 --- a/compiler/codeGen/StgCmmHeap.hs
 +++ b/compiler/codeGen/StgCmmHeap.hs
 @@ -371,7 +371,7 @@ entryHeapCheck cl_info nodeSet arity args code

 loop_id - newLabelC
 emitLabel loop_id
 -   heapCheck True (gc_call updfr_sz * mkBranch loop_id) code
 +   heapCheck True True (gc_call updfr_sz * mkBranch loop_id) code

  {-
  -- This code is slightly outdated now and we could easily keep the
 above
 @@ -461,7 +461,7 @@ cannedGCReturnsTo :: Bool - CmmExpr - [LocalReg] -
 Label - ByteOff
  cannedGCReturnsTo cont_on_stack gc regs lret off code
= do dflags - getDynFlags
 updfr_sz - getUpdFrameOff
 -   heapCheck False (gc_call dflags gc updfr_sz) code
 +   heapCheck False False (gc_call dflags gc updfr_sz) code
where
  reg_exprs = map (CmmReg . CmmLocal) regs
-- Note [stg_gc arguments]
 @@ -476,7 +476,7 @@ genericGC code
 lretry - newLabelC
 emitLabel lretry
 call - mkCall generic_gc (GC, GC) [] [] updfr_sz (0,[])
 -   heapCheck False (call * mkBranch lretry) code
 +   heapCheck False True (call * mkBranch lretry) code

  cannedGCEntryPoint :: DynFlags - [LocalReg] - Maybe CmmExpr
  cannedGCEntryPoint dflags regs
 @@ -524,22 +524,23 @@ mkGcLabel :: String - CmmExpr
  mkGcLabel s = CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit s)))

  ---
 -heapCheck :: Bool - CmmAGraph - FCode a - FCode a
 -heapCheck checkStack do_gc code
 +heapCheck :: Bool - Bool - CmmAGraph - FCode a - FCode a
 +heapCheck checkStack checkYield do_gc code
= getHeapUsage $ \ hpHw -
  -- Emit heap checks, but be sure to do it lazily so
  -- that the conditionals on hpHw don't cause a black hole
 -do  { codeOnly $ do_checks checkStack hpHw do_gc
 +do  { codeOnly $ do_checks checkStack checkYield hpHw do_gc
  ; tickyAllocHeap hpHw
  ; doGranAllocate hpHw
  ; setRealHp hpHw
  ; code }

  do_checks :: Bool   -- Should we check the stack?
 +  - Bool   -- Should we check for preemption?
- WordOff-- Heap headroom
- CmmAGraph  -- What to do on failure
- FCode ()
 -do_checks checkStack alloc do_gc = do
 +do_checks checkStack checkYield alloc do_gc = do
dflags - getDynFlags
let
  alloc_lit = mkIntExpr dflags (alloc * wORD_SIZE dflags) -- Bytes
 @@ -557,15 +558,22 @@ do_checks checkStack alloc do_gc = do
  hp_oflo = CmmMachOp (mo_wordUGt dflags)
  [CmmReg hpReg, CmmReg (CmmGlobal HpLim)]

 +-- Yielding if HpLim == 0
 +yielding = CmmMachOp (mo_wordEq dflags)
 +[CmmReg (CmmGlobal HpLim), CmmLit (zeroCLit
 dflags)]
 +
  alloc_n = mkAssign (CmmGlobal HpAlloc) alloc_lit
gc_id - newLabelC

when checkStack $ do
   emit = mkCmmIfGoto sp_oflo gc_id

 -  when (alloc /= 0) $ do
 - emitAssign hpReg bump_hp
 - emit = mkCmmIfThen hp_oflo (alloc_n * mkBranch gc_id)
 +  if (alloc /= 0)
 +then do
 +  emitAssign hpReg bump_hp
 +  emit = mkCmmIfThen hp_oflo (alloc_n * mkBranch gc_id)
 +else do
 +  emit = mkCmmIfGoto yielding gc_id

emitOutOfLine gc_id $
   do_gc -- this is expected to jump back somewhere
 }}}

 {{{
 

 Program   SizeAllocs   Runtime   Elapsed  TotalMem
 

anna  +5.5% +0.0%  0.13  0.13 +0.0%
ansi  +6.0% +0.0%  0.00  0.00 +0.0%
atom  +6.0% +0.0% +0.0% 

Re: [GHC] #367: Infinite loops can hang Concurrent Haskell

2012-09-21 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 Here are the aggregate stats for the stack check version (overall, it
 seems that it produces more bloated executables, but is a little bit
 faster):

 {{{
 

 Program   SizeAllocs   Runtime   Elapsed  TotalMem
 
 Min  +6.1% -0.1% -7.2% -6.7%-50.0%
 Max  +6.7% +5.8% +5.9% +6.1% +0.8%
  Geometric Mean  +6.6% +0.1% +0.1% +0.2% -0.8%
 }}}

 Switching to stack checks has some interesting interactions with some of
 the optimizations; for example, we can no longer optimize away Sp - 0 
 SpLim as true, since SpLim may have been twiddled with. If we run nofib
 without adding the extra yields but with those optimizations turned off,
 we see:

 {{{
 Min  +5.9% -0.1% -7.3% -7.0%-50.0%
 Max  +6.7% +5.8% +3.9% +4.1% +0.0%
  Geometric Mean  +6.6% +0.1% -0.1% -0.1% -0.8%
 }}}

 So we already pay most of the cost from having to ditch the optimizations.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:25
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-20 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by simonmar):

 Replying to [comment:20 ezyang]:
  Replying to [comment:19 simonmar]:
   You could improve code size by omitting the `HpAlloc = 0` assignment
 (perhaps making sure that it is initialized to zero in `LOAD_THREAD_STATE`
 or something).
 
  Fascinatingly enough, this doesn't help all that much, since instruction
 alignments adds in nops to fill in the space savings.

 But we don't actually align the heap-check failure branch, so I'm
 confused.  Can you post the asm code you're seeing?

   Another alternative is to use `SpLim` instead of `HpLim` to trigger
 the interrupt, on the grounds that there are more stack checks than heap
 checks. We would have to put `SpLim` in a memory location instead of a
 register, but we could move `HpLim` into a register.
 
  To be clear, this is changing globally how preemption would work, since
 prior to this patch we were zeroing HpLim to trigger a yield. But it
 should otherwise work. I'll chase up some stats here too. (If SpLim is
 checked more often, won't we pay a performance cost for having it in a
 memory location?)

 Maybe, but it's worth measuring I think.

   Something else we could do is add a flag on every top-level function
 to say whether it is non-allocating (rather like the `NoCafRefs` flag),
 and we could use that to optimise away many of the extra checks.
 
  I don't quite understand what this means: isn't alloc = 0 in the heap
 check just this information?

 I had in mind making it a transitive property - a function would get the
 alloc flag if it is guaranteed to allocate within a bounded time, so then
 any callers don't need a yield check.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:22
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-20 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 Replying to [comment:22 simonmar]:
  Replying to [comment:20 ezyang]:
   Fascinatingly enough, this doesn't help all that much, since
 instruction alignments adds in nops to fill in the space savings.
 
  But we don't actually align the heap-check failure branch, so I'm
 confused.  Can you post the asm code you're seeing?

 I misspoke; actually, we're page-aligning the data section, and the
 savings aren't enough to get us to the previous page. It's technically a
 benefit, but only if the increase in size means you can't fit the entire
 code block in the instruction cache...

 {{{
 - 12 .text 001e239c  0804a770  0804a770  2770  2**4
 + 12 .text 001e23bc  0804a770  0804a770  2770  2**4
CONTENTS, ALLOC, LOAD, READONLY, CODE
 }}}

  I had in mind making it a transitive property - a function would get the
 alloc flag if it is guaranteed to allocate within a bounded time, so then
 any callers don't need a yield check.

 Hm, I guess this is good for the little blocks we generate which only have
 one exit point, and not so good if there are multiple exit points (since
 all of them would need the Alloc flag set to work.)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:23
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-19 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 Here is the nofib results on HpAlloc:

 {{{
 

 Program   SizeAllocs   Runtime   Elapsed  TotalMem
 

anna +21.8% +0.0%  0.14  0.14 +0.0%
ansi +21.8% +0.0%  0.00  0.00 +0.0%
atom +21.9% +0.0% +0.7% +0.5% +0.0%
  awards +21.9% +0.0%  0.00  0.00 +0.0%
  banner +21.7% +0.0%  0.00  0.00 +0.0%
  bernouilli +21.9% +0.0% -2.1% -2.1% +0.0%
   boyer +21.8% +0.0%  0.06  0.06 +0.0%
  boyer2 +21.8% +0.0%  0.01  0.01 +0.0%
bspt +21.6% +0.0%  0.02  0.02 +0.0%
   cacheprof +21.3% +0.0% +3.9% +3.7% -0.2%
calendar +21.9% +0.0%  0.00  0.00 +0.0%
cichelli +21.8% +0.0%  0.11  0.11 +0.0%
 circsim +21.9% +0.0% +2.0% +2.2% +0.0%
clausify +21.9% +0.0%  0.05  0.05 +0.0%
   comp_lab_zift +21.9% +0.0% +1.9% +0.8% +0.0%
compress +21.8% +0.0% +4.2% +4.5% +0.0%
   compress2 +21.8% +0.0% +0.0% +0.0% +0.0%
 constraints +22.0% +0.0% +1.0% +1.0% +0.0%
cryptarithm1 +21.9% +0.0% +1.3% +1.2% +0.0%
cryptarithm2 +21.9% +0.0%  0.02  0.02 +0.0%
 cse +21.8% +0.0%  0.00  0.00 +0.0%
   eliza +21.5% +0.0%  0.00  0.00 +0.0%
   event +21.9% +0.0%  0.17  0.17 +0.0%
  exp3_8 +21.9% +0.0% +0.0% +0.3% +0.0%
  expert +21.9% +0.0%  0.00  0.00 +0.0%
 fem +22.1% +0.0%  0.03  0.03 +0.0%
 fft +21.6% +0.0%  0.05  0.05 +0.0%
fft2 +21.6% +0.0%  0.08  0.08 +0.0%
fibheaps +21.9% +0.0%  0.04  0.04 +0.0%
fish +21.8% +0.0%  0.03  0.03 +0.0%
   fluid +21.8% +0.0%  0.01  0.01 +0.0%
  fulsom +21.7% +0.0% +2.1% +1.7% +0.5%
  gamteb +21.7% +0.0%  0.06  0.06 +0.0%
 gcd +21.9% +0.0%  0.04  0.04 +0.0%
 gen_regexps +21.9% +0.0%  0.00  0.00 +0.0%
  genfft +21.8% +0.0%  0.05  0.05 +0.0%
  gg +21.7% +0.0%  0.02  0.02 +0.0%
grep +21.8% +0.0%  0.00  0.00 +0.0%
  hidden +22.0% +0.0%+14.6%+14.4% +0.0%
 hpg +21.7% +0.0%  0.16  0.16 +0.0%
 ida +21.9% +0.0%  0.13  0.13 +0.0%
   infer +21.8% +0.0%  0.08  0.08 +0.0%
 integer +21.9% +0.0%+14.0%+13.9% +0.0%
   integrate +21.9% +0.0% -8.0% -7.8% +0.0%
 knights +21.9% +0.0%  0.01  0.01 +0.0%
lcss +21.9% +0.0% +0.2% +0.2% +0.0%
life +21.9% +0.0% +5.9% +5.7% +0.0%
lift +21.8% +0.0%  0.00  0.00 +0.0%
   listcompr +21.8% +0.0%  0.11  0.11 +0.0%
listcopy +21.8% +0.0%  0.12  0.12 +0.0%
 }}}

 (Also here because I wanted to see if some of the improvements were
 reproduceable.)

-- 
Ticket URL: 

Re: [GHC] #367: Infinite loops can hang Concurrent Haskell

2012-09-18 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by simonmar):

 You could improve code size by omitting the `HpAlloc = 0` assignment
 (perhaps making sure that it is initialized to zero in `LOAD_THREAD_STATE`
 or something).

 Another alternative is to use `SpLim` instead of `HpLim` to trigger the
 interrupt, on the grounds that there are more stack checks than heap
 checks.  We would have to put `SpLim` in a memory location instead of a
 register, but we could move `HpLim` into a register.

 Something else we could do is add a flag on every top-level function to
 say whether it is non-allocating (rather like the `NoCafRefs` flag), and
 we could use that to optimise away many of the extra checks.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:19
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-18 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 Replying to [comment:19 simonmar]:
  You could improve code size by omitting the `HpAlloc = 0` assignment
 (perhaps making sure that it is initialized to zero in `LOAD_THREAD_STATE`
 or something).

 Fascinatingly enough, this doesn't help all that much, since instruction
 alignments adds in nops to fill in the space savings.

  Another alternative is to use `SpLim` instead of `HpLim` to trigger the
 interrupt, on the grounds that there are more stack checks than heap
 checks. We would have to put `SpLim` in a memory location instead of a
 register, but we could move `HpLim` into a register.

 To be clear, this is changing globally how preemption would work, since
 prior to this patch we were zeroing HpLim to trigger a yield. But it
 should otherwise work. I'll chase up some stats here too. (If SpLim is
 checked more often, won't we pay a performance cost for having it in a
 memory location?)

  Something else we could do is add a flag on every top-level function to
 say whether it is non-allocating (rather like the `NoCafRefs` flag), and
 we could use that to optimise away many of the extra checks.

 I don't quite understand what this means: isn't alloc = 0 in the heap
 check just this information?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:20
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-17 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-
Changes (by ezyang):

  * owner:  = ezyang


Comment:

 It turns out the stupid implementation is actually pretty fast.

 {{{diff --git a/compiler/codeGen/StgCmmHeap.hs
 b/compiler/codeGen/StgCmmHeap.hs
 index fb37391..a70d132 100644
 --- a/compiler/codeGen/StgCmmHeap.hs
 +++ b/compiler/codeGen/StgCmmHeap.hs
 @@ -557,15 +557,22 @@ do_checks checkStack alloc do_gc = do
  hp_oflo = CmmMachOp (mo_wordUGt dflags)
  [CmmReg hpReg, CmmReg (CmmGlobal HpLim)]

 +-- Yielding if HpLim == 0
 +yielding = CmmMachOp (mo_wordEq dflags)
 +[CmmReg (CmmGlobal HpLim), CmmLit (zeroCLit
 dflags)]
 +
  alloc_n = mkAssign (CmmGlobal HpAlloc) alloc_lit
gc_id - newLabelC

when checkStack $ do
   emit = mkCmmIfGoto sp_oflo gc_id

 -  when (alloc /= 0) $ do
 - emitAssign hpReg bump_hp
 - emit = mkCmmIfThen hp_oflo (alloc_n * mkBranch gc_id)
 +  if (alloc /= 0)
 +then do
 +  emitAssign hpReg bump_hp
 +  emit = mkCmmIfThen hp_oflo (alloc_n * mkBranch gc_id)
 +else do
 +  emit = mkCmmIfThen yielding (alloc_n * mkBranch gc_id)

emitOutOfLine gc_id $
   do_gc -- this is expected to jump back somewhere
 }}}

 A totally unscientific benchmark on

 {{{
 module Main where

 import qualified Data.Vector as U

 main = U.sum (U.enumFromTo 1 (10 :: Int)) `seq` return ()
 }}}

 yields this C--

 {{{
  Main.main1_entry()
  { [(c1Zm,
  Main.main1_info:
  const 65539;
  const 0;
  const 15;),
 (c1Zn,
  block_c1Zn_info:
  const 0;
  const 32;)]
  }
  c1Zm:
  if (Sp - 12  SpLim) goto c1Zv;
  if (HpLim == 0) goto c1Zu;
  I32[Sp - 8] = 0;
  I32[Sp - 12] = 1;
  I32[Sp - 4] = c1Zn;
  Sp = Sp - 12;
  jump Main.main_$s$wfoldlM'_loop_info; // []
  c1Zu:
  HpAlloc = 0;
  goto c1Zv;
  c1Zv:
  R1 = Main.main1_closure;
  jump stg_gc_fun; // [R1]
  c1Zn:
  if (HpLim == 0) goto c1ZC;
  R1 = GHC.Tuple.()_closure+1;
  Sp = Sp + 4;
  jump I32[Sp]; // [R1]
  c1ZC:
  HpAlloc = 0;
  R1 = R1;
  jump stg_gc_unbx_r1; // [R1]
 }}}

 which is only about 10% slower.

 Unfortunately, if you want to guarantee things don't hang, it's not enough
 to compile the untrusted code like this; all the other code needs to have
 this transformation applied too. So we should probably have a -yielding
 flag (like -threaded or -profiling) which allows us to compile yielding
 versions of all relevant code.  Unfortunately, the number of combinations
 of such flags exponentially increases...

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:17
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-17 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 Diff botched, here is a formatted one:

 {{{
 ezyang@javelin:~/Dev/ghc-master$ git show
 commit 5a9aee5e1d5a4d140f451aef6c57ab065c428966
 Author: Edward Z. Yang ezy...@mit.edu
 Date:   Mon Sep 17 18:28:49 2012 +0200

 Better implementation for fixing #367.

 Signed-off-by: Edward Z. Yang ezy...@mit.edu

 diff --git a/compiler/codeGen/StgCmmHeap.hs
 b/compiler/codeGen/StgCmmHeap.hs
 index fb37391..a70d132 100644
 --- a/compiler/codeGen/StgCmmHeap.hs
 +++ b/compiler/codeGen/StgCmmHeap.hs
 @@ -557,15 +557,22 @@ do_checks checkStack alloc do_gc = do
  hp_oflo = CmmMachOp (mo_wordUGt dflags)
  [CmmReg hpReg, CmmReg (CmmGlobal HpLim)]

 +-- Yielding if HpLim == 0
 +yielding = CmmMachOp (mo_wordEq dflags)
 +[CmmReg (CmmGlobal HpLim), CmmLit (zeroCLit
 dflags)]
 +
  alloc_n = mkAssign (CmmGlobal HpAlloc) alloc_lit
gc_id - newLabelC

when checkStack $ do
   emit = mkCmmIfGoto sp_oflo gc_id

 -  when (alloc /= 0) $ do
 - emitAssign hpReg bump_hp
 - emit = mkCmmIfThen hp_oflo (alloc_n * mkBranch gc_id)
 +  if (alloc /= 0)
 +then do
 +  emitAssign hpReg bump_hp
 +  emit = mkCmmIfThen hp_oflo (alloc_n * mkBranch gc_id)
 +else do
 +  emit = mkCmmIfThen yielding (alloc_n * mkBranch gc_id)

emitOutOfLine gc_id $
   do_gc -- this is expected to jump back somewhere
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:18
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-17 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 Code bloat is pretty big across the board, but runtime performance hit is
 about what I expected.

 {{{
 NoFib Results

 

 Program   SizeAllocs   Runtime   Elapsed  TotalMem
 

anna +21.8% +0.0%  0.14  0.14 +0.0%
ansi +21.8% +0.0%  0.00  0.00 +0.0%
atom +21.9% +0.0% +0.8% +0.3% +0.0%
  awards +21.9% +0.0%  0.00  0.00 +0.0%
  banner +21.7% +0.0%  0.00  0.00 +0.0%
  bernouilli +21.9% +0.0% -2.1% -1.8% +0.0%
   boyer +21.8% +0.0%  0.05  0.05 +0.0%
  boyer2 +21.8% +0.0%  0.01  0.01 +0.0%
bspt +21.6% +0.0%  0.02  0.02 +0.0%
   cacheprof +21.3% +0.1% +4.2% +4.0% +0.0%
calendar +21.9% +0.0%  0.00  0.00 +0.0%
cichelli +21.8% +0.0%  0.11  0.11 +0.0%
 circsim +21.9% +0.0% +2.1% +2.0% +0.0%
clausify +21.9% +0.0%  0.05  0.05 +0.0%
   comp_lab_zift +21.9% +0.0% +2.2% +1.1% +0.0%
compress +21.8% +0.0% +3.6% +4.5% +0.0%
   compress2 +21.8% +0.0% +0.0% +0.0% +0.0%
 constraints +22.0% +0.0% +0.4% +0.4% +0.0%
cryptarithm1 +21.9% +0.0% +1.4% +1.3% +0.0%
cryptarithm2 +21.9% +0.0%  0.02  0.02 +0.0%
 cse +21.8% +0.0%  0.00  0.00 +0.0%
   eliza +21.5% +0.0%  0.00  0.00 +0.0%
   event +21.9% +0.0%  0.17  0.17 +0.0%
  exp3_8 +21.9% +0.0% +0.0% +0.0% +0.0%
  expert +21.9% +0.0%  0.00  0.00 +0.0%
 fem +22.1% +0.0%  0.03  0.03 +0.0%
 fft +21.6% +0.0%  0.05  0.05 +0.0%
fft2 +21.6% +0.0%  0.08  0.08 +0.0%
fibheaps +21.9% +0.0%  0.04  0.04 +0.0%
fish +21.8% +0.0%  0.03  0.03 +0.0%
   fluid +21.8% +0.0%  0.01  0.01 +0.0%
  fulsom +21.7% +0.0% +2.5% +2.5% -0.9%
  gamteb +21.7% +0.0%  0.06  0.06 +0.0%
 gcd +21.9% +0.0%  0.04  0.04 +0.0%
 gen_regexps +21.9% +0.0%  0.00  0.00 +0.0%
  genfft +21.8% +0.0%  0.05  0.05 +0.0%
  gg +21.7% +0.0%  0.02  0.02 +0.0%
grep +21.8% +0.0%  0.00  0.00 +0.0%
  hidden +22.0% +0.0%+15.0%+14.8% +0.0%
 hpg +21.7% +0.0%  0.16  0.16 +0.0%
 ida +21.9% +0.0%  0.13  0.13 +0.0%
   infer +21.8% +0.0%  0.08  0.08 +0.0%
 integer +21.9% +0.0%+13.9%+13.9% +0.0%
   integrate +21.9% +0.0% -9.1% -8.1% +0.0%
 knights +21.9% +0.0%  0.01  0.01 +0.0%
lcss +21.9% +0.0% +0.2% +0.3% +0.0%
life +21.9% +0.0% +5.7% +5.2% +0.0%
lift +21.8% +0.0%  0.00  0.00 +0.0%
   listcompr +21.8% +0.0%  0.11  0.11 +0.0%
listcopy +21.8% +0.0%  0.12  0.12 +0.0%
maillist +21.9% +0.0%  0.10  0.10 

Re: [GHC] #367: Infinite loops can hang Concurrent Haskell

2012-08-06 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner: 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 While solving this problem in general may be quite hard, we might be able
 to allow users to annotate potentially time-consuming, non-allocating
 regions of code in a way that would allow them to be interrupted, by co-
 opting the mechanism we have for interruptible FFI calls. Namely,
 pthread_kill()'ing recalcitrant threads :-) (alas, this won't work for
 Windows, but you can't have everything in life...)  E.g.

 {{{
 runInterruptibly (evaluate (last (repeat 1))
 }}}

 The primary difficulty of this scheme is making sure the computation is
 being done on threads which we can afford to terminate with extreme
 prejudice. This is easy for safe FFI calls, because we give up the
 capability before entering the foreign code. But a thread executing
 Haskell will generally have the capability, since it might GC.

 One answer might be: on entering such an annotated region, give up the
 capability, and make the thread do an InCall if it happens to hit
 something that needs GC'ing. Of course, this means we need to have a
 version of all the code being generated here to use different GC entry-
 points which do the InCall shindig (in the cases where this is useful,
 there shouldn't be very many of them, since the whole point is this is a
 non-allocating loop!) but this could cause a pretty massive expansion in
 overall code size. The benefit of such a scheme is that we only pay a cost
 entering such a region. We don't want to add any checks to the pre-
 existing GC functions, since we'll pay the cost for all programs, even
 ones not using this functionality.

 Another possibility is to still give up the capability, but to demand that
 any code covered by such an annotation be statically known never to make
 allocations. But it is probably too difficult to explain to the programmer
 under what circumstances allocation occurs, and I imagine many regions of
 code will allocate once or twice, but have large chunks inside which
 perform no allocation. On the other hand, it would be pretty nice if
 Haskell programmers could carve out a chunk of code, and say, This is
 doing a very clever numeric calculation which should compile straight to
 something efficient which does no allocation.

 But I think the right answer here is to make it possible to run Haskell
 code *without* holding a capability, and then proceed from there.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:15
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] #367: Infinite loops can hang Concurrent Haskell

2012-08-06 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner: 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 Alas, the above proposal is totally infeasible in the current world order,
 because it is completely impossible to run Haskell code without holding
 the capability. I thought you might get away with only instrumenting GC
 calls, but really any and all of the memory you're looking at could get
 moved around by a GC who thinks that they have all the capabilities. So
 we’re back to an implementation strategy where a thread holding a
 capability gets killed, and then we recover, but this seems generally
 Hard(TM).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:16
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] #367: Infinite loops can hang Concurrent Haskell

2012-01-26 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner: 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-
Changes (by PHO):

 * cc: pho@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:14
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] #367: Infinite loops can hang Concurrent Haskell

2012-01-17 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner: 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-
Changes (by lpsmith):

 * cc: leon.p.smith@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#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] #367: Infinite loops can hang Concurrent Haskell

2009-11-19 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner: 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Difficulty:  Unknown  | Os:  Unknown/Multiple   
 
  Testcase:   |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by igloo):

  * failure:  = Incorrect result at runtime

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:12
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] #367: Infinite loops can hang Concurrent Haskell

2009-07-13 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  lowest|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.4.1   
Severity:  normal|   Resolution:  None
Keywords:  scheduler allocation  |   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by SamB):

  * status:  assigned = new
  * owner:  nobody =
 * cc: SamB (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:11
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] #367: Infinite loops can hang Concurrent Haskell

2009-06-17 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
-+--
Reporter:  simonpj   |Owner:  nobody  
Type:  bug   |   Status:  assigned
Priority:  lowest|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.4.1   
Severity:  normal|   Resolution:  None
Keywords:  scheduler allocation  |   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by SamB):

 According to CapabilitiesAndScheduling:

   We do have a time-slice mechanism: the timer interrupt (see Timer.c)
 sets the context_switch flag, which causes the running thread to return to
 the scheduler the next time a heap check fails (at the end of the current
 nursery block). When a heap check fails, the thread doesn't necessarily
 always return to the scheduler: as long as the context_switch flag isn't
 set, and there is another block in the nursery, it resets Hp and HpLim? to
 point to the new block, and continues.

 To fix this bug, we need a way for the timer signal handler to *force* the
 Haskell code to stop in bounded time.

 Two ways that come to mind for the handler to force a stop are:
   1. insert a breakpoint (or a special jump?) at some pre-arranged point
 in any arbitrarily-long allocation-free loop, such that the breakpoint
 signal handler can safely enter the schedular
   2. use some sort of instruction-by-instruction Call Frame Information,
 something like that of DWARF 2 and up, to figure out the innermost frame's
 stack layout.

 Approach 1 is kind of icky insofar as it might cause spurious stops in
 other threads, or worse!

 For those unfamiliar with it: DWARF's CFI represents a function of type
 (IP value × register name) → Maybe (how to find the value of that register
 in the caller), where Nothing means that register got clobbered.
 Obviously, we would also need information about which of the interrupted
 code's registers and stack slots represented pointers that should be
 followed by the garbage collector for approach 2 to work.

 Any other ideas about how the timer handler can guarantee re-entering the
 scheduler in bounded time?

 There *is* the obvious check every time around a non-allocating loop
 approach, but it seems obvious that that would cost far too much where we
 can least afford it. (Is this actually true? So many things that seem
 obvious aren't...)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:10
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] #367: Infinite loops can hang Concurrent Haskell

2009-06-16 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
-+--
Reporter:  simonpj   |Owner:  nobody  
Type:  bug   |   Status:  assigned
Priority:  lowest|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.4.1   
Severity:  normal|   Resolution:  None
Keywords:  scheduler allocation  |   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by SamB):

  * keywords:  = scheduler allocation

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#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] #367: Infinite loops can hang Concurrent Haskell

2009-02-05 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
-+--
Reporter:  simonpj   |Owner:  nobody  
Type:  bug   |   Status:  assigned
Priority:  lowest|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.4.1   
Severity:  normal|   Resolution:  None
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by SamB):

 This is just a gratuitous comment to add the word scheduler to the page.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#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] #367: Infinite loops can hang Concurrent Haskell

2007-07-03 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
-+--
Reporter:  simonpj   |Owner:  nobody  
Type:  bug   |   Status:  assigned
Priority:  lowest|Milestone:  6.8 
   Component:  Compiler  |  Version:  6.4.1   
Severity:  normal|   Resolution:  None
Keywords:|   Difficulty:  Unknown 
  Os:  Unknown   | Testcase:  
Architecture:  Unknown   |  
-+--
Changes (by guest):

  * cc:  = [EMAIL PROTECTED]

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367
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] #367: Infinite loops can hang Concurrent Haskell

2007-07-03 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
-+--
Reporter:  simonpj   |Owner:  nobody  
Type:  bug   |   Status:  assigned
Priority:  lowest|Milestone:  6.8 
   Component:  Compiler  |  Version:  6.4.1   
Severity:  normal|   Resolution:  None
Keywords:|   Difficulty:  Unknown 
  Os:  Unknown   | Testcase:  
Architecture:  Unknown   |  
-+--
Changes (by guest):

  * cc:  [EMAIL PROTECTED] = [EMAIL PROTECTED]

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367
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] #367: Infinite loops can hang Concurrent Haskell

2006-10-20 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
 Reporter:  simonpj   |  Owner:  nobody  
 Type:  bug   | Status:  assigned
 Priority:  lowest|  Milestone:  6.8 
Component:  Compiler  |Version:  6.4.1   
 Severity:  normal| Resolution:  None
 Keywords:| Difficulty:  Unknown 
 Testcase:|   Architecture:  Unknown 
   Os:  Unknown   |  
--+-
Changes (by igloo):

  * milestone:  = 6.8
  * testcase:  =

Comment:

 One reason this is annoying is that it means you can't have a manager
 thread running code (which you have no reason to believe won't go into an
 infinite loop or generate an infinite amount of output) with a timeout.

 For example, lambdabot can't just use something like the timeout function
 above to ensure its modules don't go into an infinite loop. Another
 example is not being able to give up and return a bad result if you run
 out of time in something like the ICFP contest.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367
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