
#14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): To make the data type version of the program as slow to compile as the data family instance version, you can use explicit guards: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where class SEq k where (%==) :: forall (a :: k) (b :: k). Sing a -> Sing b -> () infix 4 %== data Foo a b c d = A a b c d | B a b c d | C a b c d | D a b c d | E a b c d | F a b c d data Sing (z_awDE :: k) where SA :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('A a b c d) SB :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('B a b c d) SC :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('C a b c d) SD :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('D a b c d) SE :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('E a b c d) SF :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('F a b c d) instance (SEq a, SEq b, SEq c, SEq d) => SEq (Foo a b c d) where (%==) x y | SA {} <- x , SA {} <- y = () | SA {} <- x , SB {} <- y = () | SA {} <- x , SC {} <- y = () | SA {} <- x , SD {} <- y = () | SA {} <- x , SE {} <- y = () | SA {} <- x , SF {} <- y = () | SB {} <- x , SA {} <- y = () | SB {} <- x , SB {} <- y = () | SB {} <- x , SC {} <- y = () | SB {} <- x , SD {} <- y = () | SB {} <- x , SE {} <- y = () | SB {} <- x , SF {} <- y = () | SC {} <- x , SA {} <- y = () | SC {} <- x , SB {} <- y = () | SC {} <- x , SC {} <- y = () | SC {} <- x , SD {} <- y = () | SC {} <- x , SE {} <- y = () | SC {} <- x , SF {} <- y = () | SD {} <- x , SA {} <- y = () | SD {} <- x , SB {} <- y = () | SD {} <- x , SC {} <- y = () | SD {} <- x , SD {} <- y = () | SD {} <- x , SE {} <- y = () | SD {} <- x , SF {} <- y = () | SE {} <- x , SA {} <- y = () | SE {} <- x , SB {} <- y = () | SE {} <- x , SC {} <- y = () | SE {} <- x , SD {} <- y = () | SE {} <- x , SE {} <- y = () | SE {} <- x , SF {} <- y = () | SF {} <- x , SA {} <- y = () | SF {} <- x , SB {} <- y = () | SF {} <- x , SC {} <- y = () | SF {} <- x , SD {} <- y = () | SF {} <- x , SE {} <- y = () | SF {} <- x , SF {} <- y = () }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14899#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler