[GHC] #14301: ghc: panic! (the 'impossible' happened)

GHC ghc-devs at haskell.org
Sun Oct 1 04:12:17 UTC 2017


#14301: ghc: panic! (the 'impossible' happened)
-------------------------------------+-------------------------------------
           Reporter:  mcapodici      |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:  x86_64         |   Type of failure:  None/Unknown
  (amd64)                            |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 **When I build my program I get this:**
 {{{
 play-0.1.0.0: build (exe)
 Preprocessing executable 'play' for play-0.1.0.0...
 [1 of 1] Compiling Main             ( src/Main.hs, .stack-work/dist/x86_64
 -linux-nopie/Cabal-1.24.2.0/build/play/play-tmp/Main.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.0.2 for x86_64-unknown-linux):
         initTc: unsolved constraints
   WC {wc_insol =
         [W] interactD_aL2 :: t_aL1[tau:1] (CHoleCan: interactD)
         [W] interactD_aLt :: t_aLs[tau:1] (CHoleCan: interactD)}

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}
 **The code:**

 {{{

 {-# LANGUAGE GADTs #-}

 module Main where

 import Control.Monad.Trans.Cont
 import Control.Monad.Trans.Class

 --main :: IO ()

 {-- CONTT --
 main = evalContT contt

 contt :: ContT () IO ()
 contt = do
     k <- do
       callCC $ \exit -> do
         lift $ putStrLn "Entry"
         exit $ \_ -> do
           putStrLn "Exit"
     lift $ putStrLn "Inside"
     lift $ k ()

 --}
 {--
 class Monad m => Interact m where
   get :: m String
   say :: String -> m ()

 instance Interact IO where
   get = getLine
   say = putStrLn

 prog :: Interact a => a ()
 prog = do
   say "Hello what is your name?"
   name <- get
   say $ "Hello " ++ name ++ ", I am prog! Goodbye"

 main :: IO ()
 main = prog
 --}


 data InteractD m = InteractD
   { getD :: m String
   , sayD :: String -> m ()
   }

 interactDIO :: InteractD IO
 interactDIO = interactD getLine putStrLn

 interactDIO2 :: InteractD IO
 interactDIO2 = interactD (return "James") putStrLn
 }}}

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


More information about the ghc-tickets mailing list