[GHC] #13386: Poor compiler performance with type families
GHC
ghc-devs at haskell.org
Tue Mar 7 08:15:30 UTC 2017
#13386: Poor compiler performance with type families
-------------------------------------+-------------------------------------
Reporter: adamgundry | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Compile-time
Unknown/Multiple | performance bug
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider:
{{{#!hs
{-# LANGUAGE DataKinds, TypeApplications, TypeFamilies, TypeOperators,
UndecidableInstances #-}
{-# OPTIONS_GHC -freduction-depth=0 #-}
module TypeFamilyPerf where
import GHC.TypeLits
type DivisibleBy x y = Help x y 0 (CmpNat x 0)
type family Help x y z b where
Help x y z EQ = True
Help x y z LT = False
Help x y z GT = Help x y (z+y) (CmpNat x z)
foo :: DivisibleBy y 3 ~ True => proxy y -> ()
foo _ = ()
type N = 1002
k = foo @N undefined
}}}
On my machine `ghc-8.0.2 -O0` takes 4-5s to compile this module, with the
time increasing as `N` increases (but note that it must be a multiple of
3, otherwise typechecking fails quickly). The problem seems to be that
desugaring creates an enormous number of coercions in the representation
of `k`.
Perhaps this isn't terribly surprising, but I think we can do better. It
should be possible to represent a proof of `DivisibleBy 1002 3 ~ True`
compactly: the only information required should be the LHS and the number
of reduction steps to take (and perhaps caching the RHS might be
worthwhile).
{{{
[1 of 1] Compiling TypeFamilyPerf ( TypeFamilyPerf.hs, TypeFamilyPerf.o
)
*** Parser [TypeFamilyPerf]:
!!! Parser [TypeFamilyPerf]: finished in 0.50 milliseconds, allocated
0.655 megabytes
*** Renamer/typechecker [TypeFamilyPerf]:
!!! Renamer/typechecker [TypeFamilyPerf]: finished in 91.70 milliseconds,
allocated 58.617 megabytes
*** Desugar [TypeFamilyPerf]:
Result size of Desugar (after optimization)
= {terms: 44, types: 70, coercions: 6,058}
!!! Desugar [TypeFamilyPerf]: finished in 3781.83 milliseconds, allocated
8775.375 megabytes
*** Simplifier [TypeFamilyPerf]:
Result size of Simplifier iteration=1
= {terms: 27, types: 62, coercions: 6,060}
Result size of Simplifier
= {terms: 27, types: 62, coercions: 6,053}
!!! Simplifier [TypeFamilyPerf]: finished in 42.93 milliseconds, allocated
68.321 megabytes
*** CoreTidy [TypeFamilyPerf]:
Result size of Tidy Core = {terms: 27, types: 62, coercions: 6,053}
!!! CoreTidy [TypeFamilyPerf]: finished in 0.52 milliseconds, allocated
0.766 megabytes
Created temporary directory: /tmp/ghc5526_0
*** CorePrep [TypeFamilyPerf]:
Result size of CorePrep = {terms: 32, types: 74, coercions: 6,053}
!!! CorePrep [TypeFamilyPerf]: finished in 0.37 milliseconds, allocated
0.160 megabytes
*** Stg2Stg:
*** CodeGen [TypeFamilyPerf]:
!!! CodeGen [TypeFamilyPerf]: finished in 0.00 milliseconds, allocated
1.310 megabytes
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13386>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list