[Haskell-beginners] Re: Talking betwean the parsers.
Felipe Lessa
felipe.lessa at gmail.com
Sat Jul 18 22:34:54 EDT 2009
On Sat, Jul 18, 2009 at 10:51:26PM +0000, Maciej Piechotka wrote:
] Felipe Lessa <felipe.lessa <at> gmail.com> writes:
] ] On Sat, Jul 18, 2009 at 12:40:15AM +0200, Maciej Piechotka wrote:
] ] ] I have a data structure of
] ] ] data Monad m => NntpConnection m = NntpConnection {
] ] ] input :: ByteString,
] ] ] output :: ByteString -> m ()
] ] ] }
] ] ]
] ] ] I'd like to create echo structure such that the goes to output is going
] ] ] to (lazy) input. For sure it is possible to use network and IO monad -
] ] ] is is possible to do it purely?
] ]
] ] In words, not code: you may create a Chan of strict ByteStrings.
] ] On the output side you just append all the chunks of the lazy
] ] ByteString to the Chan, or you may copy the lazy ByteString in
] ] one chunk of strict ByteString. On the input side you
] ] "getContents" and "fromChunks". Should work, I guess.
] ]
] ] --
] ] Felipe.
] ]
]
] Sorry - I don't follow:
] 1. How the output is suppose to get into input?
Via the Chan.
] 2. Why combine getContents and fromChunks if getContents is overloaded for
] ByteString?
I said getContents but I meant getChanContents :).
] 3. How to use getContents without IO - either network or posix pipe?
It's not without the IO monad, but it works without doing I/O
(e.g. networking, files) and portably.
Ok, now with (literate Haskell) code :)
> import Control.Concurrent.Chan
> import qualified Data.ByteString.Lazy.Char8 as L
>
> data NntpConnection m = NntpConnection {
> input :: L.ByteString,
> output :: L.ByteString -> m ()
> }
>
> echoConnIO :: IO (NntpConnection IO)
> echoConnIO = do
> chan <- newChan
> inputChunks <- getChanContents chan -- lazy!
> return $ NntpConnection {
> input = L.fromChunks inputChunks,
> output = mapM_ (writeChan chan) . L.toChunks }
*Main Control.Concurrent> c <- echoConnIO
*Main Control.Concurrent> forkIO $ L.putStrLn (input c)
ThreadId 65
*Main Control.Concurrent> output c $ L.pack "Hello, world!\n"
Hello, world!
Note that the input bytestring will never end because
NntpConnection doesn't have something like 'close :: m ()'. If
you want something robust you'll probably move away from
representing you input as a lazy bytestring anyway.
--
Felipe.
More information about the Beginners
mailing list