
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

Hi Guilherme, the support for 'dotnet' FFI declarations isn't really there any longer, having bitrotted badly and hasn't been in use for a number of years. (I'd suggest removing the final vestiges of them from the codebase, actually.) You may want to have a look at http://haskell.forkIO.com/dotnet/ instead. --sigbjorn On 4/21/2009 18:56, Guilherme Oliveira wrote:
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
------------------------------------------------------------------------
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (2)
-
Guilherme Oliveira
-
Sigbjorn Finne