Using FFI for .NET
Guilherme Oliveira
gkmo at cin.ufpe.br
Tue Apr 21 21:56:14 EDT 2009
Hi guys,
I'm new to haskell and I'm trying to make some calls to static methods of
the Microsoft .NET framework with GHC 6.10.2 but I'm getting the follwoing
error:
GHC error in desugarer lookup in main:Main:
> Failed to load interface for `GHC.Dotnet':
> There are files missing in the `base' package,
> try running 'ghc-pkg check'.
> Use -v to see a list of the files searched for.
> ghc: panic! (the 'impossible' happened)
> (GHC version 6.10.2 for i386-unknown-mingw32):
> initDs IOEnv failure
>
My haskell code is this:
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Prelude
import Foreign
foreign import dotnet "static foo" foo :: Int -> Int
main = do print (foo 5)
To build the code above I'm doing like this: ghc -fvia-C Main.hs
Am I forgeting something? Does this version of GHC supports FFI for .NET?
Regards,
Guilherme Oliveira
MSc Student, UFPE - Brazil
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20090421/9eb15667/attachment.htm
More information about the Glasgow-haskell-users
mailing list