#4160: Panic! at the HEAD
-------------------------------+--------------------------------------------
Reporter: LouisWasserman | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.13 | Keywords:
Os: Linux | Testcase:
Architecture: x86 | Failure: Compile-time crash
-------------------------------+--------------------------------------------
Comment(by LouisWasserman):
Replying to [ticket:4160 LouisWasserman]:
> HEAD panics, but 6.12.1 doesn't, at the following module:
>
> {{{
> {-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, TypeFamilies #-}
> module Foo where
>
> data P f g r = f r :*: g r
> type family TrieMapT (f :: * -> *) :: * -> (* -> *) -> * -> *
> newtype PMap m1 (m2 :: * -> (* -> *) -> * -> *) k (a :: * -> *) ix =
PMap (m1 k (m2 k a) ix)
> type instance TrieMapT (P f g) = PMap (TrieMapT f) (TrieMapT g)
>
> class TrieKeyT f m where
> unionT :: (TrieMapT f ~ m) => (f k -> a ix -> a ix -> a ix) ->
> m k a ix -> m k a ix -> m k a ix
> sizeT :: (TrieMapT f ~ m) => m k a ix -> Int
>
> instance (TrieKeyT f m1, TrieKeyT g m2) => TrieKeyT (P f g) (PMap m1 m2)
where
> unionT f (PMap m1) (PMap m2) = PMap (uT (\ a -> unionT (\ b -> f
(a :*: b))) m1 m2)
> where uT = unionT
> }}}
>
Oh, I forgot -- it only panics with -O.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4160#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs