[Haskell-cafe] Help on using System.Win32.Com.Automation

Wilkes Joiner wilkesjoiner at gmail.com
Tue Mar 24 09:00:47 EDT 2009


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
<sigbjorn.finne at gmail.com> 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
>
> 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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>


More information about the Haskell-Cafe mailing list