RE: installHandler, sleep, and interrupts.

2001-10-30 Thread Simon Marlow

 When interrupting this program, the signal handler does not 
 get called:
 
 module Main where
 import Posix
 
 main = do
 installHandler 2 (Catch (putStrLn Hello, world!)) Nothing
 sleep 600
 -- putStr 

Try using Concurrent.threadDelay instead of Posix.sleep, since the
latter doesn't let other threads run while it is sleeping (it should do;
I'll fix this in my rewrite of Posix).

Cheers,
Simon

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



Re: Changed behaviour when reading from FIFOs!

2001-10-30 Thread Volker Stolz

On Mon, Oct 29, 2001 at 02:52:25PM -, Simon Marlow wrote:
  The blocking is essential since I need to be able to use MVars
  between the threadWaitRead  the hGetLine (remember the note I
  sent about fork()ing).
 
 Sorry, I can't remember that - could you remind me?  The hGetLine
 already blocks if there's no data in the FIFO, the extra threadWaitRead
 will only work if the Handle is in NoBuffering mode, because otherwise
 there might be data in the handle buffer waiting to be read which
 threadWaitRead would be unable to detect.

I'm using 'fork' (the real thing, not forkIO), in a Concurrent
Haskell programm and I need a way to lock out multiple readers
from the same file handle because of the sharing when forking.
-- 
Volker Stolz * [EMAIL PROTECTED] * PGP + S/MIME

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



RE: Small cosmetic bug

2001-10-30 Thread Simon Marlow


 I discovered a minor cosmetic bug today. After my
 undescribable hapiness about the fact that GHCi now has the
 :i command, I started playing around, and discovered the
 following ugly output:
 
   Prelude :i []
   -- [] is a data constructor
   [] :: forall t_12. [t_12]

Thanks, I've fixed this.

Cheers,
Simon

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



Re: Building GHC 5.02 on Solaris x86

2001-10-30 Thread Ian Lynagh


Thanks for your help Simon.

Unfortunately I think I have spent enough time on this, and not enough
on what I would like it for, without getting there - I may try again in
the future if the porting process becomes better documented/tested.


Ian


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



RE: ByteCodeLink.lookupIE PrelTup.Z73T{-72m-}

2001-10-30 Thread Simon Marlow

 Hi, I got the following error message:

___ ___ _
   / _ \ /\  /\/ __(_)
  / /_\// /_/ / /  | |  GHC Interactive, version 5.02, for Haskell 98.
 / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
 \/\/ /_/\/|_|  Type :? for help.
 
 Loading package std ... linking ... done.
 Compiling FormulaType  ( FormulaType.hs, interpreted )
 Compiling Reqtypes ( Reqtypes.hs, interpreted )
 Compiling Reqparser( Reqparser.hs, interpreted )
 ghc-5.02: panic! (the `impossible' happened, GHC version 5.02):
   ByteCodeLink.lookupIE PrelTup.Z73T{-72m-}

GHC uses tuples in its internal translation of mutually recursive function groups.  In 
this case, there is a group of 73(!) mutually recursive functions, and the simplifier 
wasn't able to simplify away the tuple.  Since we don't have 73-tuples defined in the 
Prelude, the linker failed.

Ok, so what are we doing about this.  Well, the problem that prevented the simplifier 
from eliminating the tuple has been fixed, so 5.02.1 will work with this code.  The 
underlying problem, namely that the compiler generates references to out-of-range 
tuples, probably won't be fixed in time for 5.02.1, but we're looking into it.

Thanks for the report.

Cheers,
Simon

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



RE: installHandler, sleep, and interrupts.

2001-10-30 Thread Anders Lau Olsen


I later ran into another problem that may or may not be related with the
first. This is the program I am running:

module Main where
import Posix

main = do
installHandler sigCONT (Catch (putStrLn - resumed -)) Nothing
forever $ do
c - getChar
putChar c

forever = sequence_ . repeat

This is the output from a conversation with the shell:

% ./program 
[2] 8959
[2]  + Suspended (tty input) ./program
% fg
./program
a
a
b
b
c
c
d
d
e
e- resumed -

The handler is run not shortly after the signal is received, but only
after a sufficient amount of I/O or processing has been done by the main
process.

Anders Lau Olsen


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