| Copyright | (c) Sigbjorn Finne <sof@dcs.gla.ac.uk> 1998-99 |
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) |
| Maintainer | sof@forkIO.com |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
System.Win32.Com.Dll
Description
Support for sealing up Haskell code as an in-proc COM server.
The main function is createIComDll which packages up a list of ComponentInfo
values specifying the Haskell implementation of COM objects. It returns
a method table which you can then wrap up as a DLL by calling its
COM-mandated entry points via.
Synopsis
- data ComponentInfo = ComponentInfo {
- newInstance :: ComponentFactory
- componentFinalise :: IO ()
- componentName :: String
- componentProgID :: String
- componentVProgID :: String
- componentTLB :: Bool
- registerComponent :: ComponentInfo -> String -> Bool -> IO ()
- componentCLSID :: CLSID
- mkComponentInfo :: CLSID -> (String -> Bool -> IO ()) -> (String -> IO () -> IID (IUnknown ()) -> IO (IUnknown ())) -> ComponentInfo
- withComponentName :: String -> ComponentInfo -> ComponentInfo
- withProgID :: String -> ComponentInfo -> ComponentInfo
- withVerIndepProgID :: String -> ComponentInfo -> ComponentInfo
- onRegister :: (ComponentInfo -> String -> Bool -> IO ()) -> ComponentInfo -> ComponentInfo
- onFinalize :: IO () -> ComponentInfo -> ComponentInfo
- hasTypeLib :: ComponentInfo -> ComponentInfo
- createIComDll :: Ptr () -> [ComponentInfo] -> IO (VTable iid_comDllState ComDllState)
- regAddEntry :: RegHive -> String -> Maybe String -> IO ()
- regRemoveEntry :: RegHive -> String -> String -> Bool -> IO ()
- data RegHive
- stdRegComponent :: ComponentInfo -> Bool -> String -> IO ()
- stdUnRegComponent :: ComponentInfo -> Bool -> String -> IO ()
- type ComponentFactory = String -> IO () -> IID (IUnknown ()) -> IO (IUnknown ())
Documentation
data ComponentInfo Source #
The information an implementation of a Haskell COM component
needs to supply in order to hook into the machinery provided
by System.Win32.Com.Dll for interfacing to how COM does
activation for in-proc components
To create one or more, you pass them into createIComDll..
Constructors
| ComponentInfo | |
Fields
| |
mkComponentInfo :: CLSID -> (String -> Bool -> IO ()) -> (String -> IO () -> IID (IUnknown ()) -> IO (IUnknown ())) -> ComponentInfo Source #
The mkComponentInfo used to lessen the reliance on concrete representation
of ComponentInfo.
withComponentName :: String -> ComponentInfo -> ComponentInfo Source #
withComponentName nm ci returns a new ComponentInfo based on ci,
but with its name set to nm.
withProgID :: String -> ComponentInfo -> ComponentInfo Source #
withProgID p ci returns a new ComponentInfo based on ci,
but with ProgID set to p.
withVerIndepProgID :: String -> ComponentInfo -> ComponentInfo Source #
withVerProgID vp ci returns a new ComponentInfo based on ci,
but with version-independent ProgID set to vp.
onRegister :: (ComponentInfo -> String -> Bool -> IO ()) -> ComponentInfo -> ComponentInfo Source #
onRegister act ci returns a new ComponentInfo based on ci,
but with the (un)registration action extended with act.
onFinalize :: IO () -> ComponentInfo -> ComponentInfo Source #
onFinalize act ci returns a new ComponentInfo based on ci,
but with the finalization action extended with act.
hasTypeLib :: ComponentInfo -> ComponentInfo Source #
hasTypeLib ci returns a new ComponentInfo based on ci, but being type library backed.
createIComDll :: Ptr () -> [ComponentInfo] -> IO (VTable iid_comDllState ComDllState) Source #
createIComDll hMod cis creates the method table for an inproc server
supporting the components specified by cis. The method table would
then be wrapped up by a Haskell DLL wrapper supporting the in-proc
DLL entry points.
regAddEntry :: RegHive -> String -> Maybe String -> IO () Source #
regAddEntry hive path val is a convenient local wrapper to the Win32
API function RegAddEntry().
regRemoveEntry :: RegHive -> String -> String -> Bool -> IO () Source #
regRemoveEntry hive path val doRemove is a convenient local wrapper to the Win32
API function RegRemoveEntry().
Instances
| Enum RegHive Source # | |
| Eq RegHive Source # | |
| Ord RegHive Source # | |
Defined in System.Win32.Com.Dll | |
stdRegComponent :: ComponentInfo -> Bool -> String -> IO () Source #
stdUnRegComponent :: ComponentInfo -> Bool -> String -> IO () Source #
type ComponentFactory = String -> IO () -> IID (IUnknown ()) -> IO (IUnknown ()) Source #
(( path final iid -> IO obj)::ComponentFactory is the component-specific
object factory method:
pathis the path to the DLL implementing the component (useful for TLB lookup etc.)finalis finalization action for the object.iidis theIIDto create object at.objis the newly created object at interfaceiid.