[GHC] #7258: Compiling DynFlags is jolly slow

GHC ghc-devs at haskell.org
Tue Nov 7 14:53:49 UTC 2017


#7258: Compiling DynFlags is jolly slow
-------------------------------------+-------------------------------------
        Reporter:  simonpj           |                Owner:  simonpj
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.6.1
      Resolution:                    |             Keywords:  deriving-perf
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 tdammers):

 I've narrowed it down a bit more.

 This behaves nicely:

 {{{
 module D where

 import Text.ParserCombinators.ReadP as ReadP
 import Control.Monad.State as State
 import Data.Char (ord)

 data DT = DT
     { field0 :: Int
     , field2 :: Int
     , field3 :: Int
     , field4 :: Int
     , field5 :: Int
     , field6 :: Int
     , field7 :: Int
     , field8 :: Int
     , field9 :: Int
     , field10 :: Int
     }
 getlD :: IO DT
 getlD = DT
     <$> (read <$> getLine)
     <*> (read <$> getLine)
     <*> (read <$> getLine)
     <*> (read <$> getLine)
     <*> (read <$> getLine)
     <*> (read <$> getLine)
     <*> (read <$> getLine)
     <*> (read <$> getLine)
     <*> (read <$> getLine)
     <*> (read <$> getLine)
 }}}

 But this doesn't:

 {{{
 module D where

 import Text.ParserCombinators.ReadP as ReadP
 import Control.Monad.State as State
 import Data.Char (ord)

 data DT = DT
     { field0 :: Int
     , field2 :: Int
     , field3 :: Int
     , field4 :: Int
     , field5 :: Int
     , field6 :: Int
     , field7 :: Int
     , field8 :: Int
     , field9 :: Int
     , field10 :: Int
     }
 readD :: ReadP DT
 readD = DT
     <$> (ord <$> ReadP.get)
     <*> (ord <$> ReadP.get)
     <*> (ord <$> ReadP.get)
     <*> (ord <$> ReadP.get)
     <*> (ord <$> ReadP.get)
     <*> (ord <$> ReadP.get)
     <*> (ord <$> ReadP.get)
     <*> (ord <$> ReadP.get)
     <*> (ord <$> ReadP.get)
     <*> (ord <$> ReadP.get)
 }}}

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


More information about the ghc-tickets mailing list