[Haskell-beginners] Stack space overflow: using strict accumulator still fails
Hugo Ferreira
hmf at inescporto.pt
Thu Oct 27 17:02:46 CEST 2011
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.
>
More information about the Beginners
mailing list