[Haskell-cafe] Do I need to roll my own?

David Leimbach leimy2k at gmail.com
Wed Mar 31 15:24:24 EDT 2010


On Wed, Mar 31, 2010 at 12:02 PM, Gregory Collins
<greg at gregorycollins.net>wrote:

> David Leimbach <leimy2k at gmail.com> writes:
>
> > to block or perhaps timeout, depending on the environment, looking for
> > "some String" on an input Handle, and it appears that iteratee works
> > in a very fixed block size.  While a fixed block size is ok, if I can
> > put back unused bytes into the enumerator somehow (I may need to put a
> > LOT back in some cases, but in the common case I will not need to put
> > any back as most expect-like scripts typically catch the last few
> > bytes of data sent before the peer is blocked waiting for a
> > response...)
>
> See IterGV from the iteratee lib:
>
>
> http://hackage.haskell.org/packages/archive/iteratee/0.3.1/doc/html/Data-Iteratee-Base.html#t%3AIterGV
>
> The second argument to the "Done" constructor is for the portion of the
> input that you didn't use. If you use the Monad instance, the unused
> input is passed on (transparently) to the next iteratee in the chain.


> If you use attoparsec-iteratee
> (
> http://hackage.haskell.org/packages/archive/attoparsec-iteratee/0.1/doc/html/Data-Attoparsec-Iteratee.html
> ),
> you could write "expect" as an attoparsec parser:
>

> ------------------------------------------------------------------------
> {-# LANGUAGE OverloadedStrings #-}
>
> import Control.Applicative
> import Control.Monad.Trans (lift)
> import Data.Attoparsec hiding (Done)
> import Data.Attoparsec.Iteratee
> import qualified Data.ByteString as S
> import Data.ByteString (ByteString)
> import Data.Iteratee
> import Data.Iteratee.IO.Fd
> import Data.Iteratee.WrappedByteString
> import Data.Word (Word8)
> import System.IO
> import System.Posix.IO
>
> expect :: (Monad m) => ByteString
>                    -> IterateeG WrappedByteString Word8 m ()
> expect s = parserToIteratee (p >> return ())
>  where
>    p = string s <|> (anyWord8 >> p)
>
>
> dialog :: (Monad m) =>
>          IterateeG WrappedByteString Word8 m a   -- ^ output end
>       -> IterateeG WrappedByteString Word8 m ()
> dialog outIter = do
>    expect "login:"
>    respond "foo\n"
>    expect "password:"
>    respond "bar\n"
>    return ()
>
>  where
>    respond s = do
>        _ <- lift $ enumPure1Chunk (WrapBS s) outIter >>= run
>        return ()
>
>
> main :: IO ()
> main = do
>    hSetBuffering stdin NoBuffering
>    hSetBuffering stdout NoBuffering
>    enumFd stdInput (dialog output) >>= run
>  where
>    output = IterateeG $ \chunk ->
>             case chunk of
>               (EOF _)            -> return $ Done () chunk
>               (Chunk (WrapBS s)) -> S.putStr s >>
>                                     hFlush stdout >>
>                                     return (Cont output Nothing)
> ------------------------------------------------------------------------
>
> Usage example:
>
>    $ awk 'BEGIN { print "login:"; fflush(); system("sleep 2"); \
>                   print "password:"; fflush(); }' | runhaskell Expect.hs
>    foo
>    bar
>
> N.B. for some reason "enumHandle" doesn't work here w.r.t buffering, had
> to go to POSIX i/o to get the proper buffering behaviour.
>
> That's pretty neat actually.  I'm going to have to incorporate timeouts
into something like that (and attoparsec-iteratee doesn't install for me for
some reason, I'll try again today).

That leads me to another question in another thread I'm about to start.

Dave



> G
> --
> Gregory Collins <greg at gregorycollins.net>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100331/1cadc9b0/attachment.html


More information about the Haskell-Cafe mailing list