
#9985: GHC panic with ViewPatterns and GADTs in a proc pattern -------------------------------------+------------------------------------- Reporter: Rafbill | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The following code causes a ghc panic with versions 7.8.4 and 7.9. {{{#!hs module A where {-# LANGUAGE GADTs, ViewPatterns, PatternSynonyms, DataKinds, Arrows, TypeOperators, TypeFamilies, UndecidableInstances #-} import Control.Arrow data Nat = Z | S Nat data Vec n a where VNil :: Vec Z a VCons :: a -> Vec n a -> Vec (S n) a viewVNil :: Vec Z a -> () viewVNil VNil = () viewVCons :: Vec (S n) a -> (a, Vec n a) viewVCons (VCons a as) = (a, as) pattern (:>) :: a -> Vec n a -> Vec (S n) a pattern a :> as <- (viewVCons -> (a, as)) pattern VNil' <- (viewVNil -> ()) type family n + m where n + Z = n n + S m = S (n + m) type family P2 n where P2 Z = S Z P2 (S n) = P2 n + P2 n class A n where a :: Arrow b => b (Vec (P2 n) a) a instance A Z where a = proc (a :> VNil) -> returnA -< a }}} If the pattern (a :> VNil) is changed to (a :> _) or (a :> VNil'), the code compiles. GADTs pattern are not allowed to appear in proc patterns, but view patterns seems to be able to bypass this restriction, #9953, and the check on subpatterns. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9985 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler