[GHC] #16382: Lifting a function from where clause to top level causes compilation time to triple

GHC ghc-devs at haskell.org
Sun Mar 3 21:25:45 UTC 2019


#16382: Lifting a function from where clause to top level causes compilation time
to triple
-------------------------------------+-------------------------------------
           Reporter:  danidiaz       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.4.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:
-------------------------------------+-------------------------------------
 I have this program that depends on the library "red-black-record" version
 2.0.2.2 on Hackage:

 {{{#!hs
 {-# LANGUAGE DataKinds, TypeApplications #-}
 module Main where

 import Data.RBR (FromList,Delete,Variant,I,injectI,winnowI,match)

 import GHC.TypeLits

 type Phase01 = FromList '[
       '("ctor1",Int),   '("ctor2",Bool),  '("ctor4",Char),
 '("ctor3",Char),
       '("ctor6",Char),  '("ctor5",Char),  '("ctor10",Char),
 '("ctor11",Char),
       '("ctor13",Char), '("ctor14",Char), '("ctor39",Char),
 '("ctor46",Char),
       '("ctor47",Char), '("ctor44",Char), '("ctor43",Char),
 '("ctor7",Char),
       '("ctor9",Char),  '("ctor20",Char), '("ctor45",Char),
 '("ctor21",Char),
       '("ctor48",Char), '("ctor49",Char), '("ctor50",Char),
 '("ctor41",Char),
       '("ctor33",Char), '("ctor32",Char), '("ctor42",Char),
 '("ctor22",Char),
       '("ctor23",Char), '("ctor8",Char),  '("ctor40",Char),
 '("ctor29",Char),
       '("ctor24",Char), '("ctor38",Char), '("ctor25",Char),
 '("ctor26",Char),
       '("ctor27",Char), '("ctor28",Char), '("ctor36",Char),
 '("ctor52",Char),
       '("ctor51",Char), '("ctor53",Char), '("ctor12",Char),
 '("ctor54",Char),
       '("ctor15",Char), '("ctor31",Char), '("ctor30",Char),
 '("ctor34",Char),
       '("ctor35",Char), '("ctor17",Char), '("ctor16",Char),
 '("ctor18",Char),
       '("ctor19",Char), '("ctor37",Char)
       ]

 type Phase02 = Delete "ctor1" Int Phase01

 main :: IO ()
 main = print (match @"ctor17" (fromPhase1ToPhase2 (injectI @"ctor1" 2)))
     where
     fromPhase1ToPhase2 :: Variant I Phase01 -> Variant I Phase02
     fromPhase1ToPhase2 v = case winnowI @"ctor1" @Int v of
         Right z -> injectI @"ctor2" False
         Left l -> l
 }}}

 "red-black-record" provides extensible variants; the code is basically
 removing a branch from a variant with 50-plus branches, and then trying to
 match another branch. It is type family-heavy code.

 The code as it is takes **~9 seconds** to compile on my machine. But when
 I move the `fromPhase1ToPhase2` function to the top level (including the
 signature) compilation time balloons to **~29 seconds**. Is there a reason
 it should be so?

 As another datapoint, moving the function to the top level but omitting
 the complex type-level map parameters (`Phase01`, `Phase02`) using partial
 type signatures (also requires a new type application) compiles in **~9
 seconds** again.

 {{{#!hs
 {-# LANGUAGE PartialTypeSignatures #-}
 {-# OPTIONS_GHC -Wno-partial-type-signatures #-}

 -- ...

 type Phase02 = Delete "ctor1" Int Phase01

 fromPhase1ToPhase2 :: Variant I _ -> Variant I _
 fromPhase1ToPhase2 v = case winnowI @"ctor1" @Int @Phase01 v of
     Right z -> injectI @"ctor2" False
     Left l -> l

 main :: IO ()
 main = print (match @"ctor17" (fromPhase1ToPhase2 (injectI @"ctor1" 2)))
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16382>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list