Bugs item #1062982, was opened at 2004-11-09 10:03
Message generated for change (Settings changed) made by simonmar
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1062982&group_id=8032

Category: Compiler
Group: 6.4
Status: Open
Resolution: None
Priority: 8
Submitted By: Nobody/Anonymous (nobody)
>Assigned to: Simon Peyton Jones (simonpj)
Summary: panic with GADTs

Initial Comment:
Version : 6.3 (cvs snapshot)
OS : Mac OS X 10.3.6

Observe:

$ ghc -fglasgow-exts -c Tdpe.hs
ghc-6.3: panic! (the `impossible' happened, GHC version 6.3):
        applyTypeToArgs v{v s1c3} sat_s1c2{v}

Please report it as a compiler bug to glasgow-haskell-
[EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.



"Tdpe.hs" is following:

module Tdpe where

infixr |->
data Type t where
    TBase :: Type Base
    TFun  :: Type a -> Type b -> Type (a -> b)
(|->) = TFun

b :: Type Base
b = TBase

newtype Base = In { out :: Term Base }

data Term t where
    App :: Term (a->b) -> Term a -> Term b
    Fun :: (Term a -> Term b) -> Term (a->b)

reify :: Type t -> t -> Term t
reify (TBase) v    = out v
reify (TFun a b) v = Fun (\x -> reify b (v (reflect a x)))

reflect :: Type t -> Term t -> t
reflect (TBase) e    = In e
reflect (TFun a b) e = \x -> reflect b (App e (reify a x))


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

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

Reply via email to