[Haskell-cafe] Questions on threads and IO

2006-08-16 Thread Creighton Hogg
Hello Haskell'rs,

I've been playing with threads and I tried to do a toy example (that used java) from a class.
When run, the program should print a prompt and accept commands just like a linux shell. It doesn't have to do anything
fancy, just spawn new threads that make system calls when commands are entered at the prompt.
The problem is that the UI doesn't work very well. It will seem fine
at first, but in order to get back a prompt you have to hit enter one
more time than you should. I've tried playing with the buffering
settings but it seems to cause the same problem no matter what. The
problem seems to be coming from calls of the form
(forkIO . system_) ls /usr/bin
Just entering this into ghci I get the same thing where I need to hit enter *again* in order to get back to the ghci prompt.
I'm sure this is something silly on my part, but it is rather confusing.

import Control.Concurrent
import System
import System.IO

main = do
 putStr 
 z - getLine
 runCommands z
 main

genWords :: Char - String - [String]
genWords c s = gwhelper c s [] []

gwhelper :: Char - String - [String] - String - [String]
gwhelper c [] acc temp = acc ++ [(reverse temp)]
gwhelper c (x:xs) acc temp | x /= c = gwhelper c xs acc (x:temp)
 | otherwise = gwhelper c xs (acc++[(reverse temp)]) []


runCommands s = mapM_ (forkIO .system_) (genWords '' s)

system_ :: String - IO ()
system_ s = do
 system s
 return ()
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Questions on threads and IO

2006-08-16 Thread Chris Kuklewicz
It looks like a stdout buffering issue, plus a 'yield' issue.  forkIO does not 
spawn OS level threads (that is forkOS) so adding a yield helps the runtime:



import Control.Concurrent
import System
import System.IO

loop = do
   putStr  
   z - getLine
   runCommands z
   yield
   loop

main = do
 hSetBuffering stdout NoBuffering
 loop

genWords :: Char - String - [String]
genWords c s = gwhelper c s [] []

gwhelper :: Char - String - [String] - String - [String]
gwhelper c [] acc temp = acc ++ [(reverse temp)]
gwhelper c (x:xs) acc temp | x /= c =  gwhelper c xs acc (x:temp)
   | otherwise = gwhelper c xs (acc++[(reverse temp)]) 
[]


runCommands s = mapM_ (forkIO . system_) (genWords '' s)

system_ :: String - IO ()
system_ [] = return ()
system_ s = do
  system s
  return ()




Creighton Hogg wrote:

Hello Haskell'rs,

I've been playing with threads and I tried to do a toy example (that 
used java) from a class.
When run, the program should print a prompt and accept commands just 
like a linux shell.  It doesn't have to do anything
fancy, just spawn new threads that make system calls when commands are 
entered at the prompt.
The problem is that the UI doesn't work very well.  It will seem fine at 
first, but in order to get back a prompt you have to hit enter one more 
time than you should.  I've tried playing with the buffering settings 
but it seems to cause the same problem no matter what.  The problem 
seems to be coming from calls of the form

(forkIO . system_) ls /usr/bin
Just entering this into ghci I get the same thing where I need to hit 
enter *again* in order to get back to the ghci prompt.

I'm sure this is something silly on my part, but it is rather confusing.

import Control.Concurrent
import System
import System.IO

main = do
   putStr 
   z - getLine
   runCommands z
   main

genWords :: Char - String - [String]
genWords c s = gwhelper c s [] []

gwhelper :: Char - String - [String] - String - [String]
gwhelper c [] acc temp = acc ++ [(reverse temp)]
gwhelper c (x:xs) acc temp | x /= c =  gwhelper c xs acc (x:temp)
   | otherwise = gwhelper c xs (acc++[(reverse 
temp)]) []



runCommands s = mapM_ (forkIO .system_) (genWords '' s)

system_ :: String - IO ()
system_ s = do
  system s
  return ()




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


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