Bugs item #646201, was opened at 2002-11-30 21:11
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=646201&group_id=8032

Category: Compiler
Group: 5.04.1
Status: Open
Resolution: None
Priority: 5
Submitted By: Markus Lauer (mlauer)
Assigned to: Nobody/Anonymous (nobody)
Summary: ghc-5.04: panic! ... tySplitTyConApp ...

Initial Comment:
compiling the below program with
   ghc -fglasgow-exts Main.hs

gives the following error:

ghc-5.04: panic! (the `impossible' happened, GHC
version 5.04):
        tcSplitTyConApp forall x{-r6S-} :: *.
Main.L{-rr-} x{-r6S-}


-----------------------------------------------------
-- Main.hs

module Main where

newtype FA c = FA (forall x . c x)
newtype L x = L [x]

my_nil = FA (L []) :: FA L

sample :: String
sample = case my_nil of FA (L x) -> "foo"++x 

-- -- but this works fine
-- sample = case my_nil of FA x -> case x of L y ->
"foo"++y 

main = print sample


----------------------------------------------------------------------

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=646201&group_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to