[Haskell-beginners] Time interval calculation

Daniel Fischer daniel.is.fischer at web.de
Sat Mar 13 15:34:41 EST 2010


Am Samstag 13 März 2010 21:20:58 schrieb legajid:
> Hi,
> my following code should show time before executing listeprem, then time
> after execution.
>
> import System.Time
> gettime :: IO ClockTime
> gettime = getClockTime
>
> main=do
>     t1d <- gettime

This gets the time, now.

>     let t1=last (listeprem 5000)

This doesn't do the calculation, it only creates a thunk what to calculate 
should t1 be demanded, takes a few nanoseconds

>     t1f <- gettime

This gets the time, a few nanoseconds later

>     putStrLn ("Methode 1 : " ++ show t1d)
>     putStrLn ("            " ++ show t1)

Now t1 is demanded, and only now it's calculated.

>     putStrLn ("            " ++ show t1f)
>
> Looking at the screen, t1d is displayed then, after a few seconds, t1
> and t1f.
> But, t1d and t1f are equal.
> It seems like if t1d and t1f where calculated at start of procedure,
> before we need calculating t1 for putStrLn.

Exactly.

> How can i have t1f evaluated after t1, so i can calculate time elapsed
> for calculation of t1?

Depends on what sort of value t1 is. If it's a simple value like an Integer 
(as I think it is here, derniere nombre premier avant 5000, 5000-th 
prime?),

{-# LANGUAGE BangPatterns #-}
...
    let !t1 = last (listeprem 5000)
    t1f <- gettime

or

    let t1 = last (listeprem 5000)
    t1f <- t1 `seq` gettime

will do. For small values, printing takes negligible time, so

    t1d <- gettime
    putStrLn ("            " ++ show t1f)
    t1f <- gettime

is another option. But getClockTime isn't particularly exact, I'd suggest 
using System.CPUTime.getCPUTime

>
> Thanks,
> Didier


More information about the Beginners mailing list