[GHC] #15646: ghci takes super long time to find the type of large fractional number

GHC ghc-devs at haskell.org
Mon Oct 1 20:08:49 UTC 2018


#15646: ghci takes super long time to find the type of large fractional number
-------------------------------------+-------------------------------------
        Reporter:  Johannkokos       |                Owner:
                                     |  JulianLeviston
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.6.1
       Component:  GHCi              |              Version:  8.4.3
      Resolution:                    |             Keywords:  newcomer
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:                    |
-------------------------------------+-------------------------------------

Comment (by osa1):

 Right, so just to summarize what JulianLeviston said in my words and give
 a concrete example, in this program:

 {{{
 {-# LANGUAGE TemplateHaskell #-}

 module Lib where

 import Language.Haskell.TH

 foo :: Q Exp
 foo = [| 1e1000000 |]
 }}}

 we use the same problematic code path when parsing the quasi-quotation and
 end up calculating a huge `Integer` when parsing (which can be seen easily
 with `-ddump-parsed-ast`). This much is probably obvious if you're
 familiar with TH internals.

 This will be fixed when we update the parser. The actual problem is we
 desugar this quasi-quote to:

 {{{
 foo = litE (rationalL (GHC.Real.:% @ Integer <huge integer> 1))
 }}}

 where `litE` is simply `return . LitE` and `rationalL` is `RationalL`.
 `RationalL` takes a `Rational` argument, which is what we're trying to
 avoid doing in compile-time. Furthermore, because these are
 [http://hackage.haskell.org/package/template-haskell-2.13.0.0/docs
 /Language-Haskell-TH-Syntax.html#t:Lit public types] they are hard (if not
 impossible) to change. I see two options:

 - Do the computation when generating the TH quasi-quote expressions
 (during desugaring, in `DsMeta`). This way the TH syntax wouldn't change
 (we would generate exactly the same desugared expr for this program), and
 the example above would take forever to compile.

 - Add one more literal constructor to TH syntax that looks like our new
 `FractionalLit` for this purpose. Then we could use our new desugaring
 (comment:23) in `Convert.hs` when we actually splice the expression. So
 both quasi-quote compilation and splicing remain fast.

 Any thoughts?

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


More information about the ghc-tickets mailing list