Re: Why do we have stack overflows?

2007-05-03 Thread Stefan O'Rear
On Thu, May 03, 2007 at 05:36:45PM -0700, Brandon Michael Moore wrote:
> On Thu, May 03, 2007 at 04:59:58PM -0700, John Meacham wrote:
> > I believe it is because a stack cannot be garbage collected, and must be
> > traversed as roots for every garbage collection. I don't think there are
> > any issues with a huge stack per se, but it does not play nice with
> > garbage collection so may hurt your performance and memory usage in
> > unforeseen ways.
> 
> Isn't it just the top of the stack that has to be treadted as a root?
> (maybe you need to walk the stack to find exception handlers and so on.)
> Maybe it shouldn't be so much worse than a heap. The Chicken Scheme
> system allocates everything on the C stack, and runs some sort of
> compacting collector when it is about to fill.

GHC uses a simple exponential-backoff algorithm for handling stacks.
When the stack pointer passes the stack limit, the thread yields to
the scheduler, where the stack size is doubled, and the old stack is
moved.  Perhaps instead we could modify the algorithm such that up to
16K stack size the behaivor is the same, but use linked lists for
larger? 

1. Allocate a new chunk, of size 16KB.

2. Copy the topmost 1KB of stack to the new block.  This decreases
   storage efficiency slightly (but not much in time - memcpy is
   several times faster than anything the current ghc code generator
   can generate), but it avoids a nasty corner case (stack size
   fluctuating across 0 mod 16K) by acting as a form of hysteresis.

3. Create a special frame at the bottom of the new stack chunk that
   returns into a stack underflow handler, thus avoiding the need for
   yet another conditional. 

Yes, 16KB unrolled linked lists are virtually as fast as flat byte
arrays; see Data.ByteString.Lazy if you want proof. 

The only hard part appears to be step 3, as it requires finding an
appropriate place to insert the trampoline frame; it seems plausible
that stack frames are sufficiently self describing to make this a
simple exercise of loops, but it could be much much harder. 

With this change GHC stacks could fill the whole heap with little more
performance degradation than ordinary objects already give. 

Stefan
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Why do we have stack overflows?

2007-05-03 Thread Brandon Michael Moore
On Thu, May 03, 2007 at 04:59:58PM -0700, John Meacham wrote:
> I believe it is because a stack cannot be garbage collected, and must be
> traversed as roots for every garbage collection. I don't think there are
> any issues with a huge stack per se, but it does not play nice with
> garbage collection so may hurt your performance and memory usage in
> unforeseen ways.

Isn't it just the top of the stack that has to be treadted as a root?
(maybe you need to walk the stack to find exception handlers and so on.)
Maybe it shouldn't be so much worse than a heap. The Chicken Scheme
system allocates everything on the C stack, and runs some sort of
compacting collector when it is about to fill.

Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Why do we have stack overflows?

2007-05-03 Thread John Meacham
On Thu, May 03, 2007 at 05:40:24PM +0100, Adrian Hey wrote:
> Duncan Coutts wrote:
> >On Thu, 2007-05-03 at 16:24 +0100, Adrian Hey wrote:
> >>Hello Folks,
> >>
> >>Just wondering about this. Please understand I'm not asking why
> >>programs use a lot of stack sometimes, but specifically why is
> >>using a lot of stack (vs. using a lot of heap) generally regarded
> >>as "bad". Or at least it seems that way given that ghc run time
> >>makes distinction between the two and sets separate
> >>limits for them (default max stack size being relatively small
> >>whereas default max heap size in unlimited). So programs can
> >>fail with a stack overflow despite having bucket loads of heap
> >>available?
> >
> >Perhaps it's there to help people who write simple non-terminating
> >recursion. They'll get an error message fairly soon rather than using
> >all memory on the machine and invoking the wrath of the OOM killer.
> 
> Hmm, I still don't see why a "stack leak" should be treated differently
> from "heap leak". They'll both kill your program in the end.

I believe it is because a stack cannot be garbage collected, and must be
traversed as roots for every garbage collection. I don't think there are
any issues with a huge stack per se, but it does not play nice with
garbage collection so may hurt your performance and memory usage in
unforeseen ways.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Why do we have stack overflows?

2007-05-03 Thread Adrian Hey

Duncan Coutts wrote:

On Thu, 2007-05-03 at 16:24 +0100, Adrian Hey wrote:

Hello Folks,

Just wondering about this. Please understand I'm not asking why
programs use a lot of stack sometimes, but specifically why is
using a lot of stack (vs. using a lot of heap) generally regarded
as "bad". Or at least it seems that way given that ghc run time
makes distinction between the two and sets separate
limits for them (default max stack size being relatively small
whereas default max heap size in unlimited). So programs can
fail with a stack overflow despite having bucket loads of heap
available?


Perhaps it's there to help people who write simple non-terminating
recursion. They'll get an error message fairly soon rather than using
all memory on the machine and invoking the wrath of the OOM killer.


Hmm, I still don't see why a "stack leak" should be treated differently
from "heap leak". They'll both kill your program in the end.

Regards
--
Adrian Hey

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Why do we have stack overflows?

2007-05-03 Thread Duncan Coutts
On Thu, 2007-05-03 at 16:24 +0100, Adrian Hey wrote:
> Hello Folks,
> 
> Just wondering about this. Please understand I'm not asking why
> programs use a lot of stack sometimes, but specifically why is
> using a lot of stack (vs. using a lot of heap) generally regarded
> as "bad". Or at least it seems that way given that ghc run time
> makes distinction between the two and sets separate
> limits for them (default max stack size being relatively small
> whereas default max heap size in unlimited). So programs can
> fail with a stack overflow despite having bucket loads of heap
> available?

Perhaps it's there to help people who write simple non-terminating
recursion. They'll get an error message fairly soon rather than using
all memory on the machine and invoking the wrath of the OOM killer.

Duncan

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Why do we have stack overflows?

2007-05-03 Thread Adrian Hey

Hello Folks,

Just wondering about this. Please understand I'm not asking why
programs use a lot of stack sometimes, but specifically why is
using a lot of stack (vs. using a lot of heap) generally regarded
as "bad". Or at least it seems that way given that ghc run time
makes distinction between the two and sets separate
limits for them (default max stack size being relatively small
whereas default max heap size in unlimited). So programs can
fail with a stack overflow despite having bucket loads of heap
available?

Frankly I don't care if my program fails because it's used
a lot of stack or a lot of heap. I would rather set some
common memory budget and have them fail if that budget was
exceeded.

This policy seems to have unfortunate consequences. Sometimes
you end up re-writing stuff in a manner that just trades stack
use for heap use (I.E. doesn't do anything to reduce overall
memory consumption). Given the cost of reclaiming heap
is rather high (compared to stack), this seems like bad idea
(the version that used a lot of stack would be better IMO
if only it didn't risk stack overflow).

Example..

-- Strict version of take
stackGobbler :: Int -> [x] -> [x]
stackGobbler 0 _  = []
stackGobbler _ [] = []
stackGobbler n (x:xs) = let xs' = stackGobbler (n-1) xs
in  xs' `seq` (x:xs')

-- Another strict version of take
heapGobbler :: Int -> [x] -> [x]
heapGobbler = heapGobbler' []
 where heapGobbler' rxs 0 _  = reverse rxs
   heapGobbler' rxs _ [] = reverse rxs
   heapGobbler' rxs n (x:xs) = heapGobbler' (x:rxs) (n-1) xs

But I guess everyone here is already aware of this, hence the question
(current ghc memory system design seems a bit odd, but maybe there's
a good reason why the rts can't work the way I would like).

Thanks
--
Adrian Hey


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Error compiling GHC/Num.lhs

2007-05-03 Thread Bas van Dijk

On 5/3/07, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:

I think I have fixed it...


You did, thanks very much!

GHC now builds and install without any errors, jippy!

Thanks,

Bas van Dijk
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Pretty printing type annotations

2007-05-03 Thread C.M.Brown
Hi,

I was wondering if there was an easy way to pretty print the result of the
type checker from GHC. I basically want the format that GHCi spits out,
rather than a type annotation with qualified types. I know I can knock up
a parser that removes the qualifiers, but I was wondering if there was a
simple function that I could call that would just printy print it for me
(and saving me the work).

The type checker gives me something of the form:

(GHC.Num.Num t1, GHC.Num.Num t) => t1 -> t -> t1

But GHCi gives me the same without any qualifying.

Hope someone can help.
Chris.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Error compiling GHC/Num.lhs

2007-05-03 Thread Simon Peyton-Jones
the base library is in a bit of a sad state.

I think I have fixed it.  Try pulling (both compiler and libraries) and try 
again

S

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On
| Behalf Of Bas van Dijk
| Sent: 03 May 2007 11:32
| To: Bertram Felgenhauer
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: Error compiling GHC/Num.lhs
|
| On 5/2/07, Bertram Felgenhauer <[EMAIL PROTECTED]> wrote:
| > ...
| > I have two patches that should fix this:
| > ...
|
| Thanks, I applied base-install-includes.patch.
| (Cabal-fix-installIncludeFiles.patch was already applied according to
| darcs.)
|
| However, in order to apply the patches I did a new checkout of GHC
| without the --partial. This seemed to have pulled a few new patches
| that break my build again.
|
| I fixed the first error (I darcs send the patch):
|
| ./compiler/coreSyn/CoreUtils.lhs 262
| -mkAltExpr DEFAULT = panic "mkAltExpr"
| +mkAltExpr DEFAULT _ _ = panic "mkAltExpr"
|
|
| This leaves the second error when building base:
|
| Building base-2.1...
|
| GHC/Exts.hs:29:1:
| Not in scope: type constructor or class `IsString'
|
| If I import Data.String in GHC/Exts.hs I get the following error:
|
| Building base-2.1...
| ghc-6.7.20070502: panic! (the 'impossible' happened)
|   (GHC version 6.7.20070502 for i386-unknown-linux):
| mkWWcpr: not a product base:Data.Typeable.TypeRep{tc r3eN}
|
| What can be the problem?
|
| regards,
|
| Bas van Dijk
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Error compiling GHC/Num.lhs

2007-05-03 Thread Bas van Dijk

On 5/2/07, Bertram Felgenhauer <[EMAIL PROTECTED]> wrote:

...
I have two patches that should fix this:
...


Thanks, I applied base-install-includes.patch.
(Cabal-fix-installIncludeFiles.patch was already applied according to
darcs.)

However, in order to apply the patches I did a new checkout of GHC
without the --partial. This seemed to have pulled a few new patches
that break my build again.

I fixed the first error (I darcs send the patch):

./compiler/coreSyn/CoreUtils.lhs 262
-mkAltExpr DEFAULT = panic "mkAltExpr"
+mkAltExpr DEFAULT _ _ = panic "mkAltExpr"


This leaves the second error when building base:

Building base-2.1...

GHC/Exts.hs:29:1:
   Not in scope: type constructor or class `IsString'

If I import Data.String in GHC/Exts.hs I get the following error:

Building base-2.1...
ghc-6.7.20070502: panic! (the 'impossible' happened)
 (GHC version 6.7.20070502 for i386-unknown-linux):
   mkWWcpr: not a product base:Data.Typeable.TypeRep{tc r3eN}

What can be the problem?

regards,

Bas van Dijk
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC -O2 and unsafePerformIO

2007-05-03 Thread Neil Mitchell

Hi Simon,


This is clearly a misuse of unsafePerformIO (as I'm sure you're aware).  Just
out of interest - what's the context?


I am writing an optimiser for Yhc, doing whole-program optimisation,
with the intention of keeping it fast and high performance. Since
writing out Yhc bytecode would kill any performance benefits, I am
writing back to Haskell to be compiled with GHC. So the basic sequence
of steps is:

compile Haskell to Yhc Core
transform Yhc Core
convert Yhc Core to Haskell
compile Haskell to GHC

The problem I'm currently overcoming is that Yhc inserts its own IO
monad, which isn't the same as the GHC one. By the time I get to GHC
Haskell, all of the Yhc monad is invisible to GHC, so I have to
unsafePerformIO the getchar/putchar functions. With this as the
primitive getchar, it seems to work for my particular example, but is
clearly a bit fragile.

All the examples I'm doing for now are wc -c, wc -l, so shouldn't
stress the IO much more than getchar/putchar.

Thanks

Neil
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC -O2 and unsafePerformIO

2007-05-03 Thread Simon Marlow

Neil Mitchell wrote:

Hi

Thanks to dcoutts, I have now come up with an answer. I don't
understand why it works now, but not before. I do remember than
browsing either Core or STG is not a fun thing to do...

p_System_IO_hGetChar h   = trace "i am here" $
   unsafePerformIO  $ getCharIO h


{-# NOINLINE getCharIO #-}
getCharIO h = do
   c <- getchar
   print c
   return $ if c == (-1) then 0 else chr_ c


This is clearly a misuse of unsafePerformIO (as I'm sure you're aware).  Just 
out of interest - what's the context?


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users