[Haskell-cafe] network-conduit proxy

Alexander V Vershilov alexander.vershilov at gmail.com
Fri Mar 9 23:05:13 CET 2012


Hello.

I'm not expert but first you should not use Network sockets, because everything
is included into Data.Conduit.Network, just use high level API.
Second, you should use not server inside client but client inside server:

so you can make such a code [1]:


{-# OPTIONS -Wall #-}
import Data.Conduit
import Data.Conduit.Network
import Control.Monad.IO.Class (liftIO)
import Control.Concurrent.Lifted (fork)

main::IO ()
main =
  runTCPServer (ServerSettings 5002 Nothing) $ \clientSrc clientSink -> do
    liftIO $ runTCPClient (ClientSettings 5000 "localhost") $ \serverSrc serverSink -> do
      _ <- liftIO $ fork $ runResourceT $ serverSrc $$ clientSink
      clientSrc $$ serverSink

tested and works

[1] https://gist.github.com/2008113

--
Alexander V Vershilov

Fri, Mar 09, 2012 at 05:44:29PM +0000, grant wrote
> I am trying to get a proxy working using the network-conduit package on windows.
> So I send a request to port 5002 and that gets forwarded to another port 5000 
> where I have a simple echo server running.
> 
> I made a stab at it, but get intermittent send errors after the first connection
> 
> Here is the code:
> {-# OPTIONS -Wall #-}
> import Data.Conduit
> import Data.Conduit.Network
> import Network (withSocketsDo)
> import Control.Monad.IO.Class (liftIO)
> import Control.Monad.Trans.Resource
> 
> main::IO ()
> main = 
>   withSocketsDo $ runTCPClient (ClientSettings 5000 "localhost") $ 
>     \src1 sink1 -> do
>     liftIO $ print "in tcpclient section"
>     liftIO $ withSocketsDo $ runTCPServer (ServerSettings 5002 Nothing) $ 
>       \src sink -> do
>       liftIO $ print "in tcpserver section"
>       _ <- liftIO $ runResourceT $ resourceForkIO $ do
>           src1 $$ sink 
>           return ()
>       src $$ sink1 
>         
>       
> Thanks for any help,
> Grant
>       
>         
> 
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 490 bytes
Desc: Digital signature
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120310/00d7a91b/attachment.pgp>


More information about the Haskell-Cafe mailing list