Question regarding deepseq (Control.DeepSeq)

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 end <- getCurrentTime putStrLn (show (end `diffUTCTime` start)) putStrLn (show meanOver2) ------------------------------------- My understanding of deepseq was that it evaluates (mean as) completely before continuing, and then the show would not take any time, but 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

On 25 June 2010 10:57, Frank Moore
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 end <- getCurrentTime putStrLn (show (end `diffUTCTime` start)) putStrLn (show meanOver2) -------------------------------------
My understanding of deepseq was that it evaluates (mean as) completely before continuing, and then the show would not take any time, but 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.
It does... but because you don't save the result it doesn't keep the result (you're wanting Common Sub-expression Elimination, which GHC doesn't do). Try this: let meanAs = mean as meanOver2 = meanAs `deepSeq` meanAs / 2 Note that your usage of "fromIntegral" isn't required, as that is automatically done for any integral literal (but if you had 2 in an Int variable then you would need fromIntegral). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Thanks for the reply.
My main is now:
main = do
let as = [1..2e7] :: [Double]
start <- getCurrentTime
let meanAs = mean as
let meanOver2 = meanAs `deepseq` meanAs / 2
end <- getCurrentTime
putStrLn (show (end `diffUTCTime` start))
start <- getCurrentTime
putStrLn (show meanOver2)
end <- getCurrentTime
putStrLn (show (end `diffUTCTime` start))
The time is still spent on the show meanOver2 command :(
Frank
On Thu, Jun 24, 2010 at 9:11 PM, Ivan Miljenovic
On 25 June 2010 10:57, 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 end <- getCurrentTime putStrLn (show (end `diffUTCTime` start)) putStrLn (show meanOver2) -------------------------------------
My understanding of deepseq was that it evaluates (mean as) completely before continuing, and then the show would not take any time, but 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.
It does... but because you don't save the result it doesn't keep the result (you're wanting Common Sub-expression Elimination, which GHC doesn't do).
Try this:
let meanAs = mean as meanOver2 = meanAs `deepSeq` meanAs / 2
Note that your usage of "fromIntegral" isn't required, as that is automatically done for any integral literal (but if you had 2 in an Int variable then you would need fromIntegral).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
-- 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@math.cornell.edu

On 25 June 2010 11:19, Frank Moore
Thanks for the reply.
My main is now:
main = do let as = [1..2e7] :: [Double] start <- getCurrentTime let meanAs = mean as let meanOver2 = meanAs `deepseq` meanAs / 2 end <- getCurrentTime putStrLn (show (end `diffUTCTime` start)) start <- getCurrentTime putStrLn (show meanOver2) end <- getCurrentTime putStrLn (show (end `diffUTCTime` start))
The time is still spent on the show meanOver2 command :(
Well, yes, because the seq'ing is still happening as part of meanOver2. The alternative is to have yet another let statement which is just "let meanAs' = meanAs `deepSeq` meanAs" and then have "meanOver2 = meanAs' / 2". -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

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
participants (4)
-
Daniel Fischer
-
Frank Moore
-
Frank Moore
-
Ivan Miljenovic