#3059: 3 different behaviours depending on profiling settings and on a 
used-only-
once form being top-level
--------------------+-------------------------------------------------------
Reporter:  jkff     |          Owner:          
    Type:  bug      |         Status:  new     
Priority:  normal   |      Component:  Compiler
 Version:  6.10.1   |       Severity:  normal  
Keywords:           |       Testcase:          
      Os:  Windows  |   Architecture:  x86     
--------------------+-------------------------------------------------------
 Below are two versions of a program using regex-tdfa-1.0.
 The versions differ in whether a form that is used exactly once in 'main'
 is top-level or declared inside 'where' in main.
 Both versions are compiled with/without profiling and the profiled version
 is called with/without +RTS -p.
 I obtain three drastically different performance results and, in the case
 where the form is top-level and profiling is turned on, a compilation bug
 is clearly seen.
 {{{
 module Main where

 import Text.Regex.TDFA
 import qualified Data.ByteString.Lazy.Char8 as L
 import qualified Data.ByteString.Char8 as S


 main = putStrLn . show . length . filter (pat . S.concat . L.toChunks) .
 replicate 100000 $ L.pack "Hello world foo=123 whereas bar=456 Goodbye"

 pat = (=~ ".*foo=([0-9]+).*bar=([0-9]+).*")


 ghc -O2 --make regex-test.hs
 ./regex-test +RTS -s
 0.00s

 ghc -O2 --make -prof -auto-all regex-test.hs
 ./regex-test +RTS -s
 265.31s

 ./regex-test +RTS -p
 276.84s
 'compile' is called 100000 times.



 module Main where

 import Text.Regex.TDFA
 import qualified Data.ByteString.Lazy.Char8 as L
 import qualified Data.ByteString.Char8 as S


 main = putStrLn . show . length . filter (pat . S.concat . L.toChunks) .
 replicate 100000 $ L.pack "Hello world foo=123 whereas bar=456 Goodbye"
     where pat = (=~ ".*foo=([0-9]+).*bar=([0-9]+).*")


 ghc -O2 --make regex-test.hs
 ./regex-test +RTS -s
 8.86s

 (I don't know how this result appeared: it is too small to result from
 1mln regex compilations, but too big to be 'normal')

 ghc -O2 --make -prof -auto-all regex-test.hs
 ./regex-test +RTS -s
 0.00s

 ./regex-test +RTS -p
 0.00s
 'compile' is called 2 times.
 }}}

 Core for the first program with/without profiling differs in the aspect
 that with profiling, the partial application (=~) does not get memoized.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3059>
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