HaskellNet-0.2.2: network related libraries such as POP3, SMTP, IMAPSource codeContentsIndex
Text.IMAPParsers
Portabilityportable
Stabilitystable
Maintainermukai@jmuk.org
Description
Parsers for IMAP server responses
Synopsis
type Mailbox = String
type UID = Word64
type Charset = String
data MailboxInfo = MboxInfo {
_mailbox :: Mailbox
_exists :: Integer
_recent :: Integer
_flags :: [Flag]
_permanentFlags :: [Flag]
_isWritable :: Bool
_isFlagWritable :: Bool
_uidNext :: UID
_uidValidity :: UID
}
data Flag
= Seen
| Answered
| Flagged
| Deleted
| Draft
| Recent
| Keyword String
data Attribute
= Noinferiors
| Noselect
| Marked
| Unmarked
| OtherAttr String
data MboxUpdate = MboxUpdate {
exists :: Maybe Integer
recent :: Maybe Integer
}
data StatusCode
= ALERT
| BADCHARSET [Charset]
| CAPABILITY_sc [String]
| PARSE
| PERMANENTFLAGS [Flag]
| READ_ONLY
| READ_WRITE
| TRYCREATE
| UIDNEXT_sc UID
| UIDVALIDITY_sc UID
| UNSEEN_sc Integer
data ServerResponse
= OK (Maybe StatusCode) String
| NO (Maybe StatusCode) String
| BAD (Maybe StatusCode) String
| PREAUTH (Maybe StatusCode) String
data MailboxStatus
= MESSAGES
| RECENT
| UIDNEXT
| UIDVALIDITY
data RespDerivs = RespDerivs {
dvFlags :: Result RespDerivs [Flag]
advTag :: Result RespDerivs String
advChar :: Result RespDerivs Char
advPos :: Pos
}
eval :: (RespDerivs -> Result RespDerivs r) -> String -> ByteString -> r
parse :: String -> Pos -> ByteString -> RespDerivs
eval' :: (RespDerivs -> Result RespDerivs r) -> String -> String -> r
parse' :: String -> Pos -> String -> RespDerivs
pNone :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, ())
pCapability :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [String])
pList :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [([Attribute], String, Mailbox)])
pLsub :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [([Attribute], String, Mailbox)])
pStatus :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [(MailboxStatus, Integer)])
pExpunge :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [Integer])
pSearch :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [UID])
pSelect :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, MailboxInfo)
pFetch :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [(Integer, [(String, String)])])
pDone :: RespDerivs -> Result RespDerivs ServerResponse
pFlag :: Parser RespDerivs Flag
pParenFlags :: RespDerivs -> Result RespDerivs [Flag]
atomChar :: Derivs d => Parser d Char
pNumberedLine :: String -> Parser RespDerivs Integer
pRecentLine :: Parser RespDerivs Integer
pExpungeLine :: Parser RespDerivs Integer
pExistsLine :: Parser RespDerivs Integer
pOtherLine :: Parser RespDerivs (Either (String, Integer) b)
pCapabilityLine :: Parser RespDerivs (Either a [String])
pListLine :: String -> Parser RespDerivs (Either a ([Attribute], String, Mailbox))
pStatusLine :: Parser RespDerivs (Either a [(MailboxStatus, Integer)])
pSearchLine :: Parser RespDerivs (Either a [UID])
pSelectLine :: Parser RespDerivs (MailboxInfo -> MailboxInfo)
pFetchLine :: Parser RespDerivs (Either a (Integer, [(String, String)]))
crlf :: String
crlfP :: Derivs d => Parser d String
lookups :: Eq a => a -> [(a, b)] -> [b]
catRights :: [Either a b] -> [b]
catLefts :: [Either a b] -> [a]
isRight :: Either a b -> Bool
isLeft :: Either a b -> Bool
getLeft :: Either a b -> a
getRight :: Either a b -> b
Documentation
type Mailbox = StringSource
type UID = Word64Source
type Charset = StringSource
data MailboxInfo Source
Constructors
MboxInfo
_mailbox :: Mailbox
_exists :: Integer
_recent :: Integer
_flags :: [Flag]
_permanentFlags :: [Flag]
_isWritable :: Bool
_isFlagWritable :: Bool
_uidNext :: UID
_uidValidity :: UID
show/hide Instances
data Flag Source
Constructors
Seen
Answered
Flagged
Deleted
Draft
Recent
Keyword String
show/hide Instances
data Attribute Source
Constructors
Noinferiors
Noselect
Marked
Unmarked
OtherAttr String
show/hide Instances
data MboxUpdate Source
Constructors
MboxUpdate
exists :: Maybe Integer
recent :: Maybe Integer
show/hide Instances
data StatusCode Source
Constructors
ALERT
BADCHARSET [Charset]
CAPABILITY_sc [String]
PARSE
PERMANENTFLAGS [Flag]
READ_ONLY
READ_WRITE
TRYCREATE
UIDNEXT_sc UID
UIDVALIDITY_sc UID
UNSEEN_sc Integer
show/hide Instances
data ServerResponse Source
Constructors
OK (Maybe StatusCode) String
NO (Maybe StatusCode) String
BAD (Maybe StatusCode) String
PREAUTH (Maybe StatusCode) String
show/hide Instances
data MailboxStatus Source
the query data type for the status command
Constructors
MESSAGESthe number of messages in the mailbox
RECENTthe number of messages with the Recent flag set
UIDNEXTthe next unique identifier value of the mailbox
UIDVALIDITYthe unique identifier validity value of the mailbox
show/hide Instances
data RespDerivs Source
Constructors
RespDerivs
dvFlags :: Result RespDerivs [Flag]
advTag :: Result RespDerivs String
advChar :: Result RespDerivs Char
advPos :: Pos
show/hide Instances
Derivs RespDerivs
eval :: (RespDerivs -> Result RespDerivs r) -> String -> ByteString -> rSource
parse :: String -> Pos -> ByteString -> RespDerivsSource
eval' :: (RespDerivs -> Result RespDerivs r) -> String -> String -> rSource
parse' :: String -> Pos -> String -> RespDerivsSource
pNone :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, ())Source
pCapability :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [String])Source
pList :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [([Attribute], String, Mailbox)])Source
pLsub :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [([Attribute], String, Mailbox)])Source
pStatus :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [(MailboxStatus, Integer)])Source
pExpunge :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [Integer])Source
pSearch :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [UID])Source
pSelect :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, MailboxInfo)Source
pFetch :: RespDerivs -> Result RespDerivs (ServerResponse, MboxUpdate, [(Integer, [(String, String)])])Source
pDone :: RespDerivs -> Result RespDerivs ServerResponseSource
pFlag :: Parser RespDerivs FlagSource
pParenFlags :: RespDerivs -> Result RespDerivs [Flag]Source
atomChar :: Derivs d => Parser d CharSource
pNumberedLine :: String -> Parser RespDerivs IntegerSource
pRecentLine :: Parser RespDerivs IntegerSource
pExpungeLine :: Parser RespDerivs IntegerSource
pExistsLine :: Parser RespDerivs IntegerSource
pOtherLine :: Parser RespDerivs (Either (String, Integer) b)Source
pCapabilityLine :: Parser RespDerivs (Either a [String])Source
pListLine :: String -> Parser RespDerivs (Either a ([Attribute], String, Mailbox))Source
pStatusLine :: Parser RespDerivs (Either a [(MailboxStatus, Integer)])Source
pSearchLine :: Parser RespDerivs (Either a [UID])Source
pSelectLine :: Parser RespDerivs (MailboxInfo -> MailboxInfo)Source
pFetchLine :: Parser RespDerivs (Either a (Integer, [(String, String)]))Source
crlf :: StringSource
crlfP :: Derivs d => Parser d StringSource
lookups :: Eq a => a -> [(a, b)] -> [b]Source
catRights :: [Either a b] -> [b]Source
catLefts :: [Either a b] -> [a]Source
isRight :: Either a b -> BoolSource
isLeft :: Either a b -> BoolSource
getLeft :: Either a b -> aSource
getRight :: Either a b -> bSource
Produced by Haddock version 2.7.2