#7280: zonkQuantifiedTyVar panic ------------------------------+--------------------------------------------- Reporter: rl | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.1 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Testcase: Blockedby: | Blocking: Related: | ------------------------------+--------------------------------------------- Small program (extracted from the dev version of vector):
{{{ {-# LANGUAGE Rank2Types, MultiParamTypeClasses, FlexibleContexts, TypeFamilies, ScopedTypeVariables #-} module T where type family Mutable (v :: * -> *) :: * -> * -> * class MVector (v :: * -> * -> *) a class MVector (Mutable v) a => Vector v a where copy :: Monad m => Mutable v s a -> v a -> m () data Chunk v s a = Chunk (forall m. (Monad m, Vector v a) => Mutable v s a -> m ()) vstep (v:vs) = Chunk (\mv -> copy mv v) }}} When I compile this, I get: {{{ ghc: panic! (the 'impossible' happened) (GHC version 7.6.1 for x86_64-unknown-linux): zonkQuantifiedTyVar f_afr{tv} [fsk] }}} -- Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7280> GHC <http://www.haskell.org/ghc/> The Glasgow Haskell Compiler _______________________________________________ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs