Can anyone help with the following:
   
How can you force a 'sequence' of evaluation in a function. The code listed 
below causes both prompts for numbers to be printed before you get a 
chance to enter the first number. (Are irrefutable patterns the answer !!!)

Also, how can you stop quotes being printed after a string, using printIO.


P.S What is the difference between `thenIO_` and `thenIO` 
                                   `bindIO_` and `bindIO`.

Aiden McCaughey
University of Ulster



> module Main where

> import PreludeGlaIO

> readStringIO :: IO [Char]
> readStringIO =  readChanIO stdin `bindIO` \x ->
>                 returnIO (head (lines x))

> promptInputIO :: [Char] -> IO [Char]
> promptInputIO p = printIO p   `thenIO_` 
                    readStringIO

> readIntIO :: IO Int
> readIntIO = readStringIO `bindIO` \x ->
>             returnIO (read x::Int)

> mainIO = printIO "Enter First Number : "      `thenIO_`
>          readIntIO                            `bindIO` \x ->
>          printIO "Enter Second Number : "     `thenIO_`
>          readIntIO                            `bindIO` \y ->
>          printIO (x-y)



Reply via email to