Re: [GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-11-10 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
+---
 Reporter:  FalconNL|  Owner: 
 Type:  bug | Status:  new
 Priority:  high|  Milestone:  6.10.2 
Component:  libraries/base  |Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  hsetbuffering buffering buffer  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Comment (by camio):

 Alistar Bayley noted this workaround in haskell-cafe
 {{{
 {-# LANGUAGE ForeignFunctionInterface #-}
 import Data.Char
 import Control.Monad (liftM)
 import Foreign.C.Types

 getHiddenChar = liftM (chr.fromEnum) c_getch
 foreign import ccall unsafe conio.h getch
   c_getch :: IO CInt
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:11
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-10-29 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
+---
 Reporter:  FalconNL|  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone:  6.10.2 
Component:  libraries/base  |Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  hsetbuffering buffering buffer  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Changes (by camio):

 * cc: camio (added)

Comment:

 This is also very important for those of us working on FRP at Anygma since
 it precludes simple console-based FRP examples.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:9
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-10-04 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
+---
 Reporter:  FalconNL|  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone:  6.10.2 
Component:  libraries/base  |Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  hsetbuffering buffering buffer  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Changes (by igloo):

  * milestone:  6.10.1 = 6.10.2

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:8
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-09-10 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
+---
 Reporter:  FalconNL|  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone:  6.10.1 
Component:  libraries/base  |Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  hsetbuffering buffering buffer  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Comment (by igloo):

 See also #2568.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:7
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-06-20 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
+---
 Reporter:  FalconNL|  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone:  6.10.1 
Component:  GHCi|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  hsetbuffering buffering buffer  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Changes (by igloo):

  * milestone:  6.8.3 = 6.10.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-05-22 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
+---
 Reporter:  FalconNL|  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone:  6.8.3  
Component:  GHCi|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  hsetbuffering buffering buffer  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Comment (by judah):

 There is code in {{{base/cbits/consUtils.c:set_console_buffering}}} to
 disable Windows line buffering (by calling the Win32 function
 `SetConsoleMode`).
 However, the code in `GHC.Handle` which is supposed to call that function
 was `#ifdef`'ed out on mingw in the following commit:

 http://cvs.haskell.org/cgi-
 bin/cvsweb.cgi/fptools/libraries/base/GHC/Handle.hs#rev1.14

 From the comments in `System.Posix.Internals`:
 {{{
 -- 'raw' mode for Win32 means turn off 'line input' (= buffering and
 -- character translation for the console.) The Win32 API for doing
 -- this is GetConsoleMode(), which also requires echoing to be disabled
 -- when turning off 'line input' processing. Notice that turning off
 -- 'line input' implies enter/return is reported as '\r' (and it won't
 -- report that character until another character is input..odd.) This
 -- latter feature doesn't sit too well with IO actions like IO.hGetLine..
 }}}

 I'm not that experienced with Windows programming, but maybe instead of
 changing the `ConsoleMode`, we could call the lower-level
 `ReadConsoleInput/PeekConsoleInput` when we want to read only one
 character at a time.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-04-30 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
+---
 Reporter:  FalconNL|  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone:  6.8.3  
Component:  GHCi|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  hsetbuffering buffering buffer  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Changes (by simonmar):

  * priority:  low = normal

Comment:

 This is important to folks here at Galois; I'll try to look at it before
 6.8.3.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-04-26 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
+---
 Reporter:  FalconNL|  Owner: 
 Type:  bug | Status:  new
 Priority:  low |  Milestone:  6.8.3  
Component:  GHCi|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  hsetbuffering buffering buffer  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Changes (by igloo):

  * priority:  normal = low

Comment:

 OK, I can reproduce the problem. At the Haskell level the problem is that
 asyncRead# isn't returning when a key is pressed; I haven't followed all
 the RTS stuff through to see where it goes wrong. Could be related to
 #806. I doubt we'll get to this for 6.8.3, so I'm marking it as low
 priority.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-04-24 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
+---
 Reporter:  FalconNL|  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone:  6.8.3  
Component:  GHCi|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  hsetbuffering buffering buffer  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Windows |  
+---
Changes (by igloo):

  * difficulty:  = Unknown
  * milestone:  = 6.8.3

Comment:

 Thanks for the report!

 It works for me on Linux; I can't test on Windows at the moment.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows XP

2008-03-31 Thread GHC
#2189: hSetBuffer stdin NoBuffering doesn't seem to work in ghc 6.8.2 on Windows
XP
---+
Reporter:  FalconNL|   Owner: 
Type:  bug |  Status:  new
Priority:  normal  |   Component:  GHCi   
 Version:  6.8.2   |Severity:  normal 
Keywords:  hsetbuffering buffering buffer  |Testcase: 
Architecture:  x86 |  Os:  Windows
---+
 The following program repeats inputted characters until the escape key is
 pressed.


 {{{
 import IO
 import Monad
 import Char

 main :: IO ()
 main = do hSetBuffering stdin NoBuffering
   inputLoop

 inputLoop :: IO ()
 inputLoop = do i - getContents
mapM_ putChar $ takeWhile ((/= 27) . ord) i
 }}}


 Because of the hSetBuffering stdin NoBuffering line it should not be
 necessary to press the enter key between keystrokes. This program works
 correctly in WinHugs (sep 2006 version). However, GHC 6.8.2 does not
 repeat the characters until the enter key is pressed. The problem was
 reproduced with all GHC executables (ghci, ghc, runghc, runhaskell), using
 both cmd.exe and command.com on Windows XP Professional.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs