Re: [Haskell-cafe] getChar

2008-03-25 Thread Albert Y. C. Lai

Cetin Sert wrote:
is there a version of getChar that doesn't buffer keyboard input until 
enter is pressed?


Look into hSetBuffering (module System.IO or IO).  As a quick start:

hSetBuffering stdin NoBuffering

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] getChar

2008-03-25 Thread Cetin Sert
Hi,

is there a version of getChar that doesn't buffer keyboard input until enter
is pressed?

specialReadln :: IO String
specialReadln = do c ← getChar
   if c == '#'
 then do return []
 else do cs ← specialReadln
 return (c:cs)

I want the input process to terminate when '#' or any other specific key has
been pressed.

Best Regards,
Cetin Sert
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getChar + System.Cmd.system + threads causes hangups

2006-02-20 Thread Einar Karttunen
Here is a version that works fine:


myRawSystem cmd args = do 
(inP, outP, errP, pid) <- runInteractiveProcess cmd args Nothing Nothing
hClose inP
os <- pGetContents outP
es <- pGetContents errP
ec <- waitForProcess pid
case ec of
  ExitSuccess   -> return ()
  ExitFailure e ->
  do hPutStrLn stderr ("Running process "++unwords (cmd:args)++" FAILED 
("++show e++")")
 hPutStrLn stderr os
 hPutStrLn stderr es
 hPutStrLn stderr ("Raising error...")
 fail "Running external command failed"

pGetContents h = do
mv <- newEmptyMVar
let put [] = putMVar mv []
put xs = last xs `seq` putMVar mv xs
forkIO (hGetContents h >>= put)
takeMVar mv

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] getChar + System.Cmd.system + threads causes hangups

2006-02-20 Thread Einar Karttunen
Hello

Using system or any variant of it from System.Process
seems broken in multithreaded environments. This
example will fail with and without -threaded.

When run the program will print "hello: start" and
then freeze. After pressing enter (the first getChar)
System.Cmd.system will complete, but without that
it will freeze for all eternity.

What is the best way to fix this? I could use System.Posix,
but that would lose windows portablity which is needed.


import Control.Concurrent
import System.Cmd

main = do forkIO (threadDelay 10 >> hello)
  getChar
  getChar

hello = do putStrLn "hello: start"
   system "echo hello world!"
   putStrLn "hello: done"


- Einar Karttunen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe