#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 hvr):

 btw, there seems to be some correlation with libraries making aggressive
 use of `{-# INLINE ... #-} when using functions from
 `Data.Vector.Algorithms.Intro` (which seems to be involved in the cases
 where packages would require the `-fsimpl-tick-factor`-workaround)

 Btw, removing all `{-# INLINE ... #-}` pragmas from
 `Data.Vector.Algorithms.Intro` reduces the ticks required below the
 threshold. More specifically, removing the `introsort` inline annotation
 already reduces the ticks required below threshold:

 {{{
 #!diff
 --- Data/Vector/Algorithms/Intro.hs-orig        2011-12-18
 17:57:31.676015597 +0100
 +++ Data/Vector/Algorithms/Intro.hs     2011-12-18 18:00:28.164011757
 +0100
 @@ -84,20 +84,19 @@
  -- Internal version of the introsort loop which allows partial
  -- sort functions to call with a specified bound on iterations.
  introsort :: (PrimMonad m, MVector v e)
            => Comparison e -> v (PrimState m) e -> Int -> Int -> Int -> m
 ()
  introsort cmp a i l u = sort i l u >> I.sortByBounds cmp a l u
   where
   sort 0 l u = H.sortByBounds cmp a l u
   sort d l u
     | len < threshold = return ()
     | otherwise = do O.sort3ByIndex cmp a c l (u-1) -- sort the median
 into the lowest position
                      p <- unsafeRead a l
                      mid <- partitionBy cmp a p (l+1) u
                      unsafeSwap a l (mid - 1)
                      sort (d-1) mid u
                      sort (d-1) l   (mid - 1)
    where
    len = u - l
    c   = (u + l) `div` 2
 -{-# INLINE introsort #-}
 }}}

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