Re: [Haskell-cafe] estimating the speed of operation

2009-02-18 Thread Thomas DuBuisson
Is this benchmark ment to measure something in particular?  Did you
not copy and paste it?  It doesn't even compile:

> parse error on input `module'
> not in scope: `pack'
> Couldn't match expected type `(Integer, Integer)' against inferred type `IO 
> Integer'
> Couldn't match expected type `(Integer, Integer)' against inferred type `IO 
> (Integer, Integer)'
etc etc.

Also, you don't have a 'main' with any print statements which makes me
think you are interpreting it - a poor way to benchmark.  It should be
compiled with -O2.

After fixing up these issue, and adding a main:

> ghc md5.hs -O2 --make ; ./md5
[[(0,16),(0,5)],[(0,10),(0,11)],[(0,78),(0,77)],[(0,770),(0,746)]]

And the code is:
> import qualified Data.ByteString.Lazy.Char8 as L8
> import Data.Digest.Pure.MD5
> import System.IO.Unsafe
> import System.Time
> import System.Random
> import Data.Char
>
> clockTime2Tuple (TOD sec pic) = (sec, pic)
>
> getClockTimeTuple :: IO (Integer, Integer)
> getClockTimeTuple = getClockTime >>= return . clockTime2Tuple
>
> subTimeTuples (s2,ps2) (s1,ps1) =
>   let dps = ps2-ps1
>   (s,ps) = (s2 -s1 - (if dps < 0 then 1 else 0), if dps<0 then 
> dps+(10^12) else dps)
>   in (s, ps `div` (10^6))
>
> test_md5 :: [L8.ByteString] -> Int -> IO [(Integer,Integer)]
> test_md5 test_input n = flip mapM test_input
>( \ input_row -> do
>t1 <- getClockTimeTuple
>sequence_ (replicate n (return $ md5 input_row))
>t2 <- getClockTimeTuple
>dt <- return $ subTimeTuples t2 t1
>return dt
>)
>
> test_list = [ L8.pack "Hello world!"] ++ [L8.replicate 100 ':']
>
> main = do
>   x <- mapM (test_md5 test_list) [1000, 1, 10, 100]
>   print x


Could someone with lots of spare time please write an e-mail filter
that attempts to compile alledged code segments and cans the e-mail if
it fails?

Tom

On Wed, Feb 18, 2009 at 5:21 AM, Belka  wrote:
>
> Thanks alot, Bulat!
>
> New results are much better:
> ---
> test_list =
> [L8.pack "Hello world!"] ++
> [L8.replicate 100 ':']
> ---
> The results are (iterations_count, microseconds):
> (1000,  [300 +/- 200 , 18400  +/- 100])
> (1, [1030 +/- 10 , 19950 +/- 50 ])
> (10, [9100 +/- 100 , 55000 +/- 15000])
> (100, [89850 +/- 500 ,185000 +/- 500 ])
>
> I also played a bit with bang patterns, to make input stricter, but this
> gave the same result.
> ---
> For the first test string time grow almost linearly, what can't be said
> about the second string. I still wonder if (and how) GHC optimizes the
> process.
>
> Belka
> --
> View this message in context: 
> http://www.nabble.com/estimating-the-speed-of-operation-tp22075843p22078560.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] estimating the speed of operation

2009-02-18 Thread Belka

Thanks alot, Bulat!

New results are much better:
---
test_list =
[L8.pack "Hello world!"] ++
[L8.replicate 100 ':'] 
---
The results are (iterations_count, microseconds):
(1000,  [300 +/- 200 , 18400  +/- 100])
(1, [1030 +/- 10 , 19950 +/- 50 ])
(10, [9100 +/- 100 , 55000 +/- 15000])
(100, [89850 +/- 500 ,185000 +/- 500 ]) 

I also played a bit with bang patterns, to make input stricter, but this
gave the same result.
---
For the first test string time grow almost linearly, what can't be said
about the second string. I still wonder if (and how) GHC optimizes the
process.

Belka
-- 
View this message in context: 
http://www.nabble.com/estimating-the-speed-of-operation-tp22075843p22078560.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] estimating the speed of operation

2009-02-18 Thread Bulat Ziganshin
Hello Belka,

Wednesday, February 18, 2009, 1:15:32 PM, you wrote:

> sequence_ (replicate n (return $ md5 input_row))

$!



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] estimating the speed of operation

2009-02-18 Thread Belka

Hello, communion people!

I have a little problem and ask for an advice. I'm trying to estimate the
performance speed of one pure function, but get some strange results.
-
import qualified module Data.ByteString.Lazy.Char8 as L8
import module Data.Digest.Pure.MD5
import module System.IO.Unsafe
import module System.Time
import module System.Random
import module Data.Char

clockTime2Tuple (TOD sec pic) = (sec, pic)
getClockTimeTuple = getClockTime >>= (\ x -> return $ clockTime2Tuple x)
subTimeTuples (s2,ps2) (s1,ps1) = let dps = ps2-ps1 in let (s,ps) =
(s2-s1-(if dps<0 then 1 else 0), if dps<0 then dps+(10^12) else dps) in (s,
(div) ps (10^6))

test_md5 test_input n = flip mapM test_input
( \ input_row -> do
t1 <- getClockTimeTuple
sequence_ (replicate n (return $ md5 input_row))
t2 <- getClockTimeTuple 
dt <- subTimeTuples t2 t1
return (dt)
)

test_list = 
[ pack "Hello world!"] ++ 
[L8.replicate 100 ':']
-
The results are (iterations_count, microseconds):
(1000,  [105,105]) (+/- 10)
(1, [1000,950]) (+/- 50)
(10, [9050,9000]) (+/- 50)
(100, [89200,89150]) (+/- 100)
-
I suspect following problems, which make the results non-objective:
1. I cant get out of laziness
2. I don't turn off GHC internal optimizers
So, perhaps, GHC evaluates the MD5 once, but cycles on something else?.. For
now I can only guess. Could anybody, please clarify and maybe suggest
configuration, which would allow objective speed estimation?

Thanks in advance,
Best regards,
Belka
-- 
View this message in context: 
http://www.nabble.com/estimating-the-speed-of-operation-tp22075843p22075843.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe