preemptive getLine on cygwin?

2003-08-14 Thread Claus Reinke
I seem to have some problems understanding preemptive getLine 
behaviour on cygwin, and wonder whether this is a known/fixed 
bug/feature (I haven't switched to ghc-6.. yet), or whether anyone 
has experience with this (behaviour on solaris, with an even older 
ghc is more or less as expected).

Claus

-- consider the following example. compile, run, and whenever the
-- program waits for input, enter the next natural number, starting
-- from 1. note that the program preempts the first input and may
-- or may not accept input after the second output..

module Main where
import IO

main = do
  hGetBuffering stdin = print
  hGetLine stdin = print 
  hGetLine stdin = print 

--- win98, cygwin

$ ./Getline
LineBuffering


1
1

$ cat | ./Getline
BlockBuffering Nothing
1
1
2
2
3

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 5.04.2


--- solaris

$ ./GetLine
LineBuffering
1
1
2
2
$ cat | ./GetLine
BlockBuffering Nothing
1
1
2
2
3
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 5.02.3



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


Re: preemptive getLine on cygwin?

2003-08-14 Thread Claus Reinke
 I seem to have some problems understanding preemptive getLine 
 behaviour on cygwin, and wonder whether this is a known/fixed 
 bug/feature (I haven't switched to ghc-6.. yet), or whether anyone 
 has experience with this (behaviour on solaris, with an even older 
 ghc is more or less as expected).

You're running a fairly old version of GHC.  With 5.04.3 here I get
different behaviour, although strangely it seems that stdin and stdout
don't default to LineBuffering in a cygwin shell window.

So that's a third variant of runtime behaviour, then, for the same 
trivial program (probably cygwin on a more modern windows?)!? 

What do other GHC versions say? And, more importantly, what 
_should_ they do? Strangely, with Blockbuffering the program
seems to be slightly better behaved than with LineBuffering in 
cygwin, so the cat-hack helps a bit (strangely, because I'm 
reading lines, so I'd usually explicitly set LineBuffering.., and 
slightly better, because it's still not quite as I would have 
expected).

I'd still like to understand what's going on and how to get my 
Haskell programs to behave (this arises in a debugging mode of 
a larger app and means that, at the moment, I can't easily use this 
for debugging, which makes life slightly difficult, but at least it
doesn't seem to cause the bug*..).

Cheers,
Claus

* just checked in an ms-dos-console, which works as expected. 
So it seems that the issue is an interaction of ghc/cygwin?

Getline
LineBuffering
1
1
2
2




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


RE: preemptive getLine on cygwin?

2003-08-14 Thread Simon Marlow
 
 So that's a third variant of runtime behaviour, then, for the same 
 trivial program (probably cygwin on a more modern windows?)!? 
 
 What do other GHC versions say? And, more importantly, what 
 _should_ they do?

GHC 5.04.3 behaves as I'd expect, except that it defaults to
BlockBuffering for stdin/stdout in a cygwin window.  In a DOS window it
defaults to LineBuffering as expected.  This appears to be because
mingw's implementation of isatty() only detects DOS windows, which is
reasonable.

 Strangely, with Blockbuffering the program
 seems to be slightly better behaved than with LineBuffering in 
 cygwin, so the cat-hack helps a bit (strangely, because I'm 
 reading lines, so I'd usually explicitly set LineBuffering.., and 
 slightly better, because it's still not quite as I would have 
 expected).
 
 I'd still like to understand what's going on and how to get my 
 Haskell programs to behave (this arises in a debugging mode of 
 a larger app and means that, at the moment, I can't easily use this 
 for debugging, which makes life slightly difficult, but at least it
 doesn't seem to cause the bug*..).

I think just upgrading your GHC should fix things.  If not, we'll look
into it.

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


RE: preemptive getLine on cygwin?

2003-08-14 Thread Simon Marlow
 
 I seem to have some problems understanding preemptive getLine 
 behaviour on cygwin, and wonder whether this is a known/fixed 
 bug/feature (I haven't switched to ghc-6.. yet), or whether anyone 
 has experience with this (behaviour on solaris, with an even older 
 ghc is more or less as expected).

You're running a fairly old version of GHC.  With 5.04.3 here I get
different behaviour, although strangely it seems that stdin and stdout
don't default to LineBuffering in a cygwin shell window.

Cheers,
Simon

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