[Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread apfelmus

Justin Bailey wrote:

-- Determines if the length of the strings in the list is longer than the given
-- count. If not, amount the list falls short is returned. Otherwise,
-- -1 indicates the prefix list is at least that long. If the count is zero and
-- the list is empty or just null strings, -1 is also returned.



prefixesAtLeast :: Int - [S.ByteString] - Int


While that doesn't help your stack overflow problem, it's not very 
haskellish to return magic numbers. A Maybe type is more appropriate here.



prefixesAtLeast !0 !ss
  | null ss = 0
  | all S.null ss = 0
  | otherwise = -1
prefixesAtLeast !n !ss = prefixesAtLeast' n ss
  where
  prefixesAtLeast' !n ss
| n  0 = -1
| null ss = n
| otherwise =
let (!s : (!rest)) = ss
in
  prefixesAtLeast' (n - (S.length s)) rest


Extracting the head and tail of  ss  with a let statement could lead to 
 a huge unevaluated expression like


  rest = tail (tail (tail (...)))

but the null test are likely to force it. Also note that the case  n = 0 
is quite rare. In any case, I'd write the function as


  lengthExcess :: Int - [S.ByteString] - Maybe Int
  lengthExcess n ss
 | n = 0= Nothing
 | otherwise = case ss of
[] - Just n
(s:ss) - lengthExcess (n - S.length s) ss

Note the that the function name is chosen to mnemonically match the 
result type Maybe Int, i.e. the excess is Just 5 characters or the 
excess is Nothing.


Regards,
apfelmus

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


Re: [Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread Justin Bailey
On 8/17/07, apfelmus [EMAIL PROTECTED] wrote:

 Extracting the head and tail of  ss  with a let statement could lead to
   a huge unevaluated expression like

rest = tail (tail (tail (...)))

Even though they are probably forced, would breaking the head and tail
apart via pattern-matching or a case statement avoid building up that
unevaluated expression?

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


[Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread apfelmus

Justin Bailey wrote:

apfelmus wrote:


Extracting the head and tail of  ss  with a let statement could lead to
  a huge unevaluated expression like

   rest = tail (tail (tail (...)))


Even though they are probably forced, would breaking the head and tail
apart via pattern-matching or a case statement avoid building up that
unevaluated expression?


Yes, absolutely, since pattern matching has to force the scrutinee in 
order to choose the matching case. In contrast, a let statement


  let (x:xs) = expr in ...

simply assumes that  expr  is of the form (x:xs) but does not force it 
and check whether that's really the case. Of course, this may turn out 
as pattern match later on as soon as  x  is demanded but  expr  was 
initially the empty list.


In your case, the test  null ss  forces  ss  and checks whether the 
let-pattern is ok. So, you basically end up doing what a case expression 
would do. In other words, the situation is more they are most likely 
forced than they are probably forced and it's just a matter of 
convenience to choose one over the other.


But there are certain situations where you can check/prove differently 
that the let pattern never fails and where such a lazy pattern is wanted.


Regards,
apfelmus

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


[Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread Joe Buehler
Matthew Brecknell wrote:

 The key point of the example is that foldl itself doesn't need any of
 the intermediate values of the accumulator, so these just build up into
 a deeply-nested unevaluated thunk. When print finally demands an
 integer, the run-time pushes a stack frame for each level of parentheses
 it enters as it tries to evaluate the thunk. Too many parentheses leads
 to a stack overflow. Of course, the solution to the example is to use

What is the point in building this huge thunk if it can't be evaluated
without a stack overflow?  Could the runtime do partial evaluation
to keep the thunk size down or would that cause semantic breakage?

Joe Buehler

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


Re: [Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread Bryan O'Sullivan

Joe Buehler wrote:


What is the point in building this huge thunk if it can't be evaluated
without a stack overflow?


It's not that there's a point to it, it's just the behaviour of foldl. 
  Hence you shouldn't be using foldl.


GHC's strictness analyser can sometimes save you from yourself if you're 
compiling with -O, but it's better to just avoid foldl and use foldr or 
Data.List.foldl' instead.


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