[Haskell-cafe] Unboxing VT_VARIANT in hscom

Krasimir Angelov kr.angelov at gmail.com
Wed Aug 20 03:58:50 EDT 2008


Aha. I got it. You should compile with -fglasgow-exts option. The
extra type signatures doesn't matter.


On Wed, Aug 20, 2008 at 8:20 AM, Praki Prakash <praki.prakash at gmail.com> wrote:
> Krasimir - thanks for your reply. I had tried explicit typing but I still
> get the same error. I have some code below and the error message.
>
> import Control.Exception
> import Foreign
> import Foreign.COM.Client
> import Foreign.COM.Automation
> import System.IO
>
> data WmiConnection =
>   WmiConnection {
>     execQuery :: String -> IO ()
>   }
>
> main = withCOM $ do
>   conn <- wmiconnect "." "root\\cimv2"
>   execQuery conn "Select * From ..."
>   print "done"
>
> wmiconnect :: String -> String -> IO WmiConnection
> wmiconnect comp cimroot =
>     do
>       clsid <- progid2clsid "WbemScripting.SWbemLocator"
>       (bracket (createInstance clsid iidIUnknown) release $ \iunkn ->
>        bracket (queryInterface iidIDispatch iunkn) release $ \idisp -> do
>        dispId <- getMethodID "ConnectServer" idisp
>        withBSTR comp $ \pComputer ->
>          withBSTR cimroot  $ \pCimRoot -> do
>            (res,args) <- invoke dispId InvokeMethod [Variant VT_BSTR
> pComputer,
>                                                      Variant VT_BSTR
> pCimRoot
>                                                ] idisp
>            print res
>            let conn = WmiConnection{ execQuery = queryFunc res }
>            return conn)
>          where
>            queryFunc :: Variant -> String -> IO ()
>            queryFunc (Variant VT_DISPATCH idisp) query = do
>              dispId <- getMethodID "ExecQuery" idisp
>              return ()
>            {-
>            queryFunc (Variant vt idisp) query =
>              if vt == VT_DISPATCH
>              then do
>                    dispId <- getMethodID "ExecQuery"  idisp
>                    return ""
>              else
>                  fail "error"
>
>              return ()
>              -}
>
> C:\>ghc --make test.hs
> [1 of 1] Compiling Main             ( test.hs, test.o )
>
> test.hs:35:47:
>     Couldn't match expected type `IDispatch a'
>            against inferred type `a1'
>       `a1' is a rigid type variable bound by
>            the constructor `Variant' at test.hs:34:22
>     In the second argument of `getMethodID', namely `idisp'
>     In a 'do' expression: dispId <- getMethodID "ExecQuery" idisp
>     In the expression:
>         do dispId <- getMethodID "ExecQuery" idisp
>            return ()
>
> Any further suggestions?
>
> Thanks,
> Praki
>
> On Tue, Aug 19, 2008 at 1:49 AM, Krasimir Angelov <kr.angelov at gmail.com>
> wrote:
>>
>> This looks like a GHC bug to me. I am pretty sure that this worked
>> before. Variant is defined like this:
>>
>> data Variant = forall a . Variant (VarType a) a
>>
>> data VarType a where
>>   ....
>>   VT_DISPATCH  :: VarType (IDispatch ())
>>
>> From this it clear that val is of type (IDispatch ()) because the
>> VarType has value VT_DISPATCH. A workaround is to add explicit type
>> singnature for val:
>>
>> someFunc (Variant VT_DISPATCH val) query = do
>>    dispId <- getMethodID "MethodName"  (val :: IDispatch ())
>>
>> I don't know why this doesn't work without the signature.
>>
>> Regards,
>>   Krasimir
>>
>>
>> On Tue, Aug 19, 2008 at 7:09 AM, Praki Prakash <praki.prakash at gmail.com>
>> wrote:
>> > I am a Haskell newbie trying to do COM automation using Haskell. I am
>> > using
>> > hscom (Krasimir's implementation of COM automation). I have run into a
>> > problem
>> > and need some help.
>> >
>> > I have a Variant returned from a COM method invocation. When I print it,
>> > it
>> > shows up as below.
>> >
>> > Variant VT_DISPATCH <interface 0x00039f00>
>> >
>> > I need to invoke methods on the wrapped interface. My attempt to unbox
>> > it as
>> > below runs into 'rigid type' error.
>> >
>> > someFunc (Variant VT_DISPATCH val) query = do
>> >  dispId <- getMethodID "MethodName"  val
>> >
>> > The code above generates this error.
>> >
>> >    Couldn't match expected type `IDispatch a'
>> >           against inferred type `a1'
>> >      `a1' is a rigid type variable bound by...
>> >
>> > I am probably missing something pretty basic. Any help on this is
>> > greatly
>> > appreciated!
>> >
>> > Thanks
>> >
>> >
>> >
>> >
>> >
>> > _______________________________________________
>> > 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