
Hi (take 4 . map (>0)) (f s t) where s = 2 : t t = 3 : s f = zipWith (-) What would be the order of evaluation for the above code? How would I illustrate the evaluation step-by-step? I'm guessing that the code necessitates lazy evaluation and as such it starts with take then it applies f which in turn applies s and t and zipWith until the first element satisfies the predicate in map and This is repeated 4 times What does the list think? Many thanks, Paul P.S. I'm not done with induction. I'm just letting it rst for a bit.

On 9 May 2008, at 21:52, PR Stanley wrote:
Hi (take 4 . map (>0)) (f s t) where s = 2 : t t = 3 : s f = zipWith (-) What would be the order of evaluation for the above code? How would I illustrate the evaluation step-by-step?
What do you need it for, really? Pure functional programs are not about evaluation order, but about values.

Hi (take 4 . map (>0)) (f s t) where s = 2 : t t = 3 : s f = zipWith (-) What would be the order of evaluation for the above code? How would I illustrate the evaluation step-by-step?
What do you need it for, really? Pure functional programs are not about evaluation order, but about values. Paul: It actually comes from an old test. The question
provides the code, asks for the evaluation of the code and then asks " You should show your working at each stage of the calculation." This isn't a straightforward top-to-bottom calculation that you can carry out in the style demonstrated frequently in the Hutton book. - {apply bla bla } So I'm wondering how else it can be done. Many thanks Paul

Hello,
I'm quite new to Haskell, but this is my understanding... Please correct me
if I am wrong, as there is a good chance I am. ;)
### Begin Code ###
module Main where
main =
putStrLn (show( (take 4 . map (> 0)) (f s t) ))
where
s = 2 : t
t = 3 : s
f = zipWith (-)
{-
- Output:
- *Main> main
- [False,True,False,True]
-}
{-
- (take 4 . map (> 0)) (f s t)
- Evaluates the list for take until 4 elements have been reached.
- Below I replaced (f s t) with the values to make the evaluation
- explicit.
-
- Evaluation:
-
- map (> 0) (zipWith (-) [2 ..] [3 ..])
- False -- 1st element for take.
-
- map (> 0) (zipWith (-) [3 ..] [2 ..])
- True -- 2nd element for take.
-
- map (> 0) (zipWith (-) [2 ..] [3 ..])
- False -- 3rd element for take.
-
- map (> 0) (zipWith (-) [3 ..] [2 ..])
- True -- 4th element for take.
-}
-- EOF.
### End Code ###
Hope that helps.
__
Donnie Jones
On Fri, May 9, 2008 at 1:52 PM, PR Stanley
Hi (take 4 . map (>0)) (f s t) where s = 2 : t t = 3 : s f = zipWith (-) What would be the order of evaluation for the above code? How would I illustrate the evaluation step-by-step? I'm guessing that the code necessitates lazy evaluation and as such it starts with take then it applies f which in turn applies s and t and zipWith until the first element satisfies the predicate in map and This is repeated 4 times What does the list think? Many thanks, Paul P.S. I'm not done with induction. I'm just letting it rst for a bit.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

PR Stanley wrote:
(take 4 . map (>0)) (f s t) where s = 2 : t t = 3 : s f = zipWith (-) What would be the order of evaluation for the above code?
As I understand it Haskell does not specify an order of evaluation and it would therefore be a mistake to write a program which relies on a particular evaluation order. This is the 'unsafe' aspect of unsafePerformIO. It is entirely at the whim of the compiler writer how it is evaluated as long as the eventual answer produced is correct. It would be possible to evaluate it in all sorts of exotic ways, or maybe choose a different one for each day of the week. However, you may be asking how does GHC 6.8.2 evaluate it when compiled at a certain optimisation level so you can make your program run fast or use less memory. In which case there will be a precise answer to your question. Richard.

As I understand it Haskell does not specify an order of evaluation and it would therefore be a mistake to write a program which relies on a particular evaluation order. This is the 'unsafe' aspect of unsafePerformIO.
Hmm... IMHO unsafePerformIO is 'unsafe' because it can lead to type errors in runtime. At least, that seems to be much more dangerous.

Miguel Mitrofanov
As I understand it Haskell does not specify an order of evaluation and it would therefore be a mistake to write a program which relies on a particular evaluation order. This is the 'unsafe' aspect of unsafePerformIO.
Hmm... IMHO unsafePerformIO is 'unsafe' because it can lead to type errors in runtime. At least, that seems to be much more dangerous.
Nope. That'd be unsafeCoerce#, which you never heard of, and I did not mention it in this post. Go away. This is not the function you are looking for. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Oh, you sure? <quote src="http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-IO-Unsafe.html "> It is less well known that unsafePerformIO is not type safe. For example: test :: IORef [a] test = unsafePerformIO $ newIORef [] main = do writeIORef test [42] bang <- readIORef test print (bang :: [Char]) This program will core dump. This problem with polymorphic references is well known in the ML community, and does not arise with normal monadic use of references. There is no easy way to make it impossible once you use unsafePerformIO. Indeed, it is possible to write coerce :: a -> b with the help of unsafePerformIO. So be careful! </quote> That's the reason why "f" has sometimes LESS general type than "\x -> f x" in OCaml. On 10 May 2008, at 01:34, Achim Schneider wrote:
Miguel Mitrofanov
wrote: As I understand it Haskell does not specify an order of evaluation and it would therefore be a mistake to write a program which relies on a particular evaluation order. This is the 'unsafe' aspect of unsafePerformIO.
Hmm... IMHO unsafePerformIO is 'unsafe' because it can lead to type errors in runtime. At least, that seems to be much more dangerous.
Nope. That'd be unsafeCoerce#, which you never heard of, and I did not mention it in this post. Go away. This is not the function you are looking for.
-- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Miguel Mitrofanov
Oh, you sure?
I was, until you wrote that. But then, I am, as I wouldn't use unsafePerformIO together with IORef's, it's giving me the creeps. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

On Fri, May 9, 2008 at 3:46 PM, Achim Schneider
Miguel Mitrofanov
wrote: Oh, you sure?
I was, until you wrote that. But then, I am, as I wouldn't use unsafePerformIO together with IORef's, it's giving me the creeps.
So.. what do you use unsafePerformIO together with? In uses where I'm not just debugging stuff, I _usually_ use it with IORefs, for more complex caching behavior than I can get out of the language. Luke

Hello Luke, Sunday, May 11, 2008, 1:24:04 PM, you wrote:
So.. what do you use unsafePerformIO together with?
when i call function that in general case depends on the execution order (so it's type is ...->IO x), but in my specific case it doesn't matter. typical example is hGetContents on config file, GetSystemInfo just to get number of processors, string processing via C functions -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Miguel Mitrofanov wrote:
As I understand it Haskell does not specify an order of evaluation and it would therefore be a mistake to write a program which relies on a particular evaluation order. This is the 'unsafe' aspect of unsafePerformIO.
Hmm... IMHO unsafePerformIO is 'unsafe' because it can lead to type errors in runtime. At least, that seems to be much more dangerous.
Oh yes, quite right. This and especially the wicked unsafeCoerce seem like great ways to shoot myself in the foot and are strong candidates for inclusion in entries to the International Obfuscated Haskell competition :) http://www.haskell.org/pipermail/haskell/2004-August/014387.html http://www.haskell.org/haskellwiki/Obfuscation Richard.

As others have pointed out, there are many allowed evaluation orders of this
expressions.
But not only that, how it gets evaluated depends on how you are going to use
it. Say that you print it, then you need all 4 elements, but say that it's
oly going to be used as an argument to null, then you will evaluate less
(probably).
Even so, it's instructive to study how the normal order reduction of this
expression would proceed under the assumption that all 4 elements will be
used.
-- Lennart
On Fri, May 9, 2008 at 6:52 PM, PR Stanley
Hi (take 4 . map (>0)) (f s t) where s = 2 : t t = 3 : s f = zipWith (-) What would be the order of evaluation for the above code? How would I illustrate the evaluation step-by-step? I'm guessing that the code necessitates lazy evaluation and as such it starts with take then it applies f which in turn applies s and t and zipWith until the first element satisfies the predicate in map and This is repeated 4 times What does the list think? Many thanks, Paul P.S. I'm not done with induction. I'm just letting it rst for a bit.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lennart Augustsson wrote:
Even so, it's instructive to study how the normal order reduction of this expression would proceed under the assumption that all 4 elements will be used.
I think it's useful to try normal order until weak head normal form. Not all steps are shown. Definitions of take, map, zipWith are taken from the Haskell 98 Report. Whenever you see me expanding a parameter, it is because some function's pattern matching forces it. (take 4 . map (>0)) (f s t) take 4 (map (>0) (f s t)) take 4 (map (>0) (zipWith (-) s t)) take 4 (map (>0) (zipWith (-) (2:t) (3:s))) take 4 (map (>0) ( 2-3 : zipWith (-) t s )) take 4 ( 2-3>0 : map (>0) (zipWith (-) t s) ) 2-3>0 : take (4-1) (map (>0) (zipWith (-) t s))

Hello You may find this paper useful http://research.microsoft.com/~simonpj/Papers/spineless-tagless-gmachine.ps.... It should give you the general feeling of how things are actually executed. It's quite old, some things in GHC have changed, but the overall scheme, I believe, is the same. The competent people will correct me, if I'm wrong. PR Stanley wrote:
Hi (take 4 . map (>0)) (f s t) where s = 2 : t t = 3 : s f = zipWith (-) What would be the order of evaluation for the above code? How would I illustrate the evaluation step-by-step? I'm guessing that the code necessitates lazy evaluation and as such it starts with take then it applies f which in turn applies s and t and zipWith until the first element satisfies the predicate in map and This is repeated 4 times What does the list think? Many thanks, Paul P.S. I'm not done with induction. I'm just letting it rst for a bit.
participants (10)
-
Achim Schneider
-
Albert Y. C. Lai
-
Bulat Ziganshin
-
Daniil Elovkov
-
Donnie Jones
-
Lennart Augustsson
-
Luke Palmer
-
Miguel Mitrofanov
-
PR Stanley
-
Richard Kelsall