
#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): Curiously, data family instances seem to play a role in this. If I replace the data family formulation of `Sing` with a normal datatype: {{{#!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) $([d| instance (SEq a, SEq b, SEq c, SEq d) => SEq (Foo a b c d) where (%==) (SA _ _ _ _) (SA _ _ _ _) = () (%==) (SA _ _ _ _) (SB _ _ _ _) = () (%==) (SA _ _ _ _) (SC _ _ _ _) = () (%==) (SA _ _ _ _) (SD _ _ _ _) = () (%==) (SA _ _ _ _) (SE _ _ _ _) = () (%==) (SA _ _ _ _) (SF _ _ _ _) = () (%==) (SB _ _ _ _) (SA _ _ _ _) = () (%==) (SB _ _ _ _) (SB _ _ _ _) = () (%==) (SB _ _ _ _) (SC _ _ _ _) = () (%==) (SB _ _ _ _) (SD _ _ _ _) = () (%==) (SB _ _ _ _) (SE _ _ _ _) = () (%==) (SB _ _ _ _) (SF _ _ _ _) = () (%==) (SC _ _ _ _) (SA _ _ _ _) = () (%==) (SC _ _ _ _) (SB _ _ _ _) = () (%==) (SC _ _ _ _) (SC _ _ _ _) = () (%==) (SC _ _ _ _) (SD _ _ _ _) = () (%==) (SC _ _ _ _) (SE _ _ _ _) = () (%==) (SC _ _ _ _) (SF _ _ _ _) = () (%==) (SD _ _ _ _) (SA _ _ _ _) = () (%==) (SD _ _ _ _) (SB _ _ _ _) = () (%==) (SD _ _ _ _) (SC _ _ _ _) = () (%==) (SD _ _ _ _) (SD _ _ _ _) = () (%==) (SD _ _ _ _) (SE _ _ _ _) = () (%==) (SD _ _ _ _) (SF _ _ _ _) = () (%==) (SE _ _ _ _) (SA _ _ _ _) = () (%==) (SE _ _ _ _) (SB _ _ _ _) = () (%==) (SE _ _ _ _) (SC _ _ _ _) = () (%==) (SE _ _ _ _) (SD _ _ _ _) = () (%==) (SE _ _ _ _) (SE _ _ _ _) = () (%==) (SE _ _ _ _) (SF _ _ _ _) = () (%==) (SF _ _ _ _) (SA _ _ _ _) = () (%==) (SF _ _ _ _) (SB _ _ _ _) = () (%==) (SF _ _ _ _) (SC _ _ _ _) = () (%==) (SF _ _ _ _) (SD _ _ _ _) = () (%==) (SF _ _ _ _) (SE _ _ _ _) = () (%==) (SF _ _ _ _) (SF _ _ _ _) = () |]) }}} Then the compilation time for GHC HEAD goes back to being the same as in 8.4.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14899#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler