[Haskell-cafe] Question regarding deepseq (Control.DeepSeq)

Daniel Fischer daniel.is.fischer at web.de
Thu Jun 24 21:38:43 EDT 2010


On Friday 25 June 2010 02:57:31, Frank Moore wrote:
> Hello Haskellers,
>
> I am new to programming in Haskell and I am having trouble understanding
> exactly when statements become evaluated.  My goal is to try and measure
> how long a computation takes without having to use a show function.  The
> code I am trying to use is below (taken in part from RWH chapter 25)
>
> ----------------------------------
> import Data.List (foldl')
> import Data.Time.Clock (diffUTCTime, getCurrentTime)
> import Control.DeepSeq (deepseq)
>
> mean :: [Double] -> Double
> mean xs = s / fromIntegral n where
>     (n,s) = foldl' k (0,0) xs
>     k (n,s) x = n `seq` s `seq` (n+1,s+x)
>
> main = do
>   let as = [1..1e7] :: [Double]
>   start <- getCurrentTime
>   let meanOver2 = deepseq (mean as) `seq` (mean as) / fromIntegral 2

This means *when meanOver2 is evaluated*, then evaluate (mean as).
Binding it in a let is lazy, so it won't be evaluated until it's needed 
(for printing in this case).
Also note that (mean as) is a Double, so deepseq is just seq in this case 
(but I suppose this is just a boiled down example and you also want to time 
computations with results where deepseq does strictly more than seq).

There are two standard ways to achieve what you want,

1.
    let meanOver2 = ...
    end <- meanOver2 `deepseq` getCurrentTime

2. put {-# LANGUAGE BangPatterns #-} at the top of the file and write

    let !meanOver2 = ...
    end <- getCurrentTime

The bang on meanOver2 means "evaluate this expression now (to weak head 
normal form, i.e. to the outermost constructor)".

>   end <- getCurrentTime
>   putStrLn (show (end `diffUTCTime` start))
>   putStrLn (show meanOver2)
> -------------------------------------

Another thing, for timing computations, wall-clock time is not appropriate, 
better use

System.CPUTime.getCPUTime

to get only the CPU-time the process took, and not also what your browser 
or whatever used in the meantime. 

>
> My understanding of deepseq was that it evaluates (mean as) completely
> before continuing, and then the show would not take any time, but

No, it evaluates (mean as) completely *when meanOver2 is demanded*, not 
before.

> instead all the time is spent in the show meanOver2 function.  I feel
> like I am missing something fundamental here.  Any suggestions?  Thanks
> for your help.
>
> Frank



More information about the Haskell-Cafe mailing list