John Lask wrote:
:
| The following code causes a "C stack overflow" in hugs (version 20051031)
| but not in ghc (version 6.6)
| The point of the exercise is to process a very large file lazily,
| returning the consumed and unconsumed parts (i.e. basic parser
combinators).
:
|
Hi
hoping someone can shed some light on this:
The following code causes a "C stack overflow" in hugs (version 20051031)
but not in ghc (version 6.6)
The point of the exercise is to process a very large file lazily, returning
the consumed and unconsumed
parts (i.e. basic parser c
, Chad; [email protected]
Subject: Re: [Haskell] stack overflow - nonobvious thunks?
Dean's version certainly seems the neatest, but just for interest you
can also do it with a cps fold instead of foldl' too:
table xs = assocs $! cpsfold f empty xs
where
f x m k = case Map.loo
On Wednesday 27 Jul 2005 10:19 pm, Scherrer, Chad wrote:
> Adrian, Does your AVL library have an "insertWith'"-type function
> mentioned by Udo?
I haven't followed this too closely, but I did try to ensure that
Data.Tree.AVL provides all the strictness control users will need
in practice.
Basical
Dean's version certainly seems the neatest, but just for interest you
can also do it with a cps fold instead of foldl' too:
table xs = assocs $! cpsfold f empty xs
where
f x m k = case Map.lookup x m of
Just v -> v `seq` (k $ Map.adjust (+1) x m)
Nothing ->
Title: RE: [Haskell] stack overflow - nonobvious
thunks?
The following version seems to do the trick (and still remain
quite readable). It worked for 1 as well.
import Data.Map as Map
import System.Random
import Data.List (foldl')
table :: (Ord a) => [a] -> [(a,Int
; f Map.empty xs
where
f m x = (Map.insert x $! 1 + Map.findWithDefault 0 x m) $! m
This helps with the stack overflow problem, but now I'm hitting a
different wall:
*Main> table $ take 1000 unif
[(1,999662),(2,1000220),(3,998800),(4,1000965),(5,999314),(6,1001819),(7
,1000997),(8,999450),
Scherrer, Chad wrote:
> f m x = Map.insertWith (+) x 1 m
insertWith is inserting the "nonobvious thunks". Internally it applies
(+) to the old value and the new one, producing a thunk. There is no
place you could put a seq or something to force the result. You
basically need insertWith',
Title: stack overflow - nonobvious thunks?
I'm trying to write a function to build a table of values from a list. Here's my current attempt:
table :: (Ord a) => [a] -> [(a,Int)]
table xs = Map.assocs $! foldl' f Map.empty xs
where
f m x = Map.insertWith (+)
> The simplest and safest solution is to change foldl to foldl', but it produces
> the unnecessary evaluation of `elem`s in addSetElem's.
Wrong. Please ignore it.
$!! is better in a sense that it reduces the stack usage further
than foldl' (foldl''s second argument needs stacks to be evaluated).
On Wed, 04 Feb 2004 23:00:50 +
Graham Klyne <[EMAIL PROTECTED]> wrote:
> I'm getting a "C stack overflow" error from Hugs when processing a
> moderately large dataset, but not doing anything that looks unreasonably
> complex or involved.
>
> I think
I'm getting a "C stack overflow" error from Hugs when processing a
moderately large dataset, but not doing anything that looks unreasonably
complex or involved.
As far as I can tell, the code causing the problem is about here:
[[
-- Return list of distinct labels used in a gr
Hi,
Interestingly given the recent discussion about foldl versus foldl'
I'd like to report that the stack overflow I was seeing was due to
addListToFM which is defined using foldl although addToFM is strict
in FiniteMap according to ghc:
addToFM :: ... {PrelBase.Ord key} -> Fini
I know it's complete heresy to say so, but I use laziness very
little in Haskell, while I probably pay quite a lot for it
in CPU time and memory, because of all those thunks which have to be
stored. However I prefer Haskell's type classes, syntax and
purity to, say, Standard ML. So I wonder whet
"C.Reinke" <[EMAIL PROTECTED]> writes:
> So foldl is indeed tail recursive, but this doesn't help if its
> operator isn't strict because the tail recursion only builds up the
> expression to be evaluated. Making strictness explicit by defining a
> variant of foldl that evaluates its accumulator a
"Julian Assange" <[EMAIL PROTECTED]>:
> ..
> | When used with a 170k input file, makemap suffers from a stack
> | overflow. foldl should be tail recursive. What's the score?
"Simon Peyton-Jones" <[EMAIL PROTECTED]>:
> Consider
>
gratuitous leaks.
Simon
| -Original Message-
| From: Julian Assange [mailto:[EMAIL PROTECTED]]
| Sent: 24 February 2001 10:50
| To: [EMAIL PROTECTED]
| Cc: [EMAIL PROTECTED]
| Subject: stack overflow
|
|
| -- compile with:
| -- ghc -i/usr/lib/ghc-4.08.1/imports/data -lHSdata
| -
oFM fm word (n+1)
where
n = lookupWithDefaultFM fm 0 word
lower = map toLower
When used with a 170k input file, makemap suffers from a stack
overflow. foldl should be tail recursive. What'
18 matches
Mail list logo