Shutting Down the RTS

2003-01-12 Thread Wolfgang Thaller
I'm almost ready to send in a patch that should fix most of the current 
issues with the threaded RTS.
But I'm stuck at the problem of terminating the RTS in a proper way.

According to the GHC manual, a concurrent Haskell program should 
terminate when the main action terminates. This sounds reasonable and 
matches the behaviour of C programs on most platforms.

In the threaded RTS, this behaviour has never been implemented. We 
can't simply return from schedule(), because we might no longer be 
running in the thread of the RTS main() routine. The thread where 
rts_mainEvalIO was called might be busy executing some foreign code 
that we know nothing about.

(Im)possible solution #1: As soon as the main action terminates, call 
shutdownHaskellAndExit(). At first, this seems to work fine.
But then, shutdownHaskellAndExit() comes along and tries to run 
finalizers. For every finalizer, the RTS is started back up again using 
rts_mainEvalIO(), and this time, we really have to exit by returning 
from rts_mainEvalIO().

Possible solution #2: Forget about running finalizers at program 
termination and just exit().
In most of the situations where I'd use finalizers, I don't need to run 
them upon program termination, the OS cleans up after me. Also, the 
finalizers are not run in the correct order anyway, and there are 
situations where running them in the wrong order might be worse than 
not running them at all.
And, most of all, solution #2 is easy to implement.

Can somebody suggest a third solution, or shall I go for #2 for the 
time being?


Cheers,

Wolfgang

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Shutting Down the RTS

2003-01-12 Thread John Meacham
An advantage of solution #2 is that the finalizers dont go through and
touch all the pages they modify causing them to be loaded into memory if
they had been swapped to disk and thrash the page lookup cache on the
CPU. The overhead of the RTS in general might drown out these concerns
but they are definatly considered important when writing efficient
C utilities.
John

On Mon, Jan 13, 2003 at 12:41:17AM +0100, Wolfgang Thaller wrote:
> I'm almost ready to send in a patch that should fix most of the current 
> issues with the threaded RTS.
> But I'm stuck at the problem of terminating the RTS in a proper way.
> 
> According to the GHC manual, a concurrent Haskell program should 
> terminate when the main action terminates. This sounds reasonable and 
> matches the behaviour of C programs on most platforms.
> 
> In the threaded RTS, this behaviour has never been implemented. We 
> can't simply return from schedule(), because we might no longer be 
> running in the thread of the RTS main() routine. The thread where 
> rts_mainEvalIO was called might be busy executing some foreign code 
> that we know nothing about.
> 
> (Im)possible solution #1: As soon as the main action terminates, call 
> shutdownHaskellAndExit(). At first, this seems to work fine.
> But then, shutdownHaskellAndExit() comes along and tries to run 
> finalizers. For every finalizer, the RTS is started back up again using 
> rts_mainEvalIO(), and this time, we really have to exit by returning 
> from rts_mainEvalIO().
> 
> Possible solution #2: Forget about running finalizers at program 
> termination and just exit().
> In most of the situations where I'd use finalizers, I don't need to run 
> them upon program termination, the OS cleans up after me. Also, the 
> finalizers are not run in the correct order anyway, and there are 
> situations where running them in the wrong order might be worse than 
> not running them at all.
> And, most of all, solution #2 is easy to implement.
> 
> Can somebody suggest a third solution, or shall I go for #2 for the 
> time being?
> 
> 
> Cheers,
> 
> Wolfgang
> 
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> 

-- 
---
John Meacham - California Institute of Technology, Alum. - [EMAIL PROTECTED]
---
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Uninitialized UArray - feature or bug?

2003-01-12 Thread Tomasz Zielonka
Hello!

This is a little weird:

Prelude> :m + Data.Array.Unboxed
Prelude Data.Array.Unboxed> let f () = array (1, 5) [] :: UArray Int Int
Prelude Data.Array.Unboxed> f () == f ()
False

Are we giving away purity for efficiency? ;)
If this behaviour is intended, maybe it should be documented?

Maybe it would be a good idea to define default values for types which
can be unboxed?

Regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Why doesn't this Template Haskell program work?

2003-01-12 Thread Sean Seefried
I compiled the following program with ghc-5.05.20030109

--

import Language.Haskell.THSyntax

main = putStrLn (show $(lift ('a', 'b')))

instance (Lift a, Lift b) => Lift (a,b) where
lift (a,b) = tup [lift a, lift b]

-

and received the following error message

---

ghc --make -fglasgow-exts -package haskell-src -package haskell98 
Main.hs -o test
Chasing modules from: Main.hs
Compiling Main ( Main.hs, ./Main.o )
Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package haskell-src ... linking ... done.
ghc-5.05.20030109: panic! (the `impossible' happened, GHC version 
5.05.20030109):
nameModule zdfLiftZ2T{-a1dB-}

Please report it as a compiler bug to [EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.

--

Why? Because if I compile the following program,



import Language.Haskell.THSyntax

main = putStrLn (show $(tup [lift 'a', lift 'b']))



it works just fine.

Also, is the template-haskell mailing list active?

Sean Seefried

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Another question regarding Template Haskell

2003-01-12 Thread Sean Seefried
Would it be possible to write a function "showFun"  such that one could 
write a program

f x y = x +y -- say

main = putStrLn (show $(showFun f))

and the result of this program would be

"f"

I don't think it's possible at the moment because one can't reify 
expressions.

Sean Seefried

p.s. If I'm posting to the wrong group, I apologise, it's just that 
template-haskell doesn't seem to be a mail group just yet.  I've posted 
to it and haven't seen any of my postings appear yet.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users