module Network.IMAP.Types where
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as BSC
import qualified Data.STM.RollingQueue as RQ
import Control.Concurrent.STM.TVar (TVar)
import Data.DeriveTH
import Control.Concurrent (ThreadId)
import Control.Concurrent.STM.TQueue (TQueue)
import Network.Connection (Connection, ConnectionContext,
connectionPut, connectionGetChunk')
import ListT (ListT)
import Control.Monad.IO.Class (liftIO)
import qualified Pipes as P
type ErrorMessage = T.Text
type CommandId = BSC.ByteString
data ConnectionState = UndefinedState
| Connected
| Disconnected
deriving (Show)
data IMAPConnection = IMAPConnection {
connectionState :: TVar ConnectionState,
untaggedQueue :: RQ.RollingQueue UntaggedResult,
imapState :: IMAPState
}
data IMAPState = IMAPState {
rawConnection :: !Connection,
connectionContext :: ConnectionContext,
responseRequests :: TQueue ResponseRequest,
serverWatcherThread :: TVar (Maybe ThreadId),
outstandingReqs :: TVar [ResponseRequest],
imapSettings :: IMAPSettings
}
type ParseResult = Either ErrorMessage CommandResult
data ResponseRequest = ResponseRequest {
responseQueue :: TQueue CommandResult,
respRequestId :: CommandId
} deriving (Eq)
data IMAPSettings = IMAPSettings {
imapTimeout :: Int,
untaggedQueueLength :: Int
}
data EmailAddress = EmailAddress {
emailLabel :: Maybe T.Text,
emailRoute :: Maybe T.Text,
emailUsername :: Maybe T.Text,
emailDomain :: Maybe T.Text
} deriving (Show, Eq)
data Flag = FSeen
| FAnswered
| FFlagged
| FDeleted
| FDraft
| FRecent
| FAny
| FOther T.Text
deriving (Show, Eq, Ord)
data Capability = CIMAP4
| CUnselect
| CIdle
| CNamespace
| CQuota
| CId
| CExperimental T.Text
| CChildren
| CUIDPlus
| CCompress T.Text
| CEnable
| CMove
| CCondstore
| CEsearch
| CUtf8 T.Text
| CAuth T.Text
| CListExtended
| CListStatus
| CAppendLimit Int
| COther T.Text (Maybe T.Text)
deriving (Show, Eq, Ord)
data TaggedResult = TaggedResult {
commandId :: CommandId,
resultState :: !ResultState,
resultRest :: T.Text
} deriving (Show, Eq)
data ResultState = OK | NO | BAD deriving (Show, Eq)
data UntaggedResult = Flags [Flag]
| Exists Integer
| Expunge Integer
| Bye
| HighestModSeq Integer
| Recent Integer
| Messages Integer
| Unseen Integer
| PermanentFlags [Flag]
| UID Integer
| MessageId Integer
| UIDNext Integer
| UIDValidity Integer
| OKResult T.Text
| NOResult T.Text
| BADResult T.Text
| Capabilities [Capability]
| ListR {
flags :: [NameAttribute],
hierarchyDelimiter :: T.Text,
inboxName :: T.Text
}
| Fetch [UntaggedResult]
| StatusR T.Text [UntaggedResult]
| Search [Integer]
| Envelope {
eDate :: Maybe T.Text,
eSubject :: Maybe T.Text,
eFrom :: Maybe [EmailAddress],
eSender :: Maybe [EmailAddress],
eReplyTo :: Maybe [EmailAddress],
eTo :: Maybe [EmailAddress],
eCC :: Maybe [EmailAddress],
eBCC :: Maybe [EmailAddress],
eInReplyTo :: Maybe T.Text,
eMessageId :: Maybe T.Text
}
| InternalDate T.Text
| Size Integer
| Unknown BSC.ByteString
| Body BSC.ByteString
| BodyStructure BSC.ByteString
| Extension BSC.ByteString ExtensionPayload
deriving (Show, Eq)
data ExtensionPayload = ExtInt Integer | ExtLabels [BSC.ByteString]
deriving (Show, Eq)
data NameAttribute = Noinferiors
| Noselect
| Marked
| Unmarked
| HasNoChildren
| OtherNameAttr T.Text
deriving (Show, Eq, Ord)
data CommandResult = Tagged TaggedResult | Untagged UntaggedResult
deriving (Show, Eq)
type SimpleResult = Either ErrorMessage [UntaggedResult]
class Monad m => Universe m where
connectionPut' :: Connection -> BSC.ByteString -> m ()
connectionGetChunk'' :: Connection -> (BSC.ByteString -> (a, BSC.ByteString)) -> m a
instance Universe IO where
connectionPut' = connectionPut
connectionGetChunk'' = connectionGetChunk'
instance Universe (ListT IO) where
connectionPut' c d = liftIO $ connectionPut c d
connectionGetChunk'' c cont = liftIO $ connectionGetChunk' c cont
instance Universe (P.ListT IO) where
connectionPut' c d = liftIO $ connectionPut c d
connectionGetChunk'' c cont = liftIO $ connectionGetChunk' c cont
defaultImapSettings :: IMAPSettings
defaultImapSettings = IMAPSettings 30 10
$(derive makeIs ''Flag)
$(derive makeIs ''UntaggedResult)
$(derive makeIs ''CommandResult)
$(derive makeIs ''ConnectionState)