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

#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 Keywords: ghci panic | Operating System: Unknown/Multiple Architecture: x86 | Type of failure: GHCi crash Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------+------------------------------------- Hi I am a beginner and was playing around with type families when ghc gave me a panic message and suggested I log a bug. I am running Windows 7 with GHC 7.6.3 installed using Haskell Platform 2013.2.0.0. Here is the reduced code producing the panic: {{{ {-# 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' = fromJust (fst <$> (continue c' z' b')) rpt i c' z' b' = let c'' = fromJust (snd <$> (continue c' z' b')) in rpt (i-1) c'' main = putStrLn "" }}} Loading the code in WinGHCi and calling main results in the following {{{ GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Prelude> :cd C:\Dev Prelude> :load "Crash.hs" [1 of 1] Compiling Main ( Crash.hs, interpreted ) Ok, modules loaded: Main. *Main> main ghc: panic! (the 'impossible' happened) (GHC version 7.6.3 for i386-unknown-mingw32): nameModule <<details unavailable>> Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug *Main> }}} There is obviously something degenerate with the code but I guess the compiler should give a better error message. Note it actually compiles, i.e. if the file itself is just compiled but not linked in it does not give any errors. If the degenerate function 'callCont' is changed as follows. {{{ {-# 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 i c' z' b' = fromJust (fst <$> (continue c' z' b')) main = putStrLn "" }}} Then you get the following compile error: {{{ Crash.hs|12 col 18 error| Occurs check: cannot construct the infinite type: uf0 = Maybe uf0 || Expected type: Maybe (F c) || Actual type: F c || In the return type of a call of `rpt' || In the expression: rpt (4 :: Int) c z b || In an equation for `callCont': || callCont c z b || = rpt (4 :: Int) c z b || where || rpt i c' z' b' = fromJust (fst <$> (continue c' z' b')) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8518 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#8518: panic ghci when probably using type families incorrectly -------------------------------------+------------------------------ Reporter: HanStolpo | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: fixed | Keywords: ghci panic Operating System: Unknown/Multiple | Architecture: x86 Type of failure: GHCi crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------ Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: Thank you! Happily the original program compiled with HEAD (shortly to be 7.8.1) gives a sensible error message {{{ T8518.hs:17:78: Could not deduce (F a1 ~ (Z a1 -> B a1 -> F a1)) from the context (Continuation c) bound by the type signature for callCont :: Continuation c => c -> Z c -> B c -> Maybe (F c) at T8518.hs:13:13-64 Relevant bindings include c'' :: a1 (bound at T8518.hs:17:30) b' :: B a1 (bound at T8518.hs:17:21) z' :: Z a1 (bound at T8518.hs:17:18) c' :: a1 (bound at T8518.hs:17:15) rpt :: a -> a1 -> Z a1 -> B a1 -> F a1 (bound at T8518.hs:16:9) In the expression: rpt (i - 1) c'' In the expression: let c'' = fromJust (snd <$> (continue c' z' b')) in rpt (i - 1) c'' }}} I'll add the example as a regression test though! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8518#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8518: panic ghci when probably using type families incorrectly
-------------------------------------+------------------------------
Reporter: HanStolpo | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Resolution: fixed | 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 Simon Peyton Jones

#8518: panic ghci when probably using type families incorrectly -------------------------------------------------+------------------------- Reporter: HanStolpo | Owner: Type: bug | Status: Priority: normal | closed Component: Compiler | Milestone: Resolution: fixed | Version: 7.6.3 Operating System: Unknown/Multiple | Keywords: ghci Type of failure: GHCi crash | panic Test Case: | Architecture: x86 indexed_types/should_fail/T8518 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * testcase: => indexed_types/should_fail/T8518 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8518#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC