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

 Actually INLINALBE things '''already are''' auto-specialised in calling
 modules.  Moreover, the RULE for that specialiation is exported so that
 importing modules can take advantage of it rather than create their own
 specialisations.
 Example:
 {{{
 module T5539a where
   {-# INLINABLE g #-}
   g :: (Eq a, Num a) => a -> a
   g 0 = 0
   g n = 1 + g (n-1)

 ------------------
 module T5536 where
   import T5539a

   f :: Int -> Int
   f x = g x + 1
 }}}
 Mouule `T5539` automatically creates a version of `g` specialised at
 `Int`, and exports the RULE
 {{{
 ------ Local rules for imported ids --------
 "SPEC T5539a.g [GHC.Types.Int]" [ALWAYS]
     forall ($dEq_shF :: GHC.Classes.Eq GHC.Types.Int)
            ($dNum_shE :: GHC.Num.Num GHC.Types.Int).
       T5539a.g @ GHC.Types.Int $dEq_shF $dNum_shE
       = T5536.$sg
 }}}

 Is that what you want?

 Simon

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

Reply via email to