[Haskell-beginners] force strict expression evaluation

Daniel Fischer daniel.is.fischer at googlemail.com
Tue Aug 2 18:16:58 CEST 2011


On Tuesday 02 August 2011, 17:58:59, Ovidiu Deac wrote:
> I'm trying to do some performance evaluation and I'm stuck with the
> fact that Haskell's lazy evaluation - which make my sort extremely
> fast :)

Well, *I* can do nothing even faster ;)

> 
> I read this page:
> http://www.haskell.org/haskellwiki/Performance/Strictness but I didn't
> get it so I'm asking here: How do I make the function 'measure' to
> actually force the evaluation of (f p)?

You have to make the getting of the second time value depend on (f p) - and 
in such a way that f p is completely evaluated. One way would be to print 
the result between the gettings of time, but for certain tasks, the 
printing may take a substantial amount of time relative to the function you 
want to time, so other dependencies would have to be introduced.
Also, printing values may not be desirable, so you can introduce artificial 
(data) dependencies with seq, pseq and such.
For sorting lists, evaluating the last element or the length forces 
complete evaluation, so [see below]

> 
> Thanks,
> ovidiu
> 
> See the code below:
> ------------------------------------
> module Main where
> import Prelude
> import Data.List
> import Data.Time.Clock
> import System.Random
> 
> quickSort [] = []
> quickSort (x:xs) = (quickSort small) ++ [x] ++ (quickSort big)
>         where
>             small = [p | p <- xs, p <= x]
>             big = [p | p <- xs, p > x]
> 
> randomlist :: Int -> StdGen -> [Int]
> randomlist n = take n . unfoldr (Just . random)
> 
> len = 10 ^ 10
> 
> measure f p = do
>     t1 <- getCurrentTime
>     let sorted = f p
          len = length sorted
> --     t2 <- getCurrentTime
      t2 <- len `seq` getCurrentTime

-- we made the action to get the second time depend on len, so the list has 
to be sorted before the action can be performed.

>     let diff = diffUTCTime t2 t1
>     return diff

However, for timing such functions, wall-clock time is not good, better is 
measuring CPU-time, so use System.CPUTime.getCPUTime instead of 
getCurrentTime (needs some adaption of other code).

> 
> main = do
>     seed  <- newStdGen
>     let rs = randomlist len seed
> 
>     putStrLn $ "Sorting " ++ (show len) ++ " elements..."
> 
>     t <- measure quickSort rs
> 
>     putStrLn $ "Time elapsed: " ++ (show t)





More information about the Beginners mailing list