[GHC] #13001: EnumFromThenTo is is not a good producer

GHC ghc-devs at haskell.org
Sun Dec 18 17:18:51 UTC 2016


#13001: EnumFromThenTo is is not a good producer
-------------------------------------+-------------------------------------
           Reporter:  George         |             Owner:
               Type:  bug            |            Status:  new
           Priority:  low            |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  MacOS X
       Architecture:  x86_64         |   Type of failure:  Runtime
  (amd64)                            |  performance bug
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# OPTIONS_GHC -Wall #-}

 module Foo where

 testFromTo :: Int -> Int
 testFromTo n = length ([0..(10^n)] :: [Int])

 testFromThenTo :: Int -> Int
 testFromThenTo n = length ([0,2..(10^n)] :: [Int])

 }}}

 {{{
 $ ghci -fobject-code -O
 GHCi, version 8.0.1: http://www.haskell.org/ghc/  :? for help
 Prelude> :load Foo
 :load Foo
 [1 of 1] Compiling Foo              ( Foo.hs, Foo.o )
 Ok, modules loaded: Foo (Foo.o).
 Prelude Foo> :set +s
 :set +s
 Prelude Foo> testFromTo 5
 testFromTo 5
 100001
 (0.02 secs, 97,992 bytes)
 Prelude Foo> testFromThenTo 5
 testFromThenTo 5
 50001
 (0.00 secs, 5,694,424 bytes)
 Prelude Foo> testFromThenTo 6
 testFromThenTo 6
 500001
 (0.02 secs, 56,095,288 bytes)
 Prelude Foo>
 }}}

 I set the Type to bug rather than feature request as the source code in
 http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Enum.html#enumFromTo
 seems to be trying to do list fusion:

 {{{#!hs
 -- efdInt and efdtInt deal with [a,b..] and [a,b..c].
 -- The code is more complicated because of worries about Int overflow.

 -- See Note [How the Enum rules work]
 {-# RULES
 "efdtInt"       [~1] forall x1 x2 y.
                      efdtInt x1 x2 y = build (\ c n -> efdtIntFB c n x1 x2
 y)
 "efdtIntUpList" [1]  efdtIntFB (:) [] = efdtInt
  #-}

 }}}

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


More information about the ghc-tickets mailing list