On Mon, 3 Mar 1997, Choi Kwang Hoon wrote:

> 
> Dear Aik Hui
> 
> I would like to point out one thing. But it might not help you solve
> your wandering. Recently I met a *confusing* program as following. I
> thought the construct `case' always meant forcing evaluation. But it
> seemed not. The reason can be shown by following program.
> 
>   $ cat test.hs
>   module Main where
> 
>   bot x = box x
>   f x = case x of x -> 1
> 
>   main = print (f (bot 1))
> 
>   $ ghc test.hs
>   $ a.out
>   1
>   $
> 
> The result of run meant that `bot 1' was not evaluated. In your example,
> `sum', `x' and `s' will be evaluated when `print' evaluates cascading
> `+'s. That seems to be like this.
> 
>   print (sum [1,2,3] 0)
> 
>   force (delay (3 + delay (2 + (delay (1 + 0)))))
> 
> `force' and `delay' mean usual way to force and to delay evaluation.
> 
> How do you think about `case' ? Is there a wrong understanding for me ?
> If not, the transformation example that you give is always legal without
> using strictness information.
> 
> Regards.
> 
> from Choi, Kwang Hoon
> 
> E-Mail : [EMAIL PROTECTED]
> W W W  : http://compiler.kaist.ac.kr/~khchoi
> 

I think I know what the *main* problem is ... and hence our anomalies
encountered.  Curious about what you wrote, I checked out the report on
Haskell v1.2, in the ACM SigPlan Notices and guess what - amongst the
semantics of case-pattern matching lies the rule: 

     (j) case e0 of { x -> e' } = ( \x -> e ) e0

which is actually equal to saying: let x = e0 in e !!!
And this is the culprit.  And so the statement "case forces evaluation"
should be actually "case forces evaluation except case e0 of {x -> e}".
Of course the latter might have been *implied* in the former when so often
quoted.  Bummer!

What this means for me is that:

        sum (x:xs) s = case (x+s) of
                       s' -> sum xs s'

does not force the evaluation of x+s.  It still builds a thunk! Unless we
do something like:

        sum (x:xs) s = case (x+s) of
                       s'@(I# t#) -> sum xs s'

Which then brings up the question of how does ghc perform strictness
transformation? ... or does it?  Does it do it like the above example?

Regards,

Aik Hui

Reply via email to