[GHC] #8814: 7.8 optimizes attoparsec improperly

GHC ghc-devs at haskell.org
Fri Feb 21 06:16:43 UTC 2014


#8814: 7.8 optimizes attoparsec improperly
------------------------------+--------------------------------------------
       Reporter:  joelteon    |             Owner:
           Type:  bug         |            Status:  new
       Priority:  normal      |         Milestone:
      Component:  Compiler    |           Version:  7.8.1-rc1
       Keywords:              |  Operating System:  MacOS X
   Architecture:  x86_64      |   Type of failure:  Runtime performance bug
  (amd64)                     |         Test Case:
     Difficulty:  Unknown     |          Blocking:
     Blocked By:              |
Related Tickets:              |
------------------------------+--------------------------------------------
 {{{
 #!haskell
 {-# LANGUAGE OverloadedStrings #-}

 import Control.Applicative
 import qualified Data.Attoparsec.Text as A
 import Data.Text (Text)
 import qualified Data.Text as T

 testParser :: Text -> Either String Int
 testParser f = fmap length
     . A.parseOnly (many (A.char 'b' <|> A.anyChar))
     $ f

 main :: IO ()
 main = print . testParser $ T.replicate 50000 "a"
 }}}

 On GHC 7.6.3 with `-O2`:
 {{{
 real    0m0.062s
 user    0m0.022s
 sys     0m0.007s
 }}}

 On GHC 7.8 tip with `-O2`:
 {{{
 real    0m12.700s
 user    0m12.504s
 sys     0m0.165s
 }}}

 On GHC 7.6.3 with `-O0`:
 {{{
 real    0m0.077s
 user    0m0.025s
 sys     0m0.007s
 }}}

 On GHC 7.8 tip with `-O0`:
 {{{
 real    0m0.055s
 user    0m0.026s
 sys     0m0.007s
 }}}

 This seems to be related to the use of `<|>`; if I change the program so
 that the second branch (`A.anyChar`) is never taken, 7.8 behavior is
 roughly the same as 7.6 under any optimization level.

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


More information about the ghc-tickets mailing list