There was recently some discussion on the subject of un-needed
laziness.
I thank  Jon Mountjoy <[EMAIL PROTECTED]>,  Simon P.Jones 
<[EMAIL PROTECTED]>,  Sietse Achterop <[EMAIL PROTECTED]> 
for their remarks and guidance.

Thus Jon Mountjoy gives a literature reference concerning foldlStrict:

> ... this whole episode about foldl is quite well known, and
> documented in Bird and Wadler for instance.


Still the whole subject of `seq' and strict data fields is not so
clear for me.

And to continue the discussion, let we point it out that 
un-recognized strictless costs NOT a constant expense but maybe,
O(n),O(n^2),O(2^n) ... - depending on that argument data size  n.
(C-coding, "stealing registers" would not help).
This is why a good specializer is needed.


Simon P.Jones  wrote

> * Why did you get different behaviour for sum1/sum2/sum3 etc
> when you split the program over two modules?  I think it's 
> because you didn't put in any type signatures.   When separately
> compiled, ghc generated overloaded functions, which weren't
> even sure that "+" is strict.  When compiled as one, it could
> see that there was only one call to sumx, inline it at the
> call site, and thereby discover which "+" you meant.


For example, for
-----------------------------------------------------------------
module  Sum (sum2)  where

sum2 xs =  sum' 0 xs  where  sum' s []     =  s
                             sum' s (x:xs) =  sum' (s+x) xs
;
module Main (main)  where
import Sum
main =  let  { ns = [1..(2^17)] :: [Int];  s = sum2 ns }  in
                                              print (shows s "\n")
------------------------------------------------------------------
sum2  needs in  ghc-2.08  more than 3M heap, stack.

-O, `INLINE' make  sum2  in-lined.  The compler sees that in `Main' 
sum2 applies to [Int].  So for `Main', it has to create the 
specialization of sum2 taken from Sum.hi.  And this specialization
will make (+) strict. 
Is this all what it has to happen?

Besides,  ghc-2.08  looks like ignoring the `SPECIALIZE' pragma.

In  ghc-0.29  it suffices to set
                             {-# SPECIALIZE sum2 :: [Int] -> Int #-}

in the module Sum to make the needed space 1000 times less.
And  sum2  is not necessarily in-lined. Presizely what it is needed.
Is this the specializer that you are going to have back to
ghc-2.08 ?  

-------------------------------------------------------------------
Another obstacle to optimization related to the strictness is that
`seq' cannot force automatically the "lazy" constructors.
Thus,  foldlStrict  will almost never have the effect because most
data are built with several levels of the lazy constructors.
Consider, for example the above function
                                         sum4 :: Num a => [a] -> a
                                         sum4 =  foldlStrict (+) 0
In many applications,
         (Int,Int), [Int], Polynomial Int, Vector (Polynomial Int),

and so on - they all belong to Num and are built with the nested 
"lazy" costructors.
And it is NOT a solution to make some costructor fields strict.
NEITHER is to define (C x)+(C y) as strict:

  ... => Num C a  where  (C x)+(C y) = let  z= x+y  in  seq z (C z)

Consider for example,
            data  (Integral a) => Ratio a = !a :% !a  deriving (Eq)
of Prelude.
For  a === Int,Integer  it is good.
But suppose we define some good ordering on the polynomials from
                         P = Pol Rational
in the variable  x  and prepare a sensible instance 
                          instance Integral (Pol Rational) where...
- note that qoutRem has sense for P as well.

Hence  Ratio P  is sensible and means the rational function domain.

And looks like for  f :% g :: Ratio P  the strict fields for  f,g  
are NOT good. They are good only sometimes - when `seq' is applied.

Probably, in the most applications most constructor fields still have
to be "lazy"
(or - am I missing something? Please, who could correct? The subject
is rather important).

For the same reason
    ... => Num C a  where  (C x)+(C y) = let  z= x+y  in  seq z (C z)

is not good. 
It may be appropriate for  C Int  but not for  C (Pol Int).
For  f:: Pol Int  has a non-trivial structure, the monomial list, and
such - which under the generic circumstances are good to process 
"lazily".

So, what it remains is to introduce `sseq' which forces all the 
constructors down all the levels.
Is this implementable?

Sorry, if I am missing some crucial details concernig `seq' and the 
data fields.



------------------
Sergey Mechveliani

[EMAIL PROTECTED]





Reply via email to