Again, sorry this doesn't help too much on Windows, but your test1 runs just fine on Mac OSX in both GHC and Hugs98. I changed the device to suit, but otherwise it was unchanged.

hIsWritable reports True on Hugs98 but False on GHCi, curiously.


On Windows, in Hugs98, I get a different error message


Program error: <handle>: IO.hGetChar: permission denied

but this changed to the same error message as yours when I started experimenting with the mode setting. Nothing I've tried seems to allow this to work. If you don't send first and only read, then it works fine.

On Windows GHCi, I can only agree with your findings.



At 13:32 23/03/2004 +1030, Peter Pudney wrote:
Thanks, Steve and Axel, for your help. I have got serial port IO working, but
the solution is a bit ugly. My solution (below) works on Windows 2000, Hugs Nov
2003. It does not work with Windows 2000, GHI 5.04.2. Later tonight I will try
it on Windows ME with the latest versions of GHC and Hugs.


The aim is to send a '?' character to a device on the serial port "COM2:". The
device waits for a button to be pressed, then sends back a character. The test
script then has to read this character from the serial port and display it.

I first tried opening "COM2:" in ReadWriteMode, but this did not work with
either GHCi or Hugs. For my second attempt, I open and close the file "COM2:"
in the appropriate mode each time I send or receive a string. Its ugly, but it
works.

I am still interested in hearing from anyone who can get this working nicely
with GHC.

My code is below.



> module SerialIO where

> import IO


Attempt 1:


>  test1 :: IO ()
>  test1
>    = do
>        com2 <- openFile "COM2:" ReadWriteMode
>        hSetBuffering com2 NoBuffering
>        isOpen <- hIsOpen com2
>        isWritable <- hIsWritable com2
>        isReadable <- hIsReadable com2
>        putStrLn $ "hIsOpen = " ++ show isOpen
>        putStrLn $ "hIsWritable = " ++ show isWritable
>        putStrLn $ "hIsReadable = " ++ show isReadable
>        putStrLn "About to send..."
>        hPutStrLn com2 "?"
>        putStrLn "Reading..."
>        c <- hGetChar com2
>        putStrLn [c]
>        putStrLn "Hoorah!"
>        hClose com2

Hugs Nov 2003 sends the character OK, but then...

Reading...

Program error: <handle>: IO.hGetChar: does not exist (file does not exist)


GHCI 5.04.2 gives hIsWritable = False, then "No such file or directory" when it
attempts to hPutChar.




Attempt 2: open and close COM2 for each transmission

>  test2 :: IO ()
>  test2
>    = do
>        sendChar '?'
>        c <- receiveChar
>        putStrLn [c]

>  sendChar :: Char -> IO ()
>  sendChar c
>    = do
>        com2 <- openFile "COM2:" WriteMode
>        hSetBuffering com2 NoBuffering
>        hPutChar com2 '?'
>        hClose com2

>  receiveChar :: IO Char
>  receiveChar
>    = do
>        com2 <- openFile "COM2:" ReadMode
>        hSetBuffering com2 NoBuffering
>        c <- hGetChar com2
>        return c


GHCI fails as before, but Hugs works.

_______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Reply via email to