[GHC] #9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm
GHC
ghc-devs at haskell.org
Fri Sep 12 20:03:18 UTC 2014
#9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Resolution: | Keywords:
Operating System: | Architecture: x86_64 (amd64)
Unknown/Multiple | Difficulty: Unknown
Type of failure: Compile- | Blocked By:
time crash | Related Tickets:
Test Case: T3500b |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by carter):
could this be an instance of the known issue about recursive types
interacting with the inliner?
https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/bugs.html see the
second item there
if i change the program to
{{{
{-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances #-}
module Main where
newtype Mu f = Mu (f (Mu f))
type family Id m
type instance Id m = m
instance Show (Id (f (Mu f))) => Show (Mu f) where
show (Mu f) = show f
{-# NOINLINE show #-}
showMu :: Mu (Either ()) -> String
showMu = show
item :: Mu (Either ())
item = Mu (Right (Mu (Left ())))
main = print (showMu item)
}}}
that is, I mark the show instance NOINLINE, the problem goes away.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9565#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list