hcom-0.0.0.2: Haskell COM support library

Copyright(c) Sigbjorn Finne sof@dcs.gla.ac.uk 1999
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainersof@forkIO.com
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

System.Win32.Com

Contents

Description

Support library for interacting with base Microsoft COM services and API.

Synopsis

Documentation

iidIUnknown :: IID (IUnknown ()) Source #

Representing interface pointers via IUnknown a, where a is the particular IUnknown-extended interface, e.g., IUnknown IDispatch_. If the interface pointer is just IUnknown, use IUnknown ().

Extend this to IIDs and parameterize them over the interface they represent.

interfaceNULL :: IUnknown a Source #

interfaceNULL is the NULL interface pointer.

isNullInterface :: IUnknown a -> Bool Source #

isNullInterface iptr returns True iff iptr is the NULL pointer.

iidNULL :: IID () Source #

The null interface

queryInterface :: IID (IUnknown b) -> IUnknown a -> IO (IUnknown b) Source #

queryInterface iid iunk queries iunk if it supports the iid interface, returning it. Notice that the type parameter to the IID matches up with that of the resulting interface pointer, giving you type safety - i.e., you can only use the interface pointer with methods supported by that interface

addRef :: IUnknown a -> IO Word32 Source #

addRef iptr increases the reference count of the interface pointer iptr. Notice that interface pointers are managed and finalized when on the Haskell heap, so manual reference counting is not required (and not encouraged as it could prevent the underlying object from being properly released, should you forget to decrement the ref count with release.)

release :: IUnknown a -> IO Word32 Source #

addRef iptr decrements the reference count of the interface pointer iptr.

(#) :: a -> (a -> IO b) -> IO b infixl 1 Source #

The # operator permits OO-style method application with do syntax:

 obj # method arg1 arg2

is equivalent to method arg1 arg2 obj, so this assumes that the COM method wrappers takes the this pointer as the last argument. Which the HDirect generated wrappers do and the various base method provided by this COM+Automation library.

(##) :: IO a -> (a -> IO b) -> IO b infixl 0 Source #

A variation on (#) where the this pointer is an action returning an object reference rather than the reference itself. Sometimes useful when you create one-off objects and call methods on them:

   (createObject arg1) ## startUp arg2

instead of the wieldier,

   obj <- createObject arg1
   obj # startUp arg2          or createObject arg1 >>= (startUp arg2)

coRun :: IO a -> IO a Source #

coRun act is the toplevel action combinator to wrap up your COM actions in. Takes care of calling coInitialize (and un-initialize) for you.

coPerformIO :: IO a -> IO a Source #

coPerformIO act runs act within an exception handler that catches and displays any COM API errors in a message box. For debugging purposes, mostly.

data GUID Source #

GUID is the Haskell representation for COM GUIDs.

Instances

Eq GUID Source # 

Methods

(==) :: GUID -> GUID -> Bool #

(/=) :: GUID -> GUID -> Bool #

Show GUID Source # 

Methods

showsPrec :: Int -> GUID -> ShowS #

show :: GUID -> String #

showList :: [GUID] -> ShowS #

newGUID :: IO GUID Source #

newGUID generates a new unique GUID.

stringToGUID :: String -> IO GUID Source #

stringToGUID "{00000000-0000-0000-C000-0000 0000 0046}" translates the COM string representation for GUIDs into an actual GUID value.

data IID a Source #

Representation of IIDs: Give the interface identifier a type parameter, so that when we come to define the Haskell type of IUnknown.QueryInterface() we can rely on the type checker to ensure that the IID passed to QueryInterface agrees with the interface at which we're using the interface pointer that's returned

Instances

Eq (IID a) Source # 

Methods

(==) :: IID a -> IID a -> Bool #

(/=) :: IID a -> IID a -> Bool #

Show (IID a) Source # 

Methods

showsPrec :: Int -> IID a -> ShowS #

show :: IID a -> String #

showList :: [IID a] -> ShowS #

castIID :: IID a -> IID b Source #

data CLSID Source #

Instances

Eq CLSID Source # 

Methods

(==) :: CLSID -> CLSID -> Bool #

(/=) :: CLSID -> CLSID -> Bool #

Show CLSID Source # 

Methods

showsPrec :: Int -> CLSID -> ShowS #

show :: CLSID -> String #

showList :: [CLSID] -> ShowS #

type LIBID = GUID Source #

Type libraries are identified by a GUID, the LIBID.

s_FALSE :: HRESULT Source #

s_OK and s_FALSE are the boolean values encoded as HRESULTs.

s_OK :: HRESULT Source #

s_OK and s_FALSE are the boolean values encoded as HRESULTs.

checkBool :: Int32 -> IO () Source #

checkBool mbZero raises a COM exception if mbZero is equal to...zero. The last error is embedded inside the exception.

returnHR :: IO () -> IO HRESULT Source #

returnHR act runs the IO action act, catching any COM exceptions. Success or failure is then mapped back into the corresponding HRESULT. In the case of success, s_OK.

coOnFail :: IO a -> String -> IO a Source #

coFail :: String -> IO a Source #

coFail msg raised the E_FAIL COM exception along with the descriptive string msg.

isCoError :: Com_Exception -> Bool Source #

isCoError e returns True for COM exceptions; False for IO exception values.

coGetErrorHR :: Com_Exception -> Maybe HRESULT Source #

coGetException ei picks out the COM HRESULT from the exception, if any.

coGetErrorString :: Com_Exception -> String Source #

coGetException ei returns a user-friendlier representation of the ei exception.

catchComException :: IO a -> (Com_Exception -> IO a) -> IO a Source #

act catchComException (ex -> hdlr ex) performs the IO action act, but catches any IO or COM exceptions ex, passing them to the handler hdlr.

throwIOComException :: Com_Exception -> IO a Source #

throwIOComException ex raises/throws the exception ex; ex is either an IOException or a ComException.

coCreateInstance :: CLSID -> Maybe (IUnknown b) -> CLSCTX -> IID (IUnknown a) -> IO (IUnknown a) Source #

coCreateInstance is the basic COM way of creating components. It takes a CLSID, an interface to aggregate on, a process context and an IID to create an object:

  coCreateInstance clsidAgentServer interfaceNULL LocalProcess iidIAgent

coCreateObject :: ProgID -> IID (IUnknown a) -> IO (IUnknown a) Source #

createObject creates an object from its progID: createObject Agent.Server. getObject creates an object from its progID and initializes it with a given file: getObject "spreadsheet.exl" Excel.Application. If the filename is empty, getObject calls getActiveObject. getActiveObject tries to connect to an already running instance of the component: getActiveObject Word.Application. getFileObject opens a file or url and loads the associated or persistent object in it: getFileObject "spreadsheet.spd". coCreateInstance is the basic com way of creating components. It takes a CLSID, process context and IID to create an object: coCreateInstance clsidAgentServer Nothing LocalProcess iidIAgent.

NOTE: prepend co to specify the initial IID, otherwise iidIDispatch is used (see Automation for more).

coGetObject :: String -> IID (IUnknown a) -> IO (IUnknown a) Source #

Bind to an object via its moniker string or display name.

coGetActiveObject :: ProgID -> IID (IUnknown a) -> IO (IUnknown a) Source #

Look up and activate the given active/running object.

coGetFileObject :: String -> ProgID -> IID (IUnknown a) -> IO (IUnknown a) Source #

Get Object from File and ProgID.

withObject :: IUnknown a -> [IUnknown a -> IO b] -> IO [b] Source #

withObject_ :: IUnknown a -> [IUnknown a -> IO b] -> IO () Source #

withMethod :: (a -> IUnknown b -> IO c) -> [a] -> IUnknown b -> IO [c] Source #

withMethod_ :: (a -> IUnknown b -> IO c) -> [a] -> IUnknown b -> IO () Source #

data CLSCTX Source #

The CLSCTX enumeration is used by comCreateInstance to specify execution context in which we'd like to component to be created (just use AnyProcess if you're not too fussed..)

type ProgID = String Source #

ProgIDs are represented in Haskell as mere strings

progIDFromCLSID :: CLSID -> IO ProgID Source #

progIDFromCLSID cid is the dual clsidFromProgID, attempting to translate in the other direction.

clsidFromProgID :: ProgID -> IO CLSID Source #

clsidFromProgID progid looks up a ProgID and tries to translate it into its registered CLSID. Raises an IO exception if the ProgID isn't known.

printMessage :: Show a => a -> IO () Source #

printMessage val shows val in a message box.

putMessage :: String -> IO () Source #

putMessage str displays str in an informational message box containing an OK button.

messageBox :: String -> String -> Word32 -> IO () Source #

messageBox msg title flg displays a message box with the given title and content. The flg parameter is the bit pattern that makes up the MB_* settings you want to use (cf. underlying Win32 API documentation for MessageBox.)

outputDebugString :: String -> IO () Source #

outputDebugString str adds an

enumNext :: Word32 -> (Ptr any -> IO a) -> Word32 -> IUnknown b -> IO [a] Source #

enumNextOne :: Word32 -> (Ptr any -> IO a) -> IUnknown b -> IO (Maybe a) Source #

freeBSTR :: Ptr a -> IO () Source #

coFree :: Ptr a -> IO () Source #

coFree ptr releases storage that has been allocated via the COM task allocator; explicitly via coAlloc or indirectly via the APIs that handed the pointer to your code.

coAlloc :: Word32 -> IO (Ptr a) Source #

coAlloc sz allocates sz bytes from the COM task allocator, returning a pointer. The onus is on the caller to constrain the type of that pointer to capture what the allocated memory points to.

castIface :: IUnknown a -> IUnknown b Source #

castIface obj performs a type

unmarshallGUID :: Bool -> Ptr GUID -> IO GUID Source #

unmarshallGUID finalize ptr unpacks a pointer to an incoming GUID, wrapping it up as a Haskell GUID. If finalize is True, the GUID is assumed allocated via the COM task allocator and will be freed/finalized when the GUID becomes garbage.

writeGUID :: Ptr GUID -> GUID -> IO () Source #

writeGUID ptr g packs the Haskell GUID into the pointer; that is, it writes a pointer to the GUID value to ptr -- no copying of underlying structure.

copyGUID :: GUID -> IO (Ptr ()) Source #

A version of the GUID marshaller which copies rather than hands back a pointer to the (immutable) GUID.

unmarshallIID :: Bool -> Ptr (IID a) -> IO (IID a) Source #

writeIID :: Ptr (IID a) -> IID a -> IO () Source #

readIID :: Bool -> Ptr (Ptr (IID a)) -> IO (IID a) Source #

copyIID :: IID t -> IO (Ptr ()) Source #

invokeAndCheck :: (Ptr any -> Ptr b -> IO HRESULT) -> Int -> IUnknown a -> IO () Source #

invokeIt :: (Ptr any -> Ptr c -> IO a) -> Int -> IUnknown b -> IO a Source #

invokeIt ( methPtr ip -> action) offset obj sets up a vtbl-indexed COM call, unmarshalling and indexing obj before passing it along to the method argument. The first argument is typically an FFI wrapped call to a function pointer (methPtr here).

Orphan instances

Eq (IUnknown_ a) Source #

Equality of interface pointers is defined by the COM spec as being equality of IUnknown (pointers to) implementations.

Methods

(==) :: IUnknown_ a -> IUnknown_ a -> Bool #

(/=) :: IUnknown_ a -> IUnknown_ a -> Bool #

Show (IUnknown_ a) Source #