[Haskell-cafe] Re: Unexpected results with simple IO
Emil Axelsson
emax at cs.chalmers.se
Mon Feb 20 02:59:17 EST 2006
What version of GHC are you using?
Your code works for me in rxvt in Cygwin, with GHC 6.4.1. But I remember having
that same problem earlier (in some earlier GHC version, so it may be fixed by now).
The solution was to run hFlush after each putStr, like so:
import System.IO (hFlush, stdout)
do putStr "..."
hHlush stdout
...
If I remember correctly, the problem only occurred in GHCi and Hugs -- not when
compiling the code.
/ Emil
Maurício skrev:
> You're right... I was running the example in rxvt, in cygwin. Now I
> tried in Windows command shell and it works.
>
> Thanks,
> Maurício
>
> Cale Gibbard wrote:
>> That doesn't happen for me at all, it works just fine. Maybe it's
>> something wrong with your terminal? You could possibly try playing
>> with the buffering settings on stdout, using hSetBuffering in
>> System.IO.
>>
>> - Cale
>>
>> On 17/02/06, Maurício <briqueabraque at yahoo.com> wrote:
>>
>>> Dear Haskell users,
>>>
>>> I have a problem using IO. The small test program below asks the user
>>> to guess from a list of random numbers between 1 and 10. Everything
>>> works well excepts for one problem: all the messages ("Guess a
>>> number...", "Right..." and "Wrong...") are printed after the program
>>> finishes, i.e., I have to use it blind. I'm afraid I misunderstand
>>> something important about lazyness or monads... What am I doing wrong?
>>>
>>> Thanks,
>>> Maurício
>>>
>>> module Main where
>>> import Random
>>>
>>> main = do
>>> r_gen <- getStdGen --random generator
>>> let r_list = (randomRs (1,10) r_gen) --random list
>>> guess_loop (r_list)
>>>
>>> guess_loop (r:r_others) = do
>>> putStrLn "Guess a number between 1 and 10:"
>>> n <- readLn
>>> if n==r
>>> then do
>>> putStrLn "Right! :)"
>>> return ()
>>> else do
>>> putStrLn "Wrong... :("
>>> guess_loop r_others
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list