#5539: GHC panic -  Simplifier ticks exhausted
---------------------------------+------------------------------------------
  Reporter:  hvr                 |          Owner:  simonpj       
      Type:  bug                 |         Status:  new           
  Priority:  high                |      Milestone:  7.4.1         
 Component:  Compiler            |        Version:  7.3           
Resolution:                      |       Keywords:                
        Os:  Linux               |   Architecture:  x86_64 (amd64)
   Failure:  Compile-time crash  |     Difficulty:  Unknown       
  Testcase:                      |      Blockedby:                
  Blocking:                      |        Related:                
---------------------------------+------------------------------------------

Comment(by rl):

 The `statistics` failure can be cured by this simple patch to
 `Data/Vector/Algorithms/Intro.hs` in `vector-algorithms`:

 {{{
 159,160d158
 <  {-# INLINE [1] isort #-}
 <  isort = introsort cmp a
 170c168
 <                       GT -> do isort (n-1) l (mid - 1)
 ---
 >                       GT -> do introsort cmp a (n-1) l (mid - 1)
 172c170
 <                       EQ -> isort (n-1) l m
 ---
 >                       EQ -> introsort cmp a (n-1) l m
 }}}

 This prevents `introsort` from being inlined into the unfolding. I'll send
 Dan a link to this thread, I don't think he is cc'd.

 In fact, `isort` should probably be `NOINLINE` since there is no benefit
 to inlining `introsort` twice. But `NOINLINE` will also prevent
 worker/wrapper and I'm not sure what the performance impact of that would
 be.

 I think we need a mechanism which lets us say that a function should
 always be specialised on certain dictionaries and arguments but not
 necessarily inlined. For example, `introsort` has this signature:

 {{{
 introsort :: (PrimMonad m, MVector v e) => Comparison e -> v (PrimState m)
 e -> Int -> Int -> Int -> m ()
 }}}

 We want to automatically specialise it for the `PrimMonad`, `MVectror` and
 `Comparison` arguments in all clients and then treat it like a normal
 function. This is quite similar to `INLINABLE` but we want the
 specialisation to happen automatically. Just like C++ templates, in fact.
 Unless I'm mistaken, `INLINE` is the only way to achieve this at the
 moment but that duplicates too much code when we want to specialise large
 algorithms.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5539#comment:36>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to