Re: [Haskell-cafe] Re: `Expect'-like lazy reading/Parsec matching on TCP sockets

2007-04-16 Thread Ian Lynagh

Hi Scott,

On Mon, Apr 09, 2007 at 10:03:55AM -0600, Scott Bell wrote:
 Have you got a complete (but preferably small) program showing the
 problem?

Great example, thanks!

Sorry for the delay in tracking it down.

 main :: IO ()
 main = do (_, h, _, p) - runInteractiveCommand telnet nyx.nyx.net
  t - hGetContentsTimeout h 15000
  print t  terminateProcess p

The input handle is being garbage collected and closed, so telnet is
exiting. Try:

main :: IO ()
main = do (hin, h, _, p) - runInteractiveCommand telnet nyx.nyx.net
 t - hGetContentsTimeout h 15000
 print t
 hClose hin
 terminateProcess p

Note that you can't do either the hClose or terminateProcess before you
have forced the whole string (which print does here). You might prefer
to pass hin and p to hGetContentsTimeout, and have it close/terminate
them just before the return .

 hGetContentsTimeout :: Handle - Int - IO String
 hGetContentsTimeout h t = do
  hSetBuffering stdin NoBuffering
  ready - hWaitForInput h t; eof - hIsEOF h  

You'll also need to remove the hIsEOF call from your code, or having
decided that nothing is ready it will then block, waiting to see if
there is an end of file or not.


Thanks
Ian

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


Re: [Haskell-cafe] Re: `Expect'-like lazy reading/Parsec matching on TCP sockets

2007-04-09 Thread Scott Bell

Have you got a complete (but preferably small) program showing the
problem?


Ian,

Here is the source and behavior that I'm seeing (Linux x86, under both
6.6 and 6.7-20070404:

module Main where

import System.IO
import System.IO.Unsafe
import System.Process
import Text.ParserCombinators.Parsec

main :: IO ()
main = do (_, h, _, p) - runInteractiveCommand telnet nyx.nyx.net
 t - hGetContentsTimeout h 15000
 print t  terminateProcess p

hGetContentsTimeout :: Handle - Int - IO String
hGetContentsTimeout h t = do
 hSetBuffering stdin NoBuffering
 ready - hWaitForInput h t; eof - hIsEOF h  
 if ((not ready) || eof) then return []
   else do c - hGetChar h
   s - unsafeInterleaveIO (hGetContentsTimeout h t)
   return (c:s)


-- Behavior with threaded RTS, string is returned early because of EOF:
[EMAIL PROTECTED]:~/src/remote$ ghc --make Remote.hs -o remote -threaded
[1 of 1] Compiling Main ( Remote.hs, Remote.o )
Linking remote ...
[EMAIL PROTECTED]:~/src/remote$ ./remote
Trying 206.124.29.1...\nConnected to nyx.nyx.net.\nEscape character is '^]'.\n

-- Behavior with non-threaded RTS, proper timeout is observed:
[EMAIL PROTECTED]:~/src/remote$ ./remote
Trying 206.124.29.1...\nConnected to nyx.nyx.net.\nEscape character
is '^]'.\n\n\n   Welcome to Nyx, The Spirit of the
Night\n(303) 409-1401\n
   nyx.nyx.net -- 206.124.29.1\n
nyx10.nyx.net -- 206.124.29.2\n\n Free Public
Internet Access\n\n
===\n  New user?
Login as new\n ===\n\n
 (If you get timed out, try later.  Nyx would be too slow to
use.)\n\n\n\n\r\n\r\nSunOS UNIX (nyx)\r\n\r\r\n\rlogin: 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: `Expect'-like lazy reading/Parsec matching on TCP sockets

2007-04-07 Thread Scott Bell

 you should write compiler version and OS for such problems.

Of course, this was 6.7-20070404 on Linux x86. I haven't had a
change to test it on my 6.6 build.

 I/O in Windows threaded RTS was fixed after initial 6.6 release and
 afaik hWaitForInput should work better now. alternatively, you can  
try

 with hand-made timeout solution

I'm not sure what the status is on hWaitForInput with the snapshot
that I am using -- any other ideas what I could try to further isolate
the problem?

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


Re: [Haskell-cafe] Re: `Expect'-like lazy reading/Parsec matching on TCP sockets

2007-04-07 Thread Ian Lynagh
On Fri, Apr 06, 2007 at 01:44:01PM -0600, Scott Bell wrote:
 Ooops! It seems that this doesn't behave well with a -threaded
 RTS. I get an EOF on handles that I know for a fact shouldn't
 be receiving them. It still works well without -threaded, but
 does anyone know why I'm getting this behavior?
 
 hGetContentsTimeout :: Handle - Int - IO String
 hGetContentsTimeout h t = do
   hSetBuffering stdin NoBuffering
   ready - hWaitForInput h t
   if (not ready) then return []
 else do
   c - hGetChar h
   s - unsafeInterleaveIO (hGetContentsTimeout h t)
   return (c:s)
 
 (I did add EOF checking, but all that did was return the end of the  
 list earlier than I wanted)

Have you got a complete (but preferably small) program showing the
problem?


Thanks
Ian

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


[Haskell-cafe] Re: `Expect'-like lazy reading/Parsec matching on TCP sockets

2007-04-06 Thread Scott Bell

Ooops! It seems that this doesn't behave well with a -threaded
RTS. I get an EOF on handles that I know for a fact shouldn't
be receiving them. It still works well without -threaded, but
does anyone know why I'm getting this behavior?

hGetContentsTimeout :: Handle - Int - IO String
hGetContentsTimeout h t = do
  hSetBuffering stdin NoBuffering
  ready - hWaitForInput h t
  if (not ready) then return []
else do
  c - hGetChar h
  s - unsafeInterleaveIO (hGetContentsTimeout h t)
  return (c:s)

(I did add EOF checking, but all that did was return the end of the  
list earlier than I wanted)___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: `Expect'-like lazy reading/Parsec matching on TCP sockets

2007-04-06 Thread Bulat Ziganshin
Hello Scott,

Friday, April 6, 2007, 11:44:01 PM, you wrote:

you should write compiler version and OS for such problems. if it's
6.6 and Win, try to upgrade to current STABLE build: smth like
http://www.haskell.org/ghc/dist/stable/dist/ghc-6.6.20061207-i386-unknown-mingw32.tar.gz
but newer (this one is dec 12 build)

I/O in Windows threaded RTS was fixed after initial 6.6 release and
afaik hWaitForInput should work better now. alternatively, you can try
with hand-made timeout solution

 Ooops! It seems that this doesn't behave well with a -threaded
 RTS. I get an EOF on handles that I know for a fact shouldn't
 be receiving them. It still works well without -threaded, but
 does anyone know why I'm getting this behavior?

 hGetContentsTimeout :: Handle - Int - IO String
 hGetContentsTimeout h t = do
   hSetBuffering stdin NoBuffering
   ready - hWaitForInput h t
   if (not ready) then return []
     else do
       c - hGetChar h
       s - unsafeInterleaveIO (hGetContentsTimeout h t)
       return (c:s)

 (I did add EOF checking, but all that did was return the end of the list 
 earlier than I wanted)

  


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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