
Suppose I've: f = map g I want to know how much time it takes (interpreted mode) to fully process list xs (at least 1e6 elements) with function g. Is it sufficient to execute: *Main> last . f $ xs <result> (x.xx secs, yyyyyyyyyyy bytes) Are there any hidden difficulties involved? Reason is: comparing timings Haskell vs an interpreted language without laziness. thanks =@@i

Hello Arie, Sunday, August 3, 2008, 1:56:43 PM, you wrote: *Main>> last . f $ xs this way you will get only "spin" of list computed, not elements itself. something like sum should be used instead -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Sorry, should go the forum. Ok, thanks. In this case the list consists of 6-digit alphanumeric codes. So doing something like: foldl1 (\x y -> g y) xs will do the job? =@@i Bulat Ziganshin schreef:
Hello Arie,
Sunday, August 3, 2008, 1:56:43 PM, you wrote:
*Main>> last . f $ xs
this way you will get only "spin" of list computed, not elements itself. something like sum should be used instead

Arie,
foldl1 is not strict in its function argument. Using it will cause stack overflows for large lists.
For example:
GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help
Loading package base ... linking ... done.
Prelude> foldl1 (+) [0..1000000]
*** Exception: stack overflow
foldl1' from Data.List is strict in its function argument, and is probably what you want.
See also http://www.haskell.org/haskellwiki/Stack_overflow.
Regards,
Brad Larsen
On Sun, 03 Aug 2008 07:06:40 -0400, Arie Groeneveld
Sorry, should go the forum.
Ok, thanks. In this case the list consists of 6-digit alphanumeric codes. So doing something like:
foldl1 (\x y -> g y) xs
will do the job?
=@@i
Bulat Ziganshin schreef:
Hello Arie,
Sunday, August 3, 2008, 1:56:43 PM, you wrote:
*Main>> last . f $ xs
this way you will get only "spin" of list computed, not elements itself. something like sum should be used instead
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Aug 3, 2008 at 11:06 AM, Arie Groeneveld
Sorry, should go the forum.
Ok, thanks. In this case the list consists of 6-digit alphanumeric codes. So doing something like:
foldl1 (\x y -> g y) xs
No, that still doesn't force elements. Let's say g is (+1): f = \x y -> (+1) y foldl1 f [1,2,3] (1 `f` 2) `f` 3 (+1) 3 4 So we don't need to compute (+1) on any numbers but 3. The most direct way is to force the elements of the list: import Control.Parallel.Strategies seqList rwhnf (map g xs) Note that the notion of "compute" in this example is to WHNF, so for example if g produces lists, it will only evaluate far enough to determine whether the list is a nil or a cons, not the whole thing.
will do the job?
=@@i
Bulat Ziganshin schreef:
Hello Arie,
Sunday, August 3, 2008, 1:56:43 PM, you wrote:
*Main>> last . f $ xs
this way you will get only "spin" of list computed, not elements itself. something like sum should be used instead
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

bradypus:
Suppose I've:
f = map g
I want to know how much time it takes (interpreted mode) to fully process list xs (at least 1e6 elements) with function g. Is it sufficient to execute:
*Main> last . f $ xs <result> (x.xx secs, yyyyyyyyyyy bytes)
Are there any hidden difficulties involved?
Reason is: comparing timings Haskell vs an interpreted language without laziness.
If you care about timings, it's probably a better idea to compile the code (with optimisations on), to get a better idea of what the code would do in a production environment. You could then just time the binary, main = print . sum $ .... ghc -O2 A.hs --make time ./A -- Don

Thanks for all the advises so far. Ok, here's my monster that need to be timed in order to make a comparison: (it's about the control digit of SEDOL numbers http://en.wikipedia.org/wiki/SEDOL ): knip _ [] = Nothing knip k xs = Just (splitAt k xs) ip xs = sum . zipWith (*) xs an = ['0'..'9']++['A'..'Z'] s = take 841 $ cycle "0987654321" f = \xs -> xs ++ [(sna!!).ip [1,3,1,7,3,9]. map (flip (fromJust .) an . findIndex . (==))$xs] Here's my try for timing: *Main> (foldl1 (\x y -> f y) .concat.replicate 1000000 $ unfoldr (knip 6) an) "UVWXYZ7" (1.31 secs, 330291000 bytes) (It's incl. the construction of the test list, as is in the language to compare ) I need the whole list to be evaluated. Interpreted mode IS A MUST :-) BTW I increased stack size thanks Don Stewart schreef:
bradypus:
Suppose I've:
f = map g
I want to know how much time it takes (interpreted mode) to fully process list xs (at least 1e6 elements) with function g. Is it sufficient to execute:
*Main> last . f $ xs <result> (x.xx secs, yyyyyyyyyyy bytes)
Are there any hidden difficulties involved?
Reason is: comparing timings Haskell vs an interpreted language without laziness.
If you care about timings, it's probably a better idea to compile the code (with optimisations on), to get a better idea of what the code would do in a production environment.
You could then just time the binary,
main = print . sum $ ....
ghc -O2 A.hs --make time ./A
-- Don

Acc. to Luke Palmers suggestion this will be the right answer? *Main> seqList rwhnf(map f $ concat.replicate 1000000 $ unfoldr (knip 6) an) () (3.46 secs, 834240864 bytes) or with/without list construction *Main> let ry = concat.replicate 1000000 $ unfoldr (knip 6) an (0.00 secs, 0 bytes) *Main> seqList rwhnf(map f ry) () (4.48 secs, 833668720 bytes) *Main> seqList rwhnf(map f ry) () (3.18 secs, 627071612 bytes) *Main> Arie Groeneveld schreef:
Thanks for all the advises so far.
Ok, here's my monster that need to be timed in order to make a comparison: (it's about the control digit of SEDOL numbers http://en.wikipedia.org/wiki/SEDOL ):
knip _ [] = Nothing knip k xs = Just (splitAt k xs)
ip xs = sum . zipWith (*) xs
an = ['0'..'9']++['A'..'Z']
s = take 841 $ cycle "0987654321" f = \xs -> xs ++ [(sna!!).ip [1,3,1,7,3,9]. map (flip (fromJust .) an . findIndex . (==))$xs]
Here's my try for timing:
*Main> (foldl1 (\x y -> f y) .concat.replicate 1000000 $ unfoldr (knip 6) an) "UVWXYZ7" (1.31 secs, 330291000 bytes)
(It's incl. the construction of the test list, as is in the language to compare )
I need the whole list to be evaluated. Interpreted mode IS A MUST :-)
BTW I increased stack size
thanks
Don Stewart schreef:
bradypus:
Suppose I've:
f = map g
I want to know how much time it takes (interpreted mode) to fully process list xs (at least 1e6 elements) with function g. Is it sufficient to execute:
*Main> last . f $ xs <result> (x.xx secs, yyyyyyyyyyy bytes)
Are there any hidden difficulties involved?
Reason is: comparing timings Haskell vs an interpreted language without laziness.
If you care about timings, it's probably a better idea to compile the code (with optimisations on), to get a better idea of what the code would do in a production environment.
You could then just time the binary,
main = print . sum $ ....
ghc -O2 A.hs --make time ./A
-- Don
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (5)
-
Arie Groeneveld
-
Brad Larsen
-
Bulat Ziganshin
-
Don Stewart
-
Luke Palmer