Re: [Haskell-cafe] Re: Order of Evaluation

2008-05-11 Thread Luke Palmer
On Fri, May 9, 2008 at 3:46 PM, Achim Schneider [EMAIL PROTECTED] wrote:
 Miguel Mitrofanov [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of Evaluation

2008-05-11 Thread Richard Kelsall

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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: Order of Evaluation

2008-05-11 Thread Bulat Ziganshin
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,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of Evaluation

2008-05-10 Thread Daniil Elovkov

Hello

You may find this paper useful

http://research.microsoft.com/~simonpj/Papers/spineless-tagless-gmachine.ps.gz

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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Order of Evaluation

2008-05-09 Thread 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


Re: [Haskell-cafe] Order of Evaluation

2008-05-09 Thread Miguel Mitrofanov


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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of Evaluation

2008-05-09 Thread Donnie Jones
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 [EMAIL PROTECTED] 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.

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of Evaluation

2008-05-09 Thread Richard Kelsall

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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of Evaluation

2008-05-09 Thread 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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of Evaluation

2008-05-09 Thread 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?


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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Order of Evaluation

2008-05-09 Thread Achim Schneider
Miguel Mitrofanov [EMAIL PROTECTED] 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


Re: [Haskell-cafe] Re: Order of Evaluation

2008-05-09 Thread Miguel Mitrofanov

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 [EMAIL PROTECTED] 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Order of Evaluation

2008-05-09 Thread Achim Schneider
Miguel Mitrofanov [EMAIL PROTECTED] 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.

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


Re: [Haskell-cafe] Order of Evaluation

2008-05-09 Thread Albert Y. C. Lai

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-30 : map (0) (zipWith (-) t s) )
2-30 : take (4-1) (map (0) (zipWith (-) t s))

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] List comprehension order of evaluation

2007-10-25 Thread Maurí­cio

Hi,

Today, if I write:

[a:[b] | a-ab , b-12]

I get:

[a1,a2,b1,b2]

Are there any guarantees that I'll never
get [a1,b1,a2,b2] instead, i.e.,
that the first list will always be the
last one to be fully transversed? Even
if I use a different compiler or a
future version of Haskell?

Reading how list comprehensions are
translated in the Haskell report it
seems the answer is yes. Is that
written in stone? Can compilers do
it in their own different way?

Thanks,
Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List comprehension order of evaluation

2007-10-25 Thread Jonathan Cast

On Thu, 2007-10-25 at 19:59 -0200, Maurí­cio wrote:
 Hi,
 
 Today, if I write:
 
 [a:[b] | a-ab , b-12]
 
 I get:
 
 [a1,a2,b1,b2]
 
 Are there any guarantees that I'll never
 get [a1,b1,a2,b2] instead, i.e.,
 that the first list will always be the
 last one to be fully transversed? Even
 if I use a different compiler or a
 future version of Haskell?

 Reading how list comprehensions are
 translated in the Haskell report it
 seems the answer is yes.

Correct.

  Is that
 written in stone?

Yes.  It's a consequence of the MonadPlus law (for [] and other
non-determinism monads)

(xn `mplus` ys) = f = (xn = f) `mplus` (ys = f)

which implies

  [ f x y | x - xn ++ xn', y - ys]
= [ f x y | x - xn, y - ys] ++ [ f x y | x - xn', y - ys]

(This rule plus the monad laws plus the natural transformation law for
return

  map f (return x) = return (f x)

provides a complete calculation system for list comprehensions, btw.
And those laws are all very much set in stone.)

  Can compilers do
 it in their own different way?

No.

jcc

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List comprehension order of evaluation

2007-10-25 Thread Thomas Hartman
If I understand list comprehensions correctly, what you wrote is the same
as

do a - ab;
  b - 12;
  [a:[b]]

which is the same as

ab == \a - do b - 12; [a:[b]]

which is the same as

ab = \a - 12 = \b - [a:[b]]

which is the same as

concat $ map  (  \a - 12 = \b - [a:[b]] ) ab

 enough desugaring for now

Point is, yes it's written in stone.

List comprehensions is just syntactic sugar for monad operations.

Good exercise is to take the above expressions and add parenthesis to make
it easier to understand order of operations. (Still trips me up often
enough).

Thomas.





Maurí­cio [EMAIL PROTECTED]
Sent by: [EMAIL PROTECTED]
10/25/2007 05:59 PM

To
haskell-cafe@haskell.org
cc

Subject
[Haskell-cafe] List comprehension order of evaluation






Hi,

Today, if I write:

[a:[b] | a-ab , b-12]

I get:

[a1,a2,b1,b2]

Are there any guarantees that I'll never
get [a1,b1,a2,b2] instead, i.e.,
that the first list will always be the
last one to be fully transversed? Even
if I use a different compiler or a
future version of Haskell?

Reading how list comprehensions are
translated in the Haskell report it
seems the answer is yes. Is that
written in stone? Can compilers do
it in their own different way?

Thanks,
Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread Derek Elkins
On Thu, 2007-07-26 at 12:04 -0500, Spencer Janssen wrote:
 On Thursday 26 July 2007 11:02:00 Jon Harrop wrote:
  On Thursday 26 July 2007 17:03:31 C.M.Brown wrote:
   Hi Jon,
  
   On Thu, 26 Jul 2007, Jon Harrop wrote:
If you have a boolean-or expression:
   
  a || b
   
will a be evaluated before b in Haskell as it is in other
languages?
  
   Yes, I believe it is defined thus:
  
   True || _= True
   _|| True = True
   _|| _= False
  
   Therefore it is strict in its first argument (it needs to evaluate its
   first argument in order to know which pattern match to take).
 
  Wonderful, thanks guys. The reason I ask is that I'm just looking over the
  Haskell ray tracer and it occurred to me that evaluation order makes an
  asymptotic difference to performance. The reason is simply that one order
  considers near spheres first and culls far spheres whereas the opposite
  order ends up traversing all spheres.
 
  Do foldl and foldr reduce from the first and last elements of a list,
  respectively?
 
 Well, beginning and end are somewhat fuzzy concepts when laziness is 
 involved.  
 Consider this example:
 
  foldr (||) False [a, b, c] === (a || (b || (c || False)))
  foldl (||) False [a, b, c] === (((False || a) || b) || c)
 
 Note that the least-nested application with foldr is (a || ...) -- this means 
 that foldr can potentially yield some result after looking at the first 
 element of the input.  This is especially useful with (||), because it only 
 uses the second argument when the first is False.
 
 In contrast, foldl's least-nested application is (... || c) -- foldl must 
 traverse to the end of the input before giving an answer.  As it is traveling 
 to the end, it will also build up the expression seen in the example.  On the 
 surface, it seems we'll require O(n) heap to build this thunk.  However, if 
 the compiler is sufficiently smart, bits of this expression will be evaluated 
 as you go along, requiring only O(1) memory, rather than O(n).  We can also 
 force this incremental evaluation with Data.List.foldl'.
 
 Now, imagine folding (+) instead of (||).  (+) evaluates both arguments 
 before 
 computing a result.  In that case, foldr will take O(n) stack.  With a 
 sufficiently smart compiler, foldl will only use O(1) memory.
 
 To summarize:
  Use foldr when the operator is lazy (||, , ++, :).
  Use foldl when the operator is strict (*, +).
  Use foldl' when you don't trust the compiler to optimize foldl.

To unsummarize, see http://www.haskell.org/haskellwiki/Stack_overflow

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread Spencer Janssen
On Thursday 26 July 2007 11:02:00 Jon Harrop wrote:
 On Thursday 26 July 2007 17:03:31 C.M.Brown wrote:
  Hi Jon,
 
  On Thu, 26 Jul 2007, Jon Harrop wrote:
   If you have a boolean-or expression:
  
 a || b
  
   will a be evaluated before b in Haskell as it is in other
   languages?
 
  Yes, I believe it is defined thus:
 
  True || _= True
  _|| True = True
  _|| _= False
 
  Therefore it is strict in its first argument (it needs to evaluate its
  first argument in order to know which pattern match to take).

 Wonderful, thanks guys. The reason I ask is that I'm just looking over the
 Haskell ray tracer and it occurred to me that evaluation order makes an
 asymptotic difference to performance. The reason is simply that one order
 considers near spheres first and culls far spheres whereas the opposite
 order ends up traversing all spheres.

 Do foldl and foldr reduce from the first and last elements of a list,
 respectively?

Well, beginning and end are somewhat fuzzy concepts when laziness is involved.  
Consider this example:

 foldr (||) False [a, b, c] === (a || (b || (c || False)))
 foldl (||) False [a, b, c] === (((False || a) || b) || c)

Note that the least-nested application with foldr is (a || ...) -- this means 
that foldr can potentially yield some result after looking at the first 
element of the input.  This is especially useful with (||), because it only 
uses the second argument when the first is False.

In contrast, foldl's least-nested application is (... || c) -- foldl must 
traverse to the end of the input before giving an answer.  As it is traveling 
to the end, it will also build up the expression seen in the example.  On the 
surface, it seems we'll require O(n) heap to build this thunk.  However, if 
the compiler is sufficiently smart, bits of this expression will be evaluated 
as you go along, requiring only O(1) memory, rather than O(n).  We can also 
force this incremental evaluation with Data.List.foldl'.

Now, imagine folding (+) instead of (||).  (+) evaluates both arguments before 
computing a result.  In that case, foldr will take O(n) stack.  With a 
sufficiently smart compiler, foldl will only use O(1) memory.

To summarize:
 Use foldr when the operator is lazy (||, , ++, :).
 Use foldl when the operator is strict (*, +).
 Use foldl' when you don't trust the compiler to optimize foldl.

 Specifically, I'm wondering if this has an effect on the foldr optimization
 that Spencer proposed (that certainly gives a ~50% speedup here) that was
 attributed to avoiding lazy accumulators, IIRC.

Did I propose something?  I recall looking at this code before, but I can't 
remember the details.


Cheers,
Spencer Janssen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Order of evaluation

2007-07-26 Thread apfelmus
Jon Harrop wrote:
 If you have a boolean-or expression:
 
   a || b
 
 will a be evaluated before b in Haskell as it is in other languages?

Yes, although the meaning of the phrase evaluated before is a bit
tricky in a lazy language, so it's probably better to state it with
denotational semantics alone:

   _|_  ||  b  = _|_

Maybe you also want to know whether the second argument is evaluated.
This is answered by

  True  || _|_ = True
  False || _|_ = _|_


Regards,
apfelmus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread Jon Harrop
On Thursday 26 July 2007 17:03:31 C.M.Brown wrote:
 Hi Jon,

 On Thu, 26 Jul 2007, Jon Harrop wrote:
  If you have a boolean-or expression:
 
a || b
 
  will a be evaluated before b in Haskell as it is in other languages?

 Yes, I believe it is defined thus:

 True || _= True
 _|| True = True
 _|| _= False

 Therefore it is strict in its first argument (it needs to evaluate its
 first argument in order to know which pattern match to take).

Wonderful, thanks guys. The reason I ask is that I'm just looking over the 
Haskell ray tracer and it occurred to me that evaluation order makes an 
asymptotic difference to performance. The reason is simply that one order 
considers near spheres first and culls far spheres whereas the opposite order 
ends up traversing all spheres.

Do foldl and foldr reduce from the first and last elements of a list, 
respectively?

Specifically, I'm wondering if this has an effect on the foldr optimization 
that Spencer proposed (that certainly gives a ~50% speedup here) that was 
attributed to avoiding lazy accumulators, IIRC.

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread C.M.Brown
Hi Jon,

On Thu, 26 Jul 2007, Jon Harrop wrote:


 If you have a boolean-or expression:

   a || b

 will a be evaluated before b in Haskell as it is in other languages?


Yes, I believe it is defined thus:

True || _= True
_|| True = True
_|| _= False

Therefore it is strict in its first argument (it needs to evaluate its
first argument in order to know which pattern match to take).

Chris.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Order of evaluation

2007-07-26 Thread Jon Harrop

If you have a boolean-or expression:

  a || b

will a be evaluated before b in Haskell as it is in other languages?

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Order of evaluation

2007-07-26 Thread Jonathan Cast
On Thursday 26 July 2007, Jon Harrop wrote:
 If you have a boolean-or expression:

   a || b

 will a be evaluated before b in Haskell as it is in other languages?

Yes.

The definition of (||) is roughly

True || b = True
False || b = b

Which de-sugars to

(||) = \ a b - case a of
  True - True
  False - b

Which does exactly what you want.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs


pgpHiL6AGRotf.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


order of evaluation ?

2002-02-17 Thread Konst Sushenko
Title: Message



hello,

below is the 
code that i wrote as an excercise for myself (I am still learning 
haskell).

it 
implements a straighforward way to simplify boolean expressions, and should be 
self-explanatory.

my question 
is, if i have an expression such as ((Const False) :: subexp), will 
subexp be reduced first (according to the definition 
'simplify (x :: y) = simplify' ((simplify x) :: (simplify y))') 
or will laziness do the right thing, and emit (Const False) without looking into 
exp?

i think the 
latter, but would appreciate a word from an expert.

thanks
konst

PS: any 
coding suggestions, etc. are also welcome




infixr 3 ::infixr 2 :|:

data Exp = Const 
Bool | Sym 
String | Not 
Exp | Exp :: 
Exp | Exp :|: 
Exp

instance Eq Exp where 
(Const x) == (Const y) = x==y (Sym x) == (Sym 
y) = x==y (Not x) == (Not 
y) = x==y (x :: y) == (u :: v) = 
x==u  y==v || x==v  y==u (x :|: y) == 
(u :|: v) = x==u  y==v || x==v  y==u 
_ == 
_ = False

simplify (x :: y) = simplify' 
((simplify x) :: (simplify y))simplify (x :|: y) = simplify' ((simplify 
x) :|: (simplify y))simplify (Not x) = simplify' (Not (simplify 
x))simplify x = 
x

simplify' (Not (Const 
True)) = Const Falsesimplify' (Not (Const 
False)) = Const True

simplify' (Not (Not 
x)) = x

simplify' ((Not x) :: y) | x==y = 
Const Falsesimplify' (x :: (Not y)) | x==y = Const Falsesimplify' 
((Not x) :|: y) | x==y = Const Truesimplify' (x :|: (Not y)) | x==y = Const 
True

simplify' ((Const False) :: _) = 
Const Falsesimplify' (_ :: (Const False)) = Const 
Falsesimplify' ((Const True) :: x) = xsimplify' (x 
:: (Const True)) = x

simplify' ((Const True) :|: _) 
= Const Truesimplify' (_ :|: (Const True)) = Const 
Truesimplify' ((Const False) :|: x) = xsimplify' (x :|: (Const 
False)) = x

simplify' (x :: y) | 
x==y = xsimplify' (x :|: y) | 
x==y = x

simplify' 
x 
= x



re: order of evaluation ?

2002-02-17 Thread Bernard James POPE

konst writes:

 my question is, if i have an expression such as ((Const False) ::
 subexp), will subexp be reduced first (according to the definition
 'simplify (x :: y) = simplify' ((simplify x) :: (simplify y))') or
 will laziness do the right thing, and emit (Const False) without looking
 into exp?
 i think the latter, but would appreciate a word from an expert.

Hi Konst,

There is an easy way to check, try making subexp an erroneous 
computation.  There is such a value in the Prelude, it is called
undefined:

   simplify ((Const False) :: undefined)

If this bombs then you know that simplify wasn't as lazy as you thought, since
it must have tried to evaluated 'undefined'. On my version of hugs I get:

   Program error: {undefined}
 
The important bits of code are: 
 
   simplify (x :: y) = simplify' ((simplify x) :: (simplify y))
 
   simplify' (x :: (Not y)) | x==y = Const False

   simplify' ((Const False) :: _)  = Const False

The order of the equations for simplify' is important. Effectively pattern
matching causes evaluation in Haskell. To determine whether the first
equation for simplify' should be used, the second argument of :: must
be evaluated to what is called weak head normal form (whnf). This means
that the outermost constructor of that argument must be computed. 
Hence the computation with undefined fails in this case.

However, what happens if you swap the order of the equations for simplify'?
Doing so will give you the lazyness that you originally expected (for this
particular example).

Swapping the order of equations is not a silver bullet however, and you must
be very careful with how you order them.

One of the best places to learn about the operational semantics of languages
like Haskell is The Implementation of Functional Programming Languages
by Simon Peyton Jones. I think it is out of print, but you may find copies
in your local uni library if you are lucky. 

For this particular example, pay close attention to the Pattern Matching
Compiler section, which I think was done by Wadler.

Cheers,
Bernie.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe