Help on using System.Win32.Com.Automation

I'm playing around with the com package, but I'm having a hard time understanding how to map a COM call to the appropriate methodN or functionN call. Does anyone have any example code that uses the method1 or higher. Any help or pointers would be appreciated. Here's the code I have so far: import System.Win32.Com import System.Win32.Com.Automation dsn = "Provider=vfpoledb.1;Data Source=C:\\SomeDirectory\\" main = coInitialize >> openConnection >>= \con -> closeConnection con openDSN :: String -> IDispatch a -> IO () openDSN dsn con = method0 "Open" [inString dsn] con openConnection :: IO (IDispatch a) openConnection = createObject "ADODB.Connection" >>= \con -> openDSN dsn con >> return con closeConnection :: IDispatch a -> IO () closeConnection = method0 "Close" [] {- Wraps ADO Connection.Execute http://msdn.microsoft.com/en-us/library/ms675023(VS.85).aspx Set recordset = connection.Execute (CommandText, RecordsAffected, Options) execute :: String -> IDispatch a -> IO a execute cmd con = method1 "Execute" [inString cmd] (inEmpty,resWord64) con -} Thank You, Wilkes

Hi Wilkes, you may want to have a look at a simple example of how to interop with Windows WMI using the COM package at -- http://haskell.forkio.com/com-examples Hope it is of some help to you. --sigbjorn On 3/19/2009 16:49, Wilkes Joiner wrote:
I'm playing around with the com package, but I'm having a hard time understanding how to map a COM call to the appropriate methodN or functionN call. Does anyone have any example code that uses the method1 or higher. Any help or pointers would be appreciated.
Here's the code I have so far:
import System.Win32.Com import System.Win32.Com.Automation
dsn = "Provider=vfpoledb.1;Data Source=C:\\SomeDirectory\\" main = coInitialize >> openConnection >>= \con -> closeConnection con
openDSN :: String -> IDispatch a -> IO () openDSN dsn con = method0 "Open" [inString dsn] con
openConnection :: IO (IDispatch a) openConnection = createObject "ADODB.Connection" >>= \con -> openDSN dsn con >> return con
closeConnection :: IDispatch a -> IO () closeConnection = method0 "Close" []
{- Wraps ADO Connection.Execute http://msdn.microsoft.com/en-us/library/ms675023(VS.85).aspx Set recordset = connection.Execute (CommandText, RecordsAffected, Options)
execute :: String -> IDispatch a -> IO a execute cmd con = method1 "Execute" [inString cmd] (inEmpty,resWord64) con
-}
Thank You, Wilkes _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Sigbjorn Finne wrote:
Hi Wilkes,
you may want to have a look at a simple example of how to interop with Windows WMI using the COM package at --
http://haskell.forkio.com/com-examples I try compile WMIDemo.hs but recive error: [code] c:\htest>ghc --make WMIDemo.hs [2 of 2] Compiling WMIDemo ( WMIDemo.hs, WMIDemo.o )
WMIDemo.hs:24:2: Couldn't match expected type `[a]' against inferred type `(a1, b)' In the pattern: (_, ls) In a stmt of a 'do' expression: (_, ls) <- is # enumVariants In the second argument of `($)', namely `do obj <- Auto.getObject "winmgmts:\\\\.\\root\\CIMV2" is <- obj # instancesOf "Win32_OperatingSystem" (Nothing :: Maybe Int) (Nothing :: Maybe (IDispatch ())) (_, ls) <- is # enumVariants case ls of { [] -> fail "Hmm..no OS information available; expected at least one." (wmi_os : _) -> do ... }' [/code] ghc 6.10.1 com-1.2.1 Windows Vista Home Ru + sp1

Alexandr N. Zamaraev wrote:
Sigbjorn Finne wrote:
Hi Wilkes,
you may want to have a look at a simple example of how to interop with Windows WMI using the COM package at --
http://haskell.forkio.com/com-examples I try compile WMIDemo.hs but recive error: [code] c:\htest>ghc --make WMIDemo.hs [2 of 2] Compiling WMIDemo ( WMIDemo.hs, WMIDemo.o )
WMIDemo.hs:24:2: Couldn't match expected type `[a]' against inferred type `(a1, b)' ...
Hi, please upgrade to the latest version - 1.2.2 - of the com package for this example, http://hackage.haskell.org/cgi-bin/hackage-scripts/package/com There's been some improvements to the lib, esp. the handling of enumerations (which is where that type error is coming from.) hth --sigbjorn

Thank you Sigbjorn. The generated WMI module had the information I
was looking for.
I wasn't able to find the ihc. Would an old hdirect package work? I
just needed to map a handful of functions so I did it by hand.
For posterity, here are the mappings I've needed so far:
createConnection :: String -> IO (IDispatch a)
createConnection dsn = do
c <- createObject "ADODB.Connection"
openConnection dsn c
return c
openConnection :: String -> IDispatch a -> IO ()
openConnection dsn = method0 "Open" [inString dsn]
closeConnection :: IDispatch a -> IO ()
closeConnection = method0 "Close" []
execute :: IDispatch i -> String -> IO (IDispatch a)
execute connection sqlStatement =
function_1_1 "Execute" sqlStatement connection
eof :: IDispatch i -> IO Bool
eof = propertyGet_0 "EOF"
fields :: IDispatch i -> IO (IDispatch a)
fields = propertyGet_0 "Fields"
count :: IDispatch i -> IO Int
count = propertyGet_0 "Count"
moveFirst :: IDispatch i -> IO ()
moveFirst = method_0_0 "MoveFirst"
moveNext :: IDispatch i -> IO ()
moveNext = method_0_0 "MoveNext"
item :: IDispatch i -> Int -> IO String
item rs key = fields rs >>= function1 "Item" [inInt key] outString
On Mon, Mar 23, 2009 at 1:11 AM, Sigbjorn Finne
Hi Wilkes,
you may want to have a look at a simple example of how to interop with Windows WMI using the COM package at --
http://haskell.forkio.com/com-examples
Hope it is of some help to you.
--sigbjorn
On 3/19/2009 16:49, Wilkes Joiner wrote:
I'm playing around with the com package, but I'm having a hard time understanding how to map a COM call to the appropriate methodN or functionN call. Does anyone have any example code that uses the method1 or higher. Any help or pointers would be appreciated.
Here's the code I have so far:
import System.Win32.Com import System.Win32.Com.Automation
dsn = "Provider=vfpoledb.1;Data Source=C:\\SomeDirectory\\" main = coInitialize >> openConnection >>= \con -> closeConnection con
openDSN :: String -> IDispatch a -> IO () openDSN dsn con = method0 "Open" [inString dsn] con
openConnection :: IO (IDispatch a) openConnection = createObject "ADODB.Connection" >>= \con -> openDSN dsn con >> return con
closeConnection :: IDispatch a -> IO () closeConnection = method0 "Close" []
{- Wraps ADO Connection.Execute http://msdn.microsoft.com/en-us/library/ms675023(VS.85).aspx Set recordset = connection.Execute (CommandText, RecordsAffected, Options)
execute :: String -> IDispatch a -> IO a execute cmd con = method1 "Execute" [inString cmd] (inEmpty,resWord64) con
-}
Thank You, Wilkes _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Alexandr N. Zamaraev
-
Sigbjorn Finne
-
Wilkes Joiner