#5981: quadratic slowdown with very long module names
------------------------------------------+---------------------------------
 Reporter:  guest                         |          Owner:                   
     Type:  bug                           |         Status:  new              
 Priority:  normal                        |      Component:  Compiler (Parser)
  Version:  7.4.1                         |       Keywords:                   
       Os:  Unknown/Multiple              |   Architecture:  Unknown/Multiple 
  Failure:  Compile-time performance bug  |       Testcase:                   
Blockedby:                                |       Blocking:                   
  Related:                                |  
------------------------------------------+---------------------------------
 Posting this for completeness, in case it exposes something more generally
 suboptimal: I'm not suggesting that such very long module names are likely
 ever to occur in the real world (and indeed Hugs has a 4k identifier
 length limit).

 In short: parsing "module Module where ..." takes O(length(Module)²) time.

 test program (NB: overwrites "./test.hs" without hesitation):

 {{{
 module Main (main) where

 import Control.Monad (forM_)
 import Data.List (genericReplicate)
 import Data.Time.Clock (getCurrentTime, diffUTCTime)
 import System.Environment (getArgs)
 import System.IO (stdout, hSetBuffering, BufferMode(NoBuffering))
 import System.Process (system)

 fibs :: [Integer]
 fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

 test :: Integer -> String
 test n = "module M" ++ genericReplicate n 'm' ++ " (main) where main :: IO
 () ; main = return ()\n"

 main :: IO ()
 main = do
   [count] <- getArgs
   hSetBuffering stdout NoBuffering
   forM_ (take (read count) fibs) $ \n -> do
     writeFile "test.hs" (test n)
     t0 <- getCurrentTime
     _ <- system "ghci </dev/null >/dev/null test.hs"
     t1 <- getCurrentTime
     putStrLn $ unwords [show n, show (diffUTCTime t1 t0)]
 }}}

 output:

 {{{
 0 0.287553s
 1 0.28064s
 1 0.294821s
 2 0.262876s
 3 0.27628s
 5 0.27605s
 8 0.279612s
 13 0.276299s
 21 0.267666s
 34 0.26738s
 55 0.295614s
 89 0.270626s
 144 0.264852s
 233 0.297883s
 377 0.295505s
 610 0.259852s
 987 0.260083s
 1597 0.294578s
 2584 0.297104s
 4181 0.312192s
 6765 0.305412s
 10946 0.364343s
 17711 0.415955s
 28657 0.562181s
 46368 0.708429s
 75025 1.093678s
 121393 1.975239s
 196418 3.702828s
 317811 8.17462s
 514229 19.291228s
 832040 45.603124s
 1346269 116.74497s
 2178309 308.660996s
 }}}

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

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to