Win32-2.1.0.0: A binding to part of the Win32 libraryContentsIndex
System.Win32.SimpleMAPI
Portabilityportable
Stabilityprovisional
MaintainerEsa Ilari Vuokko <ei@vuokko.info>
Description
FFI-bindings to interact with SimpleMAPI
Synopsis
type ULONG = DWORD
type LHANDLE = ULONG
newtype MapiRecipDesc = MapiRecipDesc ()
type MapiFlag = ULONG
mAPI_LOGON_UI :: MapiFlag
mAPI_NEW_SESSION :: MapiFlag
mAPI_FORCE_DOWNLOAD :: MapiFlag
mAPI_LOGOFF_SHARED :: MapiFlag
mAPI_LOGOFF_UI :: MapiFlag
mAPI_DIALOG :: MapiFlag
mAPI_UNREAD_ONLY :: MapiFlag
mAPI_LONG_MSGID :: MapiFlag
mAPI_GUARANTEE_FIFO :: MapiFlag
mAPI_ENVELOPE_ONLY :: MapiFlag
mAPI_PEEK :: MapiFlag
mAPI_BODY_AS_FILE :: MapiFlag
mAPI_SUPPRESS_ATTACH :: MapiFlag
mAPI_AB_NOMODIFY :: MapiFlag
mAPI_OLE :: MapiFlag
mAPI_OLE_STATIC :: MapiFlag
mAPI_UNREAD :: MapiFlag
mAPI_RECEIPT_REQUESTED :: MapiFlag
mAPI_SENT :: MapiFlag
mapiErrors :: [(ULONG, String)]
mapiErrorString :: ULONG -> String
mapiFail :: String -> IO ULONG -> IO ULONG
mapiFail_ :: String -> IO ULONG -> IO ()
type MapiLogonType = ULONG -> LPSTR -> LPSTR -> MapiFlag -> ULONG -> Ptr LHANDLE -> IO ULONG
mkMapiLogon :: FunPtr MapiLogonType -> MapiLogonType
type MapiLogoffType = LHANDLE -> ULONG -> MapiFlag -> ULONG -> IO ULONG
mkMapiLogoff :: FunPtr MapiLogoffType -> MapiLogoffType
type MapiResolveNameType = LHANDLE -> ULONG -> LPSTR -> MapiFlag -> ULONG -> Ptr (Ptr MapiRecipDesc) -> IO ULONG
mkMapiResolveName :: FunPtr MapiResolveNameType -> MapiResolveNameType
type MapiFreeBufferType = Ptr () -> IO ULONG
mkMapiFreeBuffer :: FunPtr MapiFreeBufferType -> MapiFreeBufferType
type MapiSendMailType = LHANDLE -> ULONG -> Ptr Message -> MapiFlag -> ULONG -> IO ULONG
mkMapiSendMail :: FunPtr MapiSendMailType -> MapiSendMailType
data MapiFuncs = MapiFuncs {
mapifLogon :: MapiLogonType
mapifLogoff :: MapiLogoffType
mapifResolveName :: MapiResolveNameType
mapifFreeBuffer :: MapiFreeBufferType
mapifSendMail :: MapiSendMailType
}
type MapiLoaded = (MapiFuncs, ForeignPtr ())
loadMapiFuncs :: String -> HMODULE -> IO MapiFuncs
loadMapiDll :: String -> IO (MapiFuncs, HMODULE)
withMapiFuncs :: [String] -> (MapiFuncs -> IO a) -> IO a
loadMapi :: [String] -> IO MapiLoaded
withMapiLoaded :: MapiLoaded -> (MapiFuncs -> IO a) -> IO a
maybeHWND :: Maybe HWND -> ULONG
mapiLogon :: MapiFuncs -> Maybe HWND -> Maybe String -> Maybe String -> MapiFlag -> IO LHANDLE
mapiLogoff :: MapiFuncs -> LHANDLE -> Maybe HWND -> IO ()
data RecipientClass
= RcOriginal
| RcTo
| RcCc
| RcBcc
rcToULONG :: RecipientClass -> ULONG
uLONGToRc :: ULONG -> RecipientClass
data Recipient
= RecipResolve (Maybe HWND) MapiFlag String (Maybe Recipient)
| Recip String String
type Recipients = [(RecipientClass, Recipient)]
simpleRecip :: String -> Recipient
withRecipient :: MapiFuncs -> LHANDLE -> RecipientClass -> Recipient -> (Ptr MapiRecipDesc -> IO a) -> IO a
withRecipients :: MapiFuncs -> LHANDLE -> Recipients -> (Int -> Ptr MapiRecipDesc -> IO a) -> IO a
data FileTag = FileTag {
ftTag :: (Maybe String)
ftEncoding :: (Maybe String)
}
defFileTag :: FileTag
withFileTag :: FileTag -> (Ptr FileTag -> IO a) -> IO a
data Attachment = Attachment {
attFlag :: MapiFlag
attPosition :: (Maybe ULONG)
attPath :: String
attName :: (Maybe String)
attTag :: (Maybe FileTag)
}
defAttachment :: Attachment
type Attachments = [Attachment]
withAttachments :: Attachments -> (Int -> Ptr Attachment -> IO a) -> IO a
data Message = Message {
msgSubject :: String
msgBody :: String
msgType :: (Maybe String)
msgDate :: (Maybe String)
msgConversationId :: (Maybe String)
msgFlags :: MapiFlag
msgFrom :: (Maybe Recipient)
msgRecips :: Recipients
msgAttachments :: Attachments
}
defMessage :: Message
withMessage :: MapiFuncs -> LHANDLE -> Message -> (Ptr Message -> IO a) -> IO a
mapiSendMail :: MapiFuncs -> LHANDLE -> Maybe HWND -> Message -> MapiFlag -> IO ()
Documentation
type ULONG = DWORD
type LHANDLE = ULONG
newtype MapiRecipDesc
Constructors
MapiRecipDesc ()
type MapiFlag = ULONG
mAPI_LOGON_UI :: MapiFlag
mAPI_NEW_SESSION :: MapiFlag
mAPI_FORCE_DOWNLOAD :: MapiFlag
mAPI_LOGOFF_SHARED :: MapiFlag
mAPI_LOGOFF_UI :: MapiFlag
mAPI_DIALOG :: MapiFlag
mAPI_UNREAD_ONLY :: MapiFlag
mAPI_LONG_MSGID :: MapiFlag
mAPI_GUARANTEE_FIFO :: MapiFlag
mAPI_ENVELOPE_ONLY :: MapiFlag
mAPI_PEEK :: MapiFlag
mAPI_BODY_AS_FILE :: MapiFlag
mAPI_SUPPRESS_ATTACH :: MapiFlag
mAPI_AB_NOMODIFY :: MapiFlag
mAPI_OLE :: MapiFlag
mAPI_OLE_STATIC :: MapiFlag
mAPI_UNREAD :: MapiFlag
mAPI_RECEIPT_REQUESTED :: MapiFlag
mAPI_SENT :: MapiFlag
mapiErrors :: [(ULONG, String)]
mapiErrorString :: ULONG -> String
mapiFail :: String -> IO ULONG -> IO ULONG
mapiFail_ :: String -> IO ULONG -> IO ()
type MapiLogonType = ULONG -> LPSTR -> LPSTR -> MapiFlag -> ULONG -> Ptr LHANDLE -> IO ULONG
mkMapiLogon :: FunPtr MapiLogonType -> MapiLogonType
type MapiLogoffType = LHANDLE -> ULONG -> MapiFlag -> ULONG -> IO ULONG
mkMapiLogoff :: FunPtr MapiLogoffType -> MapiLogoffType
type MapiResolveNameType = LHANDLE -> ULONG -> LPSTR -> MapiFlag -> ULONG -> Ptr (Ptr MapiRecipDesc) -> IO ULONG
mkMapiResolveName :: FunPtr MapiResolveNameType -> MapiResolveNameType
type MapiFreeBufferType = Ptr () -> IO ULONG
mkMapiFreeBuffer :: FunPtr MapiFreeBufferType -> MapiFreeBufferType
type MapiSendMailType = LHANDLE -> ULONG -> Ptr Message -> MapiFlag -> ULONG -> IO ULONG
mkMapiSendMail :: FunPtr MapiSendMailType -> MapiSendMailType
data MapiFuncs
Constructors
MapiFuncs
mapifLogon :: MapiLogonType
mapifLogoff :: MapiLogoffType
mapifResolveName :: MapiResolveNameType
mapifFreeBuffer :: MapiFreeBufferType
mapifSendMail :: MapiSendMailType
type MapiLoaded = (MapiFuncs, ForeignPtr ())
loadMapiFuncs :: String -> HMODULE -> IO MapiFuncs
loadMapiDll :: String -> IO (MapiFuncs, HMODULE)
withMapiFuncs :: [String] -> (MapiFuncs -> IO a) -> IO a
loadMapi :: [String] -> IO MapiLoaded
withMapiLoaded :: MapiLoaded -> (MapiFuncs -> IO a) -> IO a
maybeHWND :: Maybe HWND -> ULONG
mapiLogon
:: MapiFuncsFunctions loaded from MAPI DLL
-> Maybe HWNDParent window, used for modal logon dialog
-> Maybe StringSession
-> Maybe StringPassword
-> MapiFlagNone, one or many flags: FORCE_DOWNLOAD, NEW_SESSION, LOGON_UI, PASSWORD_UI
-> IO LHANDLE
Create Simple MAPI-session by logon
mapiLogoff :: MapiFuncs -> LHANDLE -> Maybe HWND -> IO ()
End Simple MAPI-session
data RecipientClass
Constructors
RcOriginal
RcTo
RcCc
RcBcc
show/hide Instances
rcToULONG :: RecipientClass -> ULONG
uLONGToRc :: ULONG -> RecipientClass
data Recipient
Constructors
RecipResolve (Maybe HWND) MapiFlag String (Maybe Recipient)
Recip String String
show/hide Instances
type Recipients = [(RecipientClass, Recipient)]
simpleRecip :: String -> Recipient
withRecipient :: MapiFuncs -> LHANDLE -> RecipientClass -> Recipient -> (Ptr MapiRecipDesc -> IO a) -> IO a
withRecipients :: MapiFuncs -> LHANDLE -> Recipients -> (Int -> Ptr MapiRecipDesc -> IO a) -> IO a
data FileTag
Constructors
FileTag
ftTag :: (Maybe String)mime
ftEncoding :: (Maybe String)
show/hide Instances
Show FileTag
defFileTag :: FileTag
withFileTag :: FileTag -> (Ptr FileTag -> IO a) -> IO a
data Attachment
Constructors
Attachment
attFlag :: MapiFlag
attPosition :: (Maybe ULONG)
attPath :: String
attName :: (Maybe String)
attTag :: (Maybe FileTag)
show/hide Instances
defAttachment :: Attachment
type Attachments = [Attachment]
withAttachments :: Attachments -> (Int -> Ptr Attachment -> IO a) -> IO a
data Message
Constructors
Message
msgSubject :: String
msgBody :: String
msgType :: (Maybe String)
msgDate :: (Maybe String)
msgConversationId :: (Maybe String)
msgFlags :: MapiFlag
msgFrom :: (Maybe Recipient)
msgRecips :: Recipients
msgAttachments :: Attachments
show/hide Instances
Show Message
defMessage :: Message
withMessage :: MapiFuncs -> LHANDLE -> Message -> (Ptr Message -> IO a) -> IO a
mapiSendMail :: MapiFuncs -> LHANDLE -> Maybe HWND -> Message -> MapiFlag -> IO ()
Produced by Haddock version 0.8