G'day all.
On a very recently checked out copy of GHC (late last week, from
memory) I get the following panic:
% ghc -fglasgow-exts -c Bug.hs
ghc-5.05: panic! (the `impossible' happened, GHC version 5.05):
applyTys
Please report it as a compiler bug to [EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.
on this code:
module Bug where
type M3 a = forall r. (forall b. M3' b -> (b -> M3' a) -> r) -> r
newtype M3' a
= M3' { mkM3' :: M3 a }
bind :: M3 a -> (a -> M3 b) -> M3 b
bind m k b = b (M3' m) (\a -> M3' (k a))
observe :: M3 a -> a
observe m
= m (\m' k -> mkM3' m'
(\bm k1 -> observe (bind (mkM3' bm)
(\a -> bind (mkM3' (k1 a)) (\a -> mkM3' (k a)))))
)
Cheers,
Andrew Bromage
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs