{-# LANGUAGE CPP #-}
module Network.HaskellNet.POP3
(
connectPop3Port
, connectPop3
, connectStream
, sendCommand
, closePop3
, user
, pass
, userPass
, apop
, auth
, stat
, dele
, retr
, top
, rset
, allList
, list
, allUIDLs
, uidl
, doPop3Port
, doPop3
, doPop3Stream
, A.AuthType(..)
)
where
import Network.HaskellNet.BSStream
import Network.Socket
import Network.Compat
import qualified Network.HaskellNet.Auth as A
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BS
import Crypto.Hash.MD5
import Numeric (showHex)
import Control.Applicative
import Control.Exception
import Control.Monad (when, unless)
import Data.List
import Data.Char (isSpace, isControl)
import System.IO
import Prelude
import Network.HaskellNet.POP3.Types
import Network.HaskellNet.POP3.Connection
hexDigest :: [Char] -> [Char]
hexDigest :: [Char] -> [Char]
hexDigest = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. (Integral a, Show a) => a -> [Char] -> [Char]
showHex [Char]
"") forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
B.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
hash forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
B.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a. Enum a => Int -> a
toEnumforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall a. Enum a => a -> Int
fromEnum)
blank :: Char -> Bool
blank :: Char -> Bool
blank Char
a = Char -> Bool
isSpace Char
a Bool -> Bool -> Bool
|| Char -> Bool
isControl Char
a
trimR :: ByteString -> ByteString
trimR :: ByteString -> ByteString
trimR ByteString
s = let rs :: ByteString
rs = ByteString -> ByteString
BS.reverse ByteString
s in
(Char -> Bool) -> ByteString -> ByteString
BS.dropWhile Char -> Bool
blank ByteString
rs
strip :: ByteString -> ByteString
strip :: ByteString -> ByteString
strip = ByteString -> ByteString
trimR forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
trimR
stripEnd :: ByteString -> ByteString
stripEnd :: ByteString -> ByteString
stripEnd = ByteString -> ByteString
BS.reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
trimR
connectPop3Port :: String -> PortNumber -> IO POP3Connection
connectPop3Port :: [Char] -> PortNumber -> IO POP3Connection
connectPop3Port [Char]
hostname PortNumber
port =
Handle -> BSStream
handleToStream forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Char] -> PortNumber -> IO Handle
connectTo [Char]
hostname PortNumber
port)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= BSStream -> IO POP3Connection
connectStream
connectPop3 :: String -> IO POP3Connection
connectPop3 :: [Char] -> IO POP3Connection
connectPop3 = forall a b c. (a -> b -> c) -> b -> a -> c
flip [Char] -> PortNumber -> IO POP3Connection
connectPop3Port PortNumber
110
connectStream :: BSStream -> IO POP3Connection
connectStream :: BSStream -> IO POP3Connection
connectStream BSStream
st =
do (Response
resp, ByteString
msg) <- BSStream -> IO (Response, ByteString)
response BSStream
st
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot connect"
let code :: ByteString
code = forall a. [a] -> a
last forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BS.words ByteString
msg
if ByteString -> Char
BS.head ByteString
code forall a. Eq a => a -> a -> Bool
== Char
'<' Bool -> Bool -> Bool
&& ByteString -> Char
BS.last ByteString
code forall a. Eq a => a -> a -> Bool
== Char
'>'
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ BSStream -> [Char] -> POP3Connection
newConnection BSStream
st (ByteString -> [Char]
BS.unpack ByteString
code)
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ BSStream -> [Char] -> POP3Connection
newConnection BSStream
st [Char]
""
response :: BSStream -> IO (Response, ByteString)
response :: BSStream -> IO (Response, ByteString)
response BSStream
st =
do ByteString
reply <- ByteString -> ByteString
strip forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BSStream -> IO ByteString
bsGetLine BSStream
st
if ([Char] -> ByteString
BS.pack [Char]
"+OK") ByteString -> ByteString -> Bool
`BS.isPrefixOf` ByteString
reply
then forall (m :: * -> *) a. Monad m => a -> m a
return (Response
Ok, Int -> ByteString -> ByteString
BS.drop Int
4 ByteString
reply)
else forall (m :: * -> *) a. Monad m => a -> m a
return (Response
Err, Int -> ByteString -> ByteString
BS.drop Int
5 ByteString
reply)
responseML :: POP3Connection -> IO (Response, ByteString)
responseML :: POP3Connection -> IO (Response, ByteString)
responseML POP3Connection
conn =
do ByteString
reply <- ByteString -> ByteString
strip forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BSStream -> IO ByteString
bsGetLine BSStream
st
if ([Char] -> ByteString
BS.pack [Char]
"+OK") ByteString -> ByteString -> Bool
`BS.isPrefixOf` ByteString
reply
then do [ByteString]
rest <- IO [ByteString]
getRest
forall (m :: * -> *) a. Monad m => a -> m a
return (Response
Ok, [ByteString] -> ByteString
BS.unlines (Int -> ByteString -> ByteString
BS.drop Int
4 ByteString
reply forall a. a -> [a] -> [a]
: [ByteString]
rest))
else forall (m :: * -> *) a. Monad m => a -> m a
return (Response
Err, Int -> ByteString -> ByteString
BS.drop Int
5 ByteString
reply)
where st :: BSStream
st = POP3Connection -> BSStream
stream POP3Connection
conn
getRest :: IO [ByteString]
getRest = do ByteString
l <- ByteString -> ByteString
stripEnd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BSStream -> IO ByteString
bsGetLine BSStream
st
if ByteString
l forall a. Eq a => a -> a -> Bool
== Char -> ByteString
BS.singleton Char
'.'
then forall (m :: * -> *) a. Monad m => a -> m a
return []
else (ByteString
lforall a. a -> [a] -> [a]
:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [ByteString]
getRest
sendCommand :: POP3Connection -> Command -> IO (Response, ByteString)
sendCommand :: POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn (LIST Maybe Int
Nothing) =
BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) ([Char] -> ByteString
BS.pack [Char]
"LIST") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> POP3Connection -> IO (Response, ByteString)
responseML POP3Connection
conn
sendCommand POP3Connection
conn (UIDL Maybe Int
Nothing) =
BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) ([Char] -> ByteString
BS.pack [Char]
"UIDL") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> POP3Connection -> IO (Response, ByteString)
responseML POP3Connection
conn
sendCommand POP3Connection
conn (RETR Int
msg) =
BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) ([Char] -> ByteString
BS.pack forall a b. (a -> b) -> a -> b
$ [Char]
"RETR " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Int
msg) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> POP3Connection -> IO (Response, ByteString)
responseML POP3Connection
conn
sendCommand POP3Connection
conn (TOP Int
msg Int
n) =
BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) ([Char] -> ByteString
BS.pack forall a b. (a -> b) -> a -> b
$ [Char]
"TOP " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Int
msg forall a. [a] -> [a] -> [a]
++ [Char]
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Int
n) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
POP3Connection -> IO (Response, ByteString)
responseML POP3Connection
conn
sendCommand POP3Connection
conn (AUTH AuthType
A.LOGIN [Char]
username [Char]
password) =
do BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) forall a b. (a -> b) -> a -> b
$ [Char] -> ByteString
BS.pack [Char]
"AUTH LOGIN"
BSStream -> IO ByteString
bsGetLine (POP3Connection -> BSStream
stream POP3Connection
conn)
BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) forall a b. (a -> b) -> a -> b
$ [Char] -> ByteString
BS.pack [Char]
userB64
BSStream -> IO ByteString
bsGetLine (POP3Connection -> BSStream
stream POP3Connection
conn)
BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) forall a b. (a -> b) -> a -> b
$ [Char] -> ByteString
BS.pack [Char]
passB64
BSStream -> IO (Response, ByteString)
response (POP3Connection -> BSStream
stream POP3Connection
conn)
where ([Char]
userB64, [Char]
passB64) = [Char] -> [Char] -> ([Char], [Char])
A.login [Char]
username [Char]
password
sendCommand POP3Connection
conn (AUTH AuthType
at [Char]
username [Char]
password) =
do BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) forall a b. (a -> b) -> a -> b
$ [Char] -> ByteString
BS.pack forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char]
unwords [[Char]
"AUTH", forall a. Show a => a -> [Char]
show AuthType
at]
ByteString
c <- BSStream -> IO ByteString
bsGetLine (POP3Connection -> BSStream
stream POP3Connection
conn)
let challenge :: [Char]
challenge =
if Int -> ByteString -> ByteString
BS.take Int
2 ByteString
c forall a. Eq a => a -> a -> Bool
== [Char] -> ByteString
BS.pack [Char]
"+ "
then [Char] -> [Char]
A.b64Decode forall a b. (a -> b) -> a -> b
$ ByteString -> [Char]
BS.unpack forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Bool
isSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Char
BS.last) forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BS.inits forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
BS.drop Int
2 ByteString
c
else [Char]
""
BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) forall a b. (a -> b) -> a -> b
$ [Char] -> ByteString
BS.pack forall a b. (a -> b) -> a -> b
$ AuthType -> [Char] -> [Char] -> [Char] -> [Char]
A.auth AuthType
at [Char]
challenge [Char]
username [Char]
password
BSStream -> IO (Response, ByteString)
response (POP3Connection -> BSStream
stream POP3Connection
conn)
sendCommand POP3Connection
conn Command
command =
BSStream -> ByteString -> IO ()
bsPutCrLf (POP3Connection -> BSStream
stream POP3Connection
conn) ([Char] -> ByteString
BS.pack [Char]
commandStr) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BSStream -> IO (Response, ByteString)
response (POP3Connection -> BSStream
stream POP3Connection
conn)
where commandStr :: [Char]
commandStr = case Command
command of
(USER [Char]
name) -> [Char]
"USER " forall a. [a] -> [a] -> [a]
++ [Char]
name
(PASS [Char]
passw) -> [Char]
"PASS " forall a. [a] -> [a] -> [a]
++ [Char]
passw
Command
NOOP -> [Char]
"NOOP"
Command
QUIT -> [Char]
"QUIT"
Command
STAT -> [Char]
"STAT"
(DELE Int
msg) -> [Char]
"DELE " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Int
msg
Command
RSET -> [Char]
"RSET"
(LIST Maybe Int
msg) -> [Char]
"LIST " forall a. [a] -> [a] -> [a]
++ forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" forall a. Show a => a -> [Char]
show Maybe Int
msg
(UIDL Maybe Int
msg) -> [Char]
"UIDL " forall a. [a] -> [a] -> [a]
++ forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" forall a. Show a => a -> [Char]
show Maybe Int
msg
(APOP [Char]
usern [Char]
passw) -> [Char]
"APOP " forall a. [a] -> [a] -> [a]
++ [Char]
usern forall a. [a] -> [a] -> [a]
++ [Char]
" " forall a. [a] -> [a] -> [a]
++
[Char] -> [Char]
hexDigest (POP3Connection -> [Char]
apopKey POP3Connection
conn forall a. [a] -> [a] -> [a]
++ [Char]
passw)
(AUTH AuthType
_ [Char]
_ [Char]
_) -> forall a. HasCallStack => [Char] -> a
error [Char]
"BUG: AUTH should not get matched here"
(RETR Int
_) -> forall a. HasCallStack => [Char] -> a
error [Char]
"BUG: RETR should not get matched here"
(TOP Int
_ Int
_) -> forall a. HasCallStack => [Char] -> a
error [Char]
"BUG: TOP should not get matched here"
user :: POP3Connection -> String -> IO ()
user :: POP3Connection -> [Char] -> IO ()
user POP3Connection
conn [Char]
name = do (Response
resp, ByteString
_) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn ([Char] -> Command
USER [Char]
name)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot send user name"
pass :: POP3Connection -> String -> IO ()
pass :: POP3Connection -> [Char] -> IO ()
pass POP3Connection
conn [Char]
pwd = do (Response
resp, ByteString
_) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn ([Char] -> Command
PASS [Char]
pwd)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot send password"
userPass :: POP3Connection -> A.UserName -> A.Password -> IO ()
userPass :: POP3Connection -> [Char] -> [Char] -> IO ()
userPass POP3Connection
conn [Char]
name [Char]
pwd = POP3Connection -> [Char] -> IO ()
user POP3Connection
conn [Char]
name forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> POP3Connection -> [Char] -> IO ()
pass POP3Connection
conn [Char]
pwd
auth :: POP3Connection -> A.AuthType -> A.UserName -> A.Password
-> IO ()
auth :: POP3Connection -> AuthType -> [Char] -> [Char] -> IO ()
auth POP3Connection
conn AuthType
at [Char]
username [Char]
password =
do (Response
resp, ByteString
msg) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn (AuthType -> [Char] -> [Char] -> Command
AUTH AuthType
at [Char]
username [Char]
password)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Ok) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"authentication failed: " forall a. [a] -> [a] -> [a]
++ ByteString -> [Char]
BS.unpack ByteString
msg
apop :: POP3Connection -> String -> String -> IO ()
apop :: POP3Connection -> [Char] -> [Char] -> IO ()
apop POP3Connection
conn [Char]
name [Char]
pwd =
do (Response
resp, ByteString
msg) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn ([Char] -> [Char] -> Command
APOP [Char]
name [Char]
pwd)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"authentication failed: " forall a. [a] -> [a] -> [a]
++ ByteString -> [Char]
BS.unpack ByteString
msg
stat :: POP3Connection -> IO (Int, Int)
stat :: POP3Connection -> IO (Int, Int)
stat POP3Connection
conn = do (Response
resp, ByteString
msg) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn Command
STAT
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot get stat info"
let (ByteString
nn, ByteString
mm) = (Char -> Bool) -> ByteString -> (ByteString, ByteString)
BS.span (forall a. Eq a => a -> a -> Bool
/=Char
' ') ByteString
msg
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Read a => [Char] -> a
read forall a b. (a -> b) -> a -> b
$ ByteString -> [Char]
BS.unpack ByteString
nn, forall a. Read a => [Char] -> a
read forall a b. (a -> b) -> a -> b
$ ByteString -> [Char]
BS.unpack forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> ByteString
BS.tail ByteString
mm)
dele :: POP3Connection -> Int -> IO ()
dele :: POP3Connection -> Int -> IO ()
dele POP3Connection
conn Int
n = do (Response
resp, ByteString
_) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn (Int -> Command
DELE Int
n)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot delete"
retr :: POP3Connection -> Int -> IO ByteString
retr :: POP3Connection -> Int -> IO ByteString
retr POP3Connection
conn Int
n = do (Response
resp, ByteString
msg) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn (Int -> Command
RETR Int
n)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot retrieve"
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> ByteString
BS.tail forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ByteString -> ByteString
BS.dropWhile (forall a. Eq a => a -> a -> Bool
/=Char
'\n') ByteString
msg
top :: POP3Connection -> Int -> Int -> IO ByteString
top :: POP3Connection -> Int -> Int -> IO ByteString
top POP3Connection
conn Int
n Int
m = do (Response
resp, ByteString
msg) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn (Int -> Int -> Command
TOP Int
n Int
m)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot retrieve"
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> ByteString
BS.tail forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ByteString -> ByteString
BS.dropWhile (forall a. Eq a => a -> a -> Bool
/=Char
'\n') ByteString
msg
rset :: POP3Connection -> IO ()
rset :: POP3Connection -> IO ()
rset POP3Connection
conn = do (Response
resp, ByteString
_) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn Command
RSET
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot reset"
allList :: POP3Connection -> IO [(Int, Int)]
allList :: POP3Connection -> IO [(Int, Int)]
allList POP3Connection
conn = do (Response
resp, ByteString
lst) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn (Maybe Int -> Command
LIST forall a. Maybe a
Nothing)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot retrieve the list"
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall {a} {b}. (Read a, Read b) => ByteString -> (a, b)
f forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
tail forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BS.lines ByteString
lst
where f :: ByteString -> (a, b)
f ByteString
s = let (ByteString
n1, ByteString
n2) = (Char -> Bool) -> ByteString -> (ByteString, ByteString)
BS.span (forall a. Eq a => a -> a -> Bool
/=Char
' ') ByteString
s
in (forall a. Read a => [Char] -> a
read forall a b. (a -> b) -> a -> b
$ ByteString -> [Char]
BS.unpack ByteString
n1, forall a. Read a => [Char] -> a
read forall a b. (a -> b) -> a -> b
$ ByteString -> [Char]
BS.unpack forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> ByteString
BS.tail ByteString
n2)
list :: POP3Connection -> Int -> IO Int
list :: POP3Connection -> Int -> IO Int
list POP3Connection
conn Int
n = do (Response
resp, ByteString
lst) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn (Maybe Int -> Command
LIST (forall a. a -> Maybe a
Just Int
n))
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot retrieve the list"
let (ByteString
_, ByteString
n2) = (Char -> Bool) -> ByteString -> (ByteString, ByteString)
BS.span (forall a. Eq a => a -> a -> Bool
/=Char
' ') ByteString
lst
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Read a => [Char] -> a
read forall a b. (a -> b) -> a -> b
$ ByteString -> [Char]
BS.unpack forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> ByteString
BS.tail ByteString
n2
allUIDLs :: POP3Connection -> IO [(Int, ByteString)]
allUIDLs :: POP3Connection -> IO [(Int, ByteString)]
allUIDLs POP3Connection
conn = do (Response
resp, ByteString
lst) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn (Maybe Int -> Command
UIDL forall a. Maybe a
Nothing)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot retrieve the uidl list"
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall {a}. Read a => ByteString -> (a, ByteString)
f forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
tail forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BS.lines ByteString
lst
where f :: ByteString -> (a, ByteString)
f ByteString
s = let (ByteString
n1, ByteString
n2) = (Char -> Bool) -> ByteString -> (ByteString, ByteString)
BS.span (forall a. Eq a => a -> a -> Bool
/=Char
' ') ByteString
s in (forall a. Read a => [Char] -> a
read forall a b. (a -> b) -> a -> b
$ ByteString -> [Char]
BS.unpack ByteString
n1, ByteString
n2)
uidl :: POP3Connection -> Int -> IO ByteString
uidl :: POP3Connection -> Int -> IO ByteString
uidl POP3Connection
conn Int
n = do (Response
resp, ByteString
msg) <- POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
conn (Maybe Int -> Command
UIDL (forall a. a -> Maybe a
Just Int
n))
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Response
resp forall a. Eq a => a -> a -> Bool
== Response
Err) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"cannot retrieve the uidl data"
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> ByteString
BS.tail forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ByteString -> ByteString
BS.dropWhile (forall a. Eq a => a -> a -> Bool
/=Char
' ') ByteString
msg
closePop3 :: POP3Connection -> IO ()
closePop3 :: POP3Connection -> IO ()
closePop3 POP3Connection
c = do POP3Connection -> Command -> IO (Response, ByteString)
sendCommand POP3Connection
c Command
QUIT
BSStream -> IO ()
bsClose (POP3Connection -> BSStream
stream POP3Connection
c)
doPop3Port :: String -> PortNumber -> (POP3Connection -> IO a) -> IO a
doPop3Port :: forall a. [Char] -> PortNumber -> (POP3Connection -> IO a) -> IO a
doPop3Port [Char]
host PortNumber
port POP3Connection -> IO a
execution =
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket ([Char] -> PortNumber -> IO POP3Connection
connectPop3Port [Char]
host PortNumber
port) POP3Connection -> IO ()
closePop3 POP3Connection -> IO a
execution
doPop3 :: String -> (POP3Connection -> IO a) -> IO a
doPop3 :: forall a. [Char] -> (POP3Connection -> IO a) -> IO a
doPop3 [Char]
host POP3Connection -> IO a
execution = forall a. [Char] -> PortNumber -> (POP3Connection -> IO a) -> IO a
doPop3Port [Char]
host PortNumber
110 POP3Connection -> IO a
execution
doPop3Stream :: BSStream -> (POP3Connection -> IO b) -> IO b
doPop3Stream :: forall b. BSStream -> (POP3Connection -> IO b) -> IO b
doPop3Stream BSStream
conn POP3Connection -> IO b
execution = forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (BSStream -> IO POP3Connection
connectStream BSStream
conn) POP3Connection -> IO ()
closePop3 POP3Connection -> IO b
execution
crlf :: BS.ByteString
crlf :: ByteString
crlf = [Char] -> ByteString
BS.pack [Char]
"\r\n"
bsPutCrLf :: BSStream -> ByteString -> IO ()
bsPutCrLf :: BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
h ByteString
s = BSStream -> ByteString -> IO ()
bsPut BSStream
h ByteString
s forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BSStream -> ByteString -> IO ()
bsPut BSStream
h ByteString
crlf forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BSStream -> IO ()
bsFlush BSStream
h