[Haskell-beginners] Network client - reading and writing to a socket

Manfred Lotz manfred.lotz at arcor.de
Sun Jul 31 17:39:48 CEST 2011


Hi there,
I'm trying to write a network client which connects to an IMAP server
thus reading from and writing to socket 143.

I have an initial solution which works except that laziness bites me.
Perhaps the whole solution using connectTo and handle is the wrong
approach.

Here is the code:


module Main where

import System.IO
import qualified Data.ByteString.Char8 as B
import Network


server :: String
server = "127.0.0.1"
port :: PortID
port = PortNumber 143


sendMsg :: Handle -> String -> IO ()
sendMsg h m = do
  putStrLn ("Sending command: " ++ m) 
  B.hPutStrLn h (B.pack m) >> hFlush h


recvMsg :: Handle -> IO B.ByteString 
recvMsg h = do
  c <- B.hGet h 1
  c' <- B.hGetNonBlocking h 40000 
  return $ B.concat [c,c']

  
  
main :: IO ()
main = withSocketsDo $ do
  h <- connectTo server port
  hSetBuffering h LineBuffering
  imapDialog h 


imapDialog :: Handle -> IO ()
imapDialog h = do
  greet <- recvMsg h 
  B.putStrLn greet

  sendMsg h "1 LOGIN manfred \"password\""
  resp <- recvMsg h 
  B.putStrLn resp

  sendMsg h "2 SELECT HAM-learn"
  resp1 <- recvMsg h
  B.putStrLn resp1

  sendMsg h "3 FETCH 1:* (uid flags internaldate body[header.fields
  (Message-Id)])" 
  resp2 <- recvMsg h
  B.putStrLn resp2

  sendMsg h "4 FETCH 1 (rfc822)"
  resp3 <- recvMsg h
  B.putStrLn resp3 


The problem is that the message itself is some 30K big and I only
get some 16K of the message. 

How could I force to get the whole message?

 

-- 
Manfred





More information about the Beginners mailing list