[GHC] #8518: panic ghci when probably using type families incorrectly

GHC ghc-devs at haskell.org
Mon Nov 11 04:30:53 UTC 2013


#8518: panic ghci when probably using type families incorrectly
-------------------------------------+------------------------------
        Reporter:  HanStolpo         |            Owner:
            Type:  bug               |           Status:  new
        Priority:  normal            |        Milestone:
       Component:  Compiler          |          Version:  7.6.3
      Resolution:                    |         Keywords:  ghci panic
Operating System:  Unknown/Multiple  |     Architecture:  x86
 Type of failure:  GHCi crash        |       Difficulty:  Unknown
       Test Case:                    |       Blocked By:
        Blocking:                    |  Related Tickets:
-------------------------------------+------------------------------

Comment (by HanStolpo):

 If the code is fixed to be valid compilable code then it does not panic
 any more.

 {{{
 {-# LANGUAGE TypeFamilies #-}
 import Data.Maybe
 import Control.Applicative

 class Continuation c where
     type Z c
     type B c
     type F c
     continue ::  c -> (Z c) -> (B c) -> Maybe ((F c), c)

 callCont :: Continuation c => c -> (Z c) -> (B c) -> Maybe (F c)
 callCont c z b = rpt (4 :: Int) c z b
     where
         rpt 0 c' z' b' = (fst <$> (continue c' z' b'))
         rpt i c' z' b' = let c'' = fromJust (snd <$> (continue c' z' b'))
 in rpt (i-1) c'' z' b'

 main = putStrLn ""
 }}}

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


More information about the ghc-tickets mailing list