Portability | portable |
---|---|
Stability | provisional |
Maintainer | Esa Ilari Vuokko <ei@vuokko.info> |
Safe Haskell | Trustworthy |
FFI-bindings to interact with SimpleMAPI
- 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
- mapiErrors :: [(ULONG, String)]
- 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
- 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 {}
- 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
- 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 {}
- defFileTag :: FileTag
- withFileTag :: FileTag -> (Ptr FileTag -> IO a) -> IO a
- data Attachment = Attachment {}
- defAttachment :: Attachment
- type Attachments = [Attachment]
- withAttachments :: Attachments -> (Int -> Ptr Attachment -> IO a) -> IO a
- data Message = Message {}
- defMessage :: Message
- withMessage :: MapiFuncs -> LHANDLE -> Message -> (Ptr Message -> IO a) -> IO a
- mapiSendMail :: MapiFuncs -> LHANDLE -> Maybe HWND -> Message -> MapiFlag -> IO ()
- handleIOException :: (IOException -> IO a) -> IO a -> IO a
Documentation
newtype MapiRecipDesc Source
mapiErrors :: [(ULONG, String)]Source
mapiErrorString :: ULONG -> StringSource
type MapiResolveNameType = LHANDLE -> ULONG -> LPSTR -> MapiFlag -> ULONG -> Ptr (Ptr MapiRecipDesc) -> IO ULONGSource
type MapiFreeBufferType = Ptr () -> IO ULONGSource
type MapiLoaded = (MapiFuncs, ForeignPtr ())Source
loadMapi :: [String] -> IO MapiLoadedSource
withMapiLoaded :: MapiLoaded -> (MapiFuncs -> IO a) -> IO aSource
:: MapiFuncs | Functions loaded from MAPI DLL |
-> Maybe HWND | Parent window, used for modal logon dialog |
-> Maybe String | Session |
-> Maybe String | Password |
-> MapiFlag | None, one or many flags: FORCE_DOWNLOAD, NEW_SESSION, LOGON_UI, PASSWORD_UI |
-> IO LHANDLE |
Create Simple MAPI-session by logon
data RecipientClass Source
type Recipients = [(RecipientClass, Recipient)]Source
simpleRecip :: String -> RecipientSource
withRecipient :: MapiFuncs -> LHANDLE -> RecipientClass -> Recipient -> (Ptr MapiRecipDesc -> IO a) -> IO aSource
withRecipients :: MapiFuncs -> LHANDLE -> Recipients -> (Int -> Ptr MapiRecipDesc -> IO a) -> IO aSource
type Attachments = [Attachment]Source
withAttachments :: Attachments -> (Int -> Ptr Attachment -> IO a) -> IO aSource
Message | |
|
handleIOException :: (IOException -> IO a) -> IO a -> IO aSource