
#8331: GHC fails to apply {-# SPECIALIZE #-} for dubious reasons -------------------------+------------------------------------------------- Reporter: | Owner: blitzcode | Status: new Type: bug | Milestone: Priority: | Version: 7.6.3 normal | Operating System: Unknown/Multiple Component: | Type of failure: Incorrect warning at Compiler | compile-time Keywords: | Test Case: Architecture: | Blocking: Unknown/Multiple | Difficulty: | Unknown | Blocked By: | Related Tickets: | -------------------------+------------------------------------------------- I encountered a 'RULE left-hand side too complicated to desugar' warning when trying to reduce some typeclass overhead through a SPECIALIZE pragma. The change I had to make to my program to make the warning go away seems rather strange, so I thought it might be worth reporting as a bug. This is the small test case I wrote to understand the problem better: {{{ {-# LANGUAGE FlexibleInstances, RankNTypes #-} module Main (main) where import Control.Monad import Control.Monad.Reader import Control.Monad.ST import Control.Applicative class (Applicative m, {- Functor m ,-} Monad m) => MonadAbstractIOST m where addstuff :: Int -> m Int type ReaderST s = ReaderT (Int) (ST s) instance MonadAbstractIOST (ReaderST s) where addstuff a = return . (a +) =<< ask runAbstractST :: (forall s. ReaderST s a) -> a runAbstractST f = runST $ runReaderT f 99 {-# SPECIALIZE INLINE useAbstractMonad :: ReaderST s Int #-} useAbstractMonad :: MonadAbstractIOST m => m Int useAbstractMonad = foldM (\a b -> a `seq` return . (a +) =<< (addstuff b)) 0 [1..50000000] -- useConcreteMonad :: ReaderST s Int -- useConcreteMonad = foldM (\a b -> a `seq` return . (a +) =<< (addstuff b)) 0 [1..50000000] main :: IO () main = do let st = runAbstractST useAbstractMonad putStrLn . show $ st }}} The use case here is simply having a library of functions which are abstracted from the underlying implementation of state (Reader / IO, Reader / ST, etc.) and operate on it with a small set of typeclass functions. This has very severe runtime overhead (~5x) compared to using the actual transformer stack directly, so a SPECIALIZE pragma seemed a good idea. The simple program above works as expected, but the warning appears as soon as the 'Functor' superclass is commented back in. It seems to me this should make no difference as Functor is already a superclass of Applicative. It was still there simply by oversight. I think SPECIALIZE should not fail in this case, and if it does, it would be really helpful to have a better error message. 'Too complicated' does not help in tracking down what needs to be changed for the specialization to happen, and given how harsh the overhead is otherwise, this is quite painful. In any case, once the specialization is applied in my actual program, the following error appears: {{{ ghc: panic! (the 'impossible' happened) (GHC version 7.6.3 for i386-apple-darwin): Simplifier ticks exhausted When trying UnfoldingDone a_saCf{v} [lid] To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 66169 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} It seems like I need a -fsimpl-tick-factor of 450-500 for the compilation to succeed, resulting in a ~3x increase in binary size and a ~4x increase in compile time. The resulting code at least seems to benefit from the specialization as expected. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8331 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler