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

Frank Moore frankmoore at math.cornell.edu
Thu Jun 24 22:00:10 EDT 2010


Daniel,

>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).

Thanks for the help, I think I understand now.  This is indeed a
boiled down example.  I have some data that I am trying to compute in
parallel, and I want to control how much evaluation to force.  To do
this, I was trying to use NFData and deepseq, since I thought bang
patterns were a little clunky (but maybe they are less clunky than
forcing evaluations with seq and deepseqs).  Are there best practices
for keeping track of which variables are bound where, when writing a
complex program?

>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)".

Sometimes for me, whnf is not quite enough.  For example, if I have a
newtype P (with type constructor P) that is a for Map M Int.  Is
NFData and deepseq the way to do this, or should I be trying to
implement my own Strategy along the lines of rwhnf in
Control.Parallel.Strategies?

>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.

Thanks for the tip.

Frank

> On Thu, Jun 24, 2010 at 9:38 PM, Daniel Fischer <daniel.is.fischer at web.de> wrote:
>>
>> 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
>>
>
>
>
> --
> Dr. W. Frank Moore
> H. C. Wang Assistant Professor
> Department of Mathematics, Cornell University
> 310 Malott Hall, Ithaca NY 14853-4201, USA
>
> Office: Malott 587, Phone: +1 607 255 4030
> Email: frankmoore at math.cornell.edu



--
Dr. W. Frank Moore
H. C. Wang Assistant Professor
Department of Mathematics, Cornell University
310 Malott Hall, Ithaca NY 14853-4201, USA

Office: Malott 587, Phone: +1 607 255 4030
Email: frankmoore at math.cornell.edu


More information about the Haskell-Cafe mailing list