Stack space overflow: using strict accumulator still fails

Hello, Have a stack overflow but cannot see why (read up on [1], may be missing something trivial). Once again using the http://nlpwp.org/ book code. If I call the following function, it blows its top: scoreRule :: TransformationRule -> Z.Zipper (Tag, Tag) -> Int scoreRule r z = nCorrect - nIncorrect where (nCorrect, nIncorrect) = scoreRule_ r z scoreRule_ :: TransformationRule -> Z.Zipper (Tag, Tag) -> (Int, Int) scoreRule_ r = Z.foldlz' (scoreElem r) (0, 0) where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect + 1, nIncorrect) else (nCorrect, nIncorrect + 1) Nothing -> s where (correct, _) = Z.cursor z however I see that the eager version of foldlz is being used. I also though that maybe ruleApplication my not be executing immediately. But I cannot see why (added definition below for reference). Can anyone point out why this is not strict? TIA, Hugo F. [1] http://www.haskell.org/haskellwiki/Stack_overflow ruleApplication :: TransformationRule -> Z.Zipper (Tag, Tag) -> Maybe Tag ruleApplication (NextTagRule (Replacement old new) next) z = do (_, proposed) <- Z.safeCursor z (_, nextProposed) <- rightCursor z if proposed == old && nextProposed == next then Just new else Nothing ruleApplication (PrevTagRule (Replacement old new) prev) z = do (_, proposed) <- Z.safeCursor z (_, prevProposed) <- leftCursor z if proposed == old && prevProposed == prev then Just new else Nothing ruleApplication (SurroundTagRule (Replacement old new) prev next) z = do (_, proposed) <- Z.safeCursor z (_, nextProposed) <- rightCursor z (_, prevProposed) <- leftCursor z if proposed == old && prevProposed == prev && nextProposed == next then Just new else Nothing

On Thursday 27 October 2011, 12:45:11, Hugo Ferreira wrote:
Hello,
Have a stack overflow but cannot see why (read up on [1], may be missing something trivial). Once again using the http://nlpwp.org/ book code. If I call the following function, it blows its top:
scoreRule :: TransformationRule -> Z.Zipper (Tag, Tag) -> Int scoreRule r z = nCorrect - nIncorrect where (nCorrect, nIncorrect) = scoreRule_ r z
scoreRule_ :: TransformationRule -> Z.Zipper (Tag, Tag) -> (Int, Int) scoreRule_ r = Z.foldlz' (scoreElem r) (0, 0) where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect + 1, nIncorrect) else (nCorrect, nIncorrect + 1) Nothing -> s where (correct, _) = Z.cursor z
however I see that the eager version of foldlz is being used. I also though that maybe ruleApplication my not be executing immediately. But I cannot see why (added definition below for reference).
Can anyone point out why this is not strict?
The additions (increments) are never forced before the final subtraction, so from scoreRule_ you will probably get a pair of thunks (((...(0+1)+1...)+1), ((...(0+1)+1...)+1)), since the forcing in the fold can only use seq, to force *the outermost constructor* of the intermediate results, in this case, the outermost constructor is the pair constructor - (,) - and the components are left unforced. To force the increments without (big) delay, you can - use a custom strict pair type instead of ordinary pairs data P = P !Int !Int -- {-# UNPACK #-} the fields for extra goodness so that forcing the outermost constructor automatically forces the components. - make the scoreElem function strict in the components of the accumulator s, with ghc {-# LANGUAGE BangPatterns #-}, scoreElem r !s@(!nCorrect, !nIncorrect) z = ... that way you will never get bigger thungks than (n+1) in the components - force the updated count as it is constructed, if tag == correct then let newCorrect = nCorrect+1 in newCorrect `seq` (newCorrect, nIncorrect) else let newIncorrect = ... The important thing to be aware of is that seq only forces the outermost level of a value. If the value is a structure with more levels, it doesn't prevent the building of huge thunks in the inner levels at all. You then have to take care of that yourself, by using a datatype with the desired strictness or, in the case of folds and similar, providing a comination function with the desired strictness. HTH, Daniel

Daniel, Appreciate the comprehensive and clear explanation. I see it has something to do with seq and weak head normal form explanation in [1]. I will stick to the last solution. Thanks, Hugo F On 10/27/2011 12:41 PM, Daniel Fischer wrote:
On Thursday 27 October 2011, 12:45:11, Hugo Ferreira wrote:
Hello,
Have a stack overflow but cannot see why (read up on [1], may be missing something trivial). Once again using the http://nlpwp.org/ book code. If I call the following function, it blows its top:
scoreRule :: TransformationRule -> Z.Zipper (Tag, Tag) -> Int scoreRule r z = nCorrect - nIncorrect where (nCorrect, nIncorrect) = scoreRule_ r z
scoreRule_ :: TransformationRule -> Z.Zipper (Tag, Tag) -> (Int, Int) scoreRule_ r = Z.foldlz' (scoreElem r) (0, 0) where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect + 1, nIncorrect) else (nCorrect, nIncorrect + 1) Nothing -> s where (correct, _) = Z.cursor z
however I see that the eager version of foldlz is being used. I also though that maybe ruleApplication my not be executing immediately. But I cannot see why (added definition below for reference).
Can anyone point out why this is not strict?
The additions (increments) are never forced before the final subtraction, so from scoreRule_ you will probably get a pair of thunks (((...(0+1)+1...)+1), ((...(0+1)+1...)+1)), since the forcing in the fold can only use seq, to force *the outermost constructor* of the intermediate results, in this case, the outermost constructor is the pair constructor - (,) - and the components are left unforced.
To force the increments without (big) delay, you can - use a custom strict pair type instead of ordinary pairs
data P = P !Int !Int -- {-# UNPACK #-} the fields for extra goodness
so that forcing the outermost constructor automatically forces the components.
- make the scoreElem function strict in the components of the accumulator s, with ghc {-# LANGUAGE BangPatterns #-},
scoreElem r !s@(!nCorrect, !nIncorrect) z = ...
that way you will never get bigger thungks than (n+1) in the components
- force the updated count as it is constructed,
if tag == correct then let newCorrect = nCorrect+1 in newCorrect `seq` (newCorrect, nIncorrect) else let newIncorrect = ...
The important thing to be aware of is that seq only forces the outermost level of a value. If the value is a structure with more levels, it doesn't prevent the building of huge thunks in the inner levels at all. You then have to take care of that yourself, by using a datatype with the desired strictness or, in the case of folds and similar, providing a comination function with the desired strictness.
HTH, Daniel

Hello, After trying the suggestions, I still cannot execute the code. I have tried: scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r !s@(!nCorrect, !nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect + 1) Nothing -> s where (correct, _) = Z.cursor z and scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs nIncorrect) where (correct, _) = Z.cursor z nCorrect = nCorrect + 1 nIncorrect = nIncorrect + 1 where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then let nCorrect = nCorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) else let nIncorrect = nIncorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) Nothing -> s where (correct, _) = Z.cursor z In an attempt to figure out the problem I also tried: scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r !s@(!nCorrect, !nIncorrect) z = (nCorrect, nIncorrect) where (correct, _) = Z.cursor z nCorrect = nCorrect + 1 nIncorrect = nIncorrect + 1 Strangely enough GHC complains that correct, nCorrect and nIncorrect are not used. Why is this so for nCorrect and nIncorrect? Why won't the above also execute in a strict manner? Does anyone have any ideas why I still get stack-overflow? TIA, Hugo F. On 10/27/2011 12:41 PM, Daniel Fischer wrote:
On Thursday 27 October 2011, 12:45:11, Hugo Ferreira wrote:
Hello,
Have a stack overflow but cannot see why (read up on [1], may be missing something trivial). Once again using the http://nlpwp.org/ book code. If I call the following function, it blows its top:
scoreRule :: TransformationRule -> Z.Zipper (Tag, Tag) -> Int scoreRule r z = nCorrect - nIncorrect where (nCorrect, nIncorrect) = scoreRule_ r z
scoreRule_ :: TransformationRule -> Z.Zipper (Tag, Tag) -> (Int, Int) scoreRule_ r = Z.foldlz' (scoreElem r) (0, 0) where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect + 1, nIncorrect) else (nCorrect, nIncorrect + 1) Nothing -> s where (correct, _) = Z.cursor z
however I see that the eager version of foldlz is being used. I also though that maybe ruleApplication my not be executing immediately. But I cannot see why (added definition below for reference).
Can anyone point out why this is not strict?
The additions (increments) are never forced before the final subtraction, so from scoreRule_ you will probably get a pair of thunks (((...(0+1)+1...)+1), ((...(0+1)+1...)+1)), since the forcing in the fold can only use seq, to force *the outermost constructor* of the intermediate results, in this case, the outermost constructor is the pair constructor - (,) - and the components are left unforced.
To force the increments without (big) delay, you can - use a custom strict pair type instead of ordinary pairs
data P = P !Int !Int -- {-# UNPACK #-} the fields for extra goodness
so that forcing the outermost constructor automatically forces the components.
- make the scoreElem function strict in the components of the accumulator s, with ghc {-# LANGUAGE BangPatterns #-},
scoreElem r !s@(!nCorrect, !nIncorrect) z = ...
that way you will never get bigger thungks than (n+1) in the components
- force the updated count as it is constructed,
if tag == correct then let newCorrect = nCorrect+1 in newCorrect `seq` (newCorrect, nIncorrect) else let newIncorrect = ...
The important thing to be aware of is that seq only forces the outermost level of a value. If the value is a structure with more levels, it doesn't prevent the building of huge thunks in the inner levels at all. You then have to take care of that yourself, by using a datatype with the desired strictness or, in the case of folds and similar, providing a comination function with the desired strictness.
HTH, Daniel

My apologies, the 2nd function should be: scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then let nCorrect = nCorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) else let nIncorrect = nIncorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) Nothing -> s where (correct, _) = Z.cursor z R, Hugo F. On 10/27/2011 02:22 PM, Hugo Ferreira wrote:
Hello,
After trying the suggestions, I still cannot execute the code. I have tried:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r !s@(!nCorrect, !nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect + 1) Nothing -> s where (correct, _) = Z.cursor z
and
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs nIncorrect) where (correct, _) = Z.cursor z nCorrect = nCorrect + 1 nIncorrect = nIncorrect + 1 where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then let nCorrect = nCorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) else let nIncorrect = nIncorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) Nothing -> s where (correct, _) = Z.cursor z
In an attempt to figure out the problem I also tried:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r !s@(!nCorrect, !nIncorrect) z = (nCorrect, nIncorrect) where (correct, _) = Z.cursor z nCorrect = nCorrect + 1 nIncorrect = nIncorrect + 1
Strangely enough GHC complains that correct, nCorrect and nIncorrect are not used. Why is this so for nCorrect and nIncorrect? Why won't the above also execute in a strict manner?
Does anyone have any ideas why I still get stack-overflow?
TIA, Hugo F.
On 10/27/2011 12:41 PM, Daniel Fischer wrote:
On Thursday 27 October 2011, 12:45:11, Hugo Ferreira wrote:
Hello,
Have a stack overflow but cannot see why (read up on [1], may be missing something trivial). Once again using the http://nlpwp.org/ book code. If I call the following function, it blows its top:
scoreRule :: TransformationRule -> Z.Zipper (Tag, Tag) -> Int scoreRule r z = nCorrect - nIncorrect where (nCorrect, nIncorrect) = scoreRule_ r z
scoreRule_ :: TransformationRule -> Z.Zipper (Tag, Tag) -> (Int, Int) scoreRule_ r = Z.foldlz' (scoreElem r) (0, 0) where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect + 1, nIncorrect) else (nCorrect, nIncorrect + 1) Nothing -> s where (correct, _) = Z.cursor z
however I see that the eager version of foldlz is being used. I also though that maybe ruleApplication my not be executing immediately. But I cannot see why (added definition below for reference).
Can anyone point out why this is not strict?
The additions (increments) are never forced before the final subtraction, so from scoreRule_ you will probably get a pair of thunks (((...(0+1)+1...)+1), ((...(0+1)+1...)+1)), since the forcing in the fold can only use seq, to force *the outermost constructor* of the intermediate results, in this case, the outermost constructor is the pair constructor - (,) - and the components are left unforced.
To force the increments without (big) delay, you can - use a custom strict pair type instead of ordinary pairs
data P = P !Int !Int -- {-# UNPACK #-} the fields for extra goodness
so that forcing the outermost constructor automatically forces the components.
- make the scoreElem function strict in the components of the accumulator s, with ghc {-# LANGUAGE BangPatterns #-},
scoreElem r !s@(!nCorrect, !nIncorrect) z = ...
that way you will never get bigger thungks than (n+1) in the components
- force the updated count as it is constructed,
if tag == correct then let newCorrect = nCorrect+1 in newCorrect `seq` (newCorrect, nIncorrect) else let newIncorrect = ...
The important thing to be aware of is that seq only forces the outermost level of a value. If the value is a structure with more levels, it doesn't prevent the building of huge thunks in the inner levels at all. You then have to take care of that yourself, by using a datatype with the desired strictness or, in the case of folds and similar, providing a comination function with the desired strictness.
HTH, Daniel
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thursday 27 October 2011, 15:44:34, Hugo Ferreira wrote:
My apologies, the 2nd function should be:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then let nCorrect = nCorrect + 1 in
This is a cyclic definition. The nCorrect on the right hand side is not the nCorrect from the function parameter but the nCorrect from the left hand side of the definition, so you have a nonterminating value here. You need to introduce a new name, let newCorrect = nCorrect + 1 in newCorrect `seq` (newCorrect, nIncorrect) (since nIncorrect isn't changed, we don't need to use seq on that).
nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) else let nIncorrect = nIncorrect + 1 in
Same problem here.
nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) Nothing -> s where (correct, _) = Z.cursor z
R, Hugo F.
On 10/27/2011 02:22 PM, Hugo Ferreira wrote:
Hello,
After trying the suggestions, I still cannot execute the code. I have tried:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r !s@(!nCorrect, !nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect + 1) Nothing -> s where (correct, _) = Z.cursor z
That should run, what's the problem here? Perhaps the bangs should be placed s@(!(InCorrect, !nIncorrect)), I'm not sure how ghc treats bang patterns exactly atm.
and
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs nIncorrect) where (correct, _) = Z.cursor z nCorrect = nCorrect + 1 nIncorrect = nIncorrect + 1
Again cyclic definitions.
where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then let nCorrect = nCorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) else let nIncorrect = nIncorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) Nothing -> s where (correct, _) = Z.cursor z
Here too.
In an attempt to figure out the problem I also tried:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r !s@(!nCorrect, !nIncorrect) z = (nCorrect, nIncorrect) where (correct, _) = Z.cursor z nCorrect = nCorrect + 1 nIncorrect = nIncorrect + 1
Strangely enough GHC complains that correct, nCorrect and nIncorrect are not used.
With -Wall or -fwarn-name-shadowing it should also complain about the shadowing of nCorrect and nIncorrect.
Why is this so for nCorrect and nIncorrect? Why won't the above also execute in a strict manner?
Does anyone have any ideas why I still get stack-overflow?
TIA, Hugo F.

Daniel, On 10/27/2011 03:26 PM, Daniel Fischer wrote:
On Thursday 27 October 2011, 15:44:34, Hugo Ferreira wrote:
My apologies, the 2nd function should be:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then let nCorrect = nCorrect + 1 in
This is a cyclic definition. The nCorrect on the right hand side is not the nCorrect from the function parameter but the nCorrect from the left hand side of the definition, so you have a nonterminating value here. You need to introduce a new name,
let newCorrect = nCorrect + 1 in newCorrect `seq` (newCorrect, nIncorrect)
That was unexpected. I assumed a new variable with the same name.
(since nIncorrect isn't changed, we don't need to use seq on that).
Ok. Understood. But something seems to be wrong here. If I do: scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r s z = let (nCorrect, nIncorrect) = s in case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1) Nothing -> (nCorrect, nIncorrect) where c = Z.cursor z (correct,_) = c it works correctly, however this does not work: scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r (!nCorrect, !nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1) Nothing -> (nCorrect, nIncorrect) where c = Z.cursor z (correct,_) = c I have been staring at this for some time now, but cannot understand why it does not work. Any ideas? Regards, Hugo F.
nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) else let nIncorrect = nIncorrect + 1 in
Same problem here.
nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) Nothing -> s where (correct, _) = Z.cursor z
R, Hugo F.
On 10/27/2011 02:22 PM, Hugo Ferreira wrote:
Hello,
After trying the suggestions, I still cannot execute the code. I have tried:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r !s@(!nCorrect, !nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect + 1) Nothing -> s where (correct, _) = Z.cursor z
That should run, what's the problem here? Perhaps the bangs should be placed s@(!(InCorrect, !nIncorrect)), I'm not sure how ghc treats bang patterns exactly atm.
and
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs nIncorrect) where (correct, _) = Z.cursor z nCorrect = nCorrect + 1 nIncorrect = nIncorrect + 1
Again cyclic definitions.
where scoreElem r s@(nCorrect, nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then let nCorrect = nCorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) else let nIncorrect = nIncorrect + 1 in nCorrect `seq` nIncorrect `seq` (nCorrect, nIncorrect) Nothing -> s where (correct, _) = Z.cursor z
Here too.
In an attempt to figure out the problem I also tried:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r !s@(!nCorrect, !nIncorrect) z = (nCorrect, nIncorrect) where (correct, _) = Z.cursor z nCorrect = nCorrect + 1 nIncorrect = nIncorrect + 1
Strangely enough GHC complains that correct, nCorrect and nIncorrect are not used.
With -Wall or -fwarn-name-shadowing it should also complain about the shadowing of nCorrect and nIncorrect.
Why is this so for nCorrect and nIncorrect? Why won't the above also execute in a strict manner?
Does anyone have any ideas why I still get stack-overflow?
TIA, Hugo F.

On Thursday 27 October 2011, 17:02:46, Hugo Ferreira wrote:
But something seems to be wrong here. If I do:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r s z = let (nCorrect, nIncorrect) = s in case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1) Nothing -> (nCorrect, nIncorrect) where c = Z.cursor z (correct,_) = c
it works correctly, however this does not work:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r (!nCorrect, !nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1) Nothing -> (nCorrect, nIncorrect) where c = Z.cursor z (correct,_) = c
I have been staring at this for some time now, but cannot understand why it does not work. Any ideas?
No. Looks perfectly okay (well, the indentation is wrong, but that's the same for the working version above and is probably due to the mail client). Can you post the complete source for diagnosis?

Hello, Apologies for the late reply but I had to prep the code. On 10/28/2011 09:43 AM, Daniel Fischer wrote:
On Thursday 27 October 2011, 17:02:46, Hugo Ferreira wrote:
But something seems to be wrong here. If I do:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r s z = let (nCorrect, nIncorrect) = s in case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1) Nothing -> (nCorrect, nIncorrect) where c = Z.cursor z (correct,_) = c
it works correctly, however this does not work:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs where scoreElem r (!nCorrect, !nIncorrect) z = case ruleApplication r z of Just tag -> if tag == correct then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1) Nothing -> (nCorrect, nIncorrect) where c = Z.cursor z (correct,_) = c
I have been staring at this for some time now, but cannot understand why it does not work. Any ideas?
No. Looks perfectly okay (well, the indentation is wrong, but that's the same for the working version above and is probably due to the mail client).
Not really. That's pretty much the indentation I am using. I actually had additional trace statements. Can you please tell me what's wrong?
Can you post the complete source for diagnosis?
I have attached the code + cabal files. I think that is all that is required. I am not sending the training data because it is too large (+7 Mega bytes). That is available at http://nlpwp.org/nlpwp-data.zip TIA, Hugo F.

On Monday 31 October 2011, 10:36:53, Hugo Ferreira wrote:
Hello,
Apologies for the late reply but I had to prep the code.
On 10/28/2011 09:43 AM, Daniel Fischer wrote:
On Thursday 27 October 2011, 17:02:46, Hugo Ferreira wrote:
But something seems to be wrong here. If I do:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs
where scoreElem r s z =
let (nCorrect, nIncorrect) = s in case ruleApplication r z of
Just tag -> if tag == correct
then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1)
Nothing -> (nCorrect, nIncorrect)
where c = Z.cursor z
(correct,_) = c
it works correctly, however this does not work:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs
where scoreElem r (!nCorrect, !nIncorrect) z =
case ruleApplication r z of
Just tag -> if tag == correct
then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1)
Nothing -> (nCorrect, nIncorrect)
where c = Z.cursor z
(correct,_) = c
I have been staring at this for some time now, but cannot understand why it does not work. Any ideas?
No. Looks perfectly okay (well, the indentation is wrong, but that's the same for the working version above and is probably due to the mail client).
Not really. That's pretty much the indentation I am using. I actually had additional trace statements. Can you please tell me what's wrong?
You're not having the 'where's on their own lines ;) Seriously: I hadn't bothered to view it in fixed-width font and underestimated how much my mail client compresses contiguous whitespace.
Can you post the complete source for diagnosis?
I have attached the code + cabal files. I think that is all that is required. I am not sending the training data because it is too large (+7 Mega bytes). That is available at http://nlpwp.org/nlpwp-data.zip
Been a bugger to hunt down, but I finally found it. The culprit is *drumroll, ba-dum tish*: a one-character typo in Data.List.Zipper. foldlz' isn't. The recursive call is to foldlz, not foldlz'.

On 10/31/2011 09:14 PM, Daniel Fischer wrote:
On Monday 31 October 2011, 10:36:53, Hugo Ferreira wrote:
Hello,
Apologies for the late reply but I had to prep the code.
On 10/28/2011 09:43 AM, Daniel Fischer wrote:
On Thursday 27 October 2011, 17:02:46, Hugo Ferreira wrote:
But something seems to be wrong here. If I do:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs
where scoreElem r s z =
let (nCorrect, nIncorrect) = s in case ruleApplication r z of
Just tag -> if tag == correct
then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1)
Nothing -> (nCorrect, nIncorrect)
where c = Z.cursor z
(correct,_) = c
it works correctly, however this does not work:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs
where scoreElem r (!nCorrect, !nIncorrect) z =
case ruleApplication r z of
Just tag -> if tag == correct
then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1)
Nothing -> (nCorrect, nIncorrect)
where c = Z.cursor z
(correct,_) = c
I have been staring at this for some time now, but cannot understand why it does not work. Any ideas?
No. Looks perfectly okay (well, the indentation is wrong, but that's the same for the working version above and is probably due to the mail client).
Not really. That's pretty much the indentation I am using. I actually had additional trace statements. Can you please tell me what's wrong?
You're not having the 'where's on their own lines ;)
You mean, I have to use something like: where (correct,_) = Z.cursor z instead of where (correct,_) = Z.cursor z I googled the rules and found http://en.wikibooks.org/wiki/Haskell/Indentation. Doesn't seem to be a requirement.
Seriously: I hadn't bothered to view it in fixed-width font and underestimated how much my mail client compresses contiguous whitespace.
Can you post the complete source for diagnosis?
I have attached the code + cabal files. I think that is all that is required. I am not sending the training data because it is too large (+7 Mega bytes). That is available at http://nlpwp.org/nlpwp-data.zip
Been a bugger to hunt down, but I finally found it. The culprit is *drumroll, ba-dum tish*: a one-character typo in Data.List.Zipper. foldlz' isn't. The recursive call is to foldlz, not foldlz'.
Now I am baffled B-( The package docs state: foldlz' is foldlz with a strict accumulator Why would/should one not use the strict version here? What do you mean when you say "recursive call"? TIA, Hugo F.

On Monday 31 October 2011, 23:12:03, Hugo Ferreira wrote:
You mean, I have to use something like:
where (correct,_) = Z.cursor z
instead of
where (correct,_) = Z.cursor z
Yes.
I googled the rules and found http://en.wikibooks.org/wiki/Haskell/Indentation. Doesn't seem to be a requirement.
Hence the ";)".
Been a bugger to hunt down, but I finally found it. The culprit is *drumroll, ba-dum tish*: a one-character typo in Data.List.Zipper. foldlz' isn't. The recursive call is to foldlz, not foldlz'.
Now I am baffled B-(
The package docs state: foldlz' is foldlz with a strict accumulator
Why would/should one not use the strict version here?
Because there's a typo in the implementation (notified the maintainer).
What do you mean when you say "recursive call"?
Let's look at lists first. The specification in the standard is foldl f z [] = z foldl f z (x:xs) = foldl f (f z x) xs ^^^^^ recursive call to foldl Very similar for the list zipper, we have foldlz :: (b -> Zipper a -> b) -> b -> Zipper a -> b foldlz f x z | endp z = x | otherwise = foldlz f (f x z) (right z) ^^^^^^ And for foldlz', the intention was foldlz' :: (b -> Zipper a -> b) -> b -> Zipper a -> b foldlz' f x z | endp z = x | otherwise = acc `seq` foldlz' f acc (right z) where acc = f x z but in the otherwise branch, the ' has been omitted, so instead of recursively calling itself with the new accumulator, it calls foldlz.

On 10/31/2011 10:31 PM, Daniel Fischer wrote:
On Monday 31 October 2011, 23:12:03, Hugo Ferreira wrote:
You mean, I have to use something like:
where (correct,_) = Z.cursor z
instead of
where (correct,_) = Z.cursor z
Yes.
I googled the rules and found http://en.wikibooks.org/wiki/Haskell/Indentation. Doesn't seem to be a requirement.
Hence the ";)".
I see. B-)
Been a bugger to hunt down, but I finally found it. The culprit is *drumroll, ba-dum tish*: a one-character typo in Data.List.Zipper. foldlz' isn't. The recursive call is to foldlz, not foldlz'.
Now I am baffled B-(
The package docs state: foldlz' is foldlz with a strict accumulator
Why would/should one not use the strict version here?
Because there's a typo in the implementation (notified the maintainer).
What do you mean when you say "recursive call"?
Let's look at lists first.
The specification in the standard is
foldl f z [] = z foldl f z (x:xs) = foldl f (f z x) xs ^^^^^ recursive call to foldl
Very similar for the list zipper, we have
foldlz :: (b -> Zipper a -> b) -> b -> Zipper a -> b foldlz f x z | endp z = x | otherwise = foldlz f (f x z) (right z) ^^^^^^
And for foldlz', the intention was
foldlz' :: (b -> Zipper a -> b) -> b -> Zipper a -> b foldlz' f x z | endp z = x | otherwise = acc `seq` foldlz' f acc (right z) where acc = f x z
but in the otherwise branch, the ' has been omitted, so instead of recursively calling itself with the new accumulator, it calls foldlz.
Ok, I though the typo was on my side. So you have found a bug. My hat is off to you. Thanks, Hugo F.

On Monday 31 October 2011, 23:42:30, Hugo Ferreira wrote:
So you have found a bug.
Just FYI, Ryan uploaded a new version, presumably with the bug fixed. You can now just cabal update; cabal install ListZipper and happily use foldlz' :D

On 10/31/2011 11:50 PM, Daniel Fischer wrote:
On Monday 31 October 2011, 23:42:30, Hugo Ferreira wrote:
So you have found a bug.
Just FYI, Ryan uploaded a new version, presumably with the bug fixed. You can now just cabal update; cabal install ListZipper and happily use foldlz' :D
Ok, I have updated and installed the new package. All is ok now. I unpacked and checked. Indeed, this bug has been corrected. Just a note for the rest of us newbies. I also did the following: - ghc-pkg unregister ListZipper-1.2.0.1 - configure the cabal package again - build the cabal package Thanks Daniel and Ryan, Rs, Hugo F.

On 11/01/2011 10:37 AM, Hugo Ferreira wrote:
On 10/31/2011 11:50 PM, Daniel Fischer wrote:
On Monday 31 October 2011, 23:42:30, Hugo Ferreira wrote:
So you have found a bug.
Just FYI, Ryan uploaded a new version, presumably with the bug fixed. You can now just cabal update; cabal install ListZipper and happily use foldlz' :D
Ok, I have updated and installed the new package. All is ok now. I unpacked and checked. Indeed, this bug has been corrected.
Just a note for the rest of us newbies. I also did the following:
- ghc-pkg unregister ListZipper-1.2.0.1 - configure the cabal package again - build the cabal package
Oops, the "package" above refers to my own code.
Thanks Daniel and Ryan,
Rs, Hugo F.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 10/31/2011 09:14 PM, Daniel Fischer wrote:
On Monday 31 October 2011, 10:36:53, Hugo Ferreira wrote:
Hello,
Apologies for the late reply but I had to prep the code.
On 10/28/2011 09:43 AM, Daniel Fischer wrote:
On Thursday 27 October 2011, 17:02:46, Hugo Ferreira wrote:
But something seems to be wrong here. If I do:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs
where scoreElem r s z =
let (nCorrect, nIncorrect) = s in case ruleApplication r z of
Just tag -> if tag == correct
then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1)
Nothing -> (nCorrect, nIncorrect)
where c = Z.cursor z
(correct,_) = c
it works correctly, however this does not work:
scoreRule_ r zs = Z.foldlz' (scoreElem r) (0, 0) zs
where scoreElem r (!nCorrect, !nIncorrect) z =
case ruleApplication r z of
Just tag -> if tag == correct
then (nCorrect+1, nIncorrect) else (nCorrect, nIncorrect+1)
Nothing -> (nCorrect, nIncorrect)
where c = Z.cursor z
(correct,_) = c
I have been staring at this for some time now, but cannot understand why it does not work. Any ideas?
No. Looks perfectly okay (well, the indentation is wrong, but that's the same for the working version above and is probably due to the mail client).
Not really. That's pretty much the indentation I am using. I actually had additional trace statements. Can you please tell me what's wrong?
You're not having the 'where's on their own lines ;) Seriously: I hadn't bothered to view it in fixed-width font and underestimated how much my mail client compresses contiguous whitespace.
Can you post the complete source for diagnosis?
I have attached the code + cabal files. I think that is all that is required. I am not sending the training data because it is too large (+7 Mega bytes). That is available at http://nlpwp.org/nlpwp-data.zip
Been a bugger to hunt down, but I finally found it. The culprit is *drumroll, ba-dum tish*: a one-character typo in Data.List.Zipper. foldlz' isn't. The recursive call is to foldlz, not foldlz'.
BTW, I changed foldlz' to foldlz and used (!) but still get the stack overflow. Need I do anything else? TIA, Hugo F.

On Monday 31 October 2011, 23:16:55, Hugo Ferreira wrote:
BTW, I changed foldlz' to foldlz and used (!)
No good. foldlz needs (in this case) the laziness in the accumulator.
but still get the stack overflow. Need I do anything else?
You can patch your ListZipper (cabal unpack ListZipper; correct the typo; increment version number in ListZipper.cabal; cabal install), then you can use foldlz' with a strict accumulator. Or you can use foldlz with a lazy accumulator, doesn't make much difference for the brown corpus. Also, in tokenTagFreqs, replace M.insertWith (twice) with M.insertWith', you're filling your maps with thunks as is. Evaluating entries on the spot reduces time and memory requirements.

On 10/31/2011 10:46 PM, Daniel Fischer wrote:
On Monday 31 October 2011, 23:16:55, Hugo Ferreira wrote:
BTW, I changed foldlz' to foldlz and used (!)
No good. foldlz needs (in this case) the laziness in the accumulator.
but still get the stack overflow. Need I do anything else?
You can patch your ListZipper (cabal unpack ListZipper; correct the typo; increment version number in ListZipper.cabal; cabal install), then you can use foldlz' with a strict accumulator. Or you can use foldlz with a lazy accumulator, doesn't make much difference for the brown corpus.
Hmmm.... how so? I get stack overflow. You mean use the RTS options to increase memory.
Also, in tokenTagFreqs, replace M.insertWith (twice) with M.insertWith', you're filling your maps with thunks as is. Evaluating entries on the spot reduces time and memory requirements.
Will report this to the book's authors. Thanks once again, Hugo F.
participants (2)
-
Daniel Fischer
-
Hugo Ferreira