[Haskell-cafe] very hard to build darcs with win32 ghc-6.8.2!
Daniel Fischer
daniel.is.fischer at web.de
Wed Jun 4 17:28:52 EDT 2008
Am Mittwoch, 4. Juni 2008 22:26 schrieb Tim Newsham:
>
> Here's a small test program which uses FFI to SleepEx which I was
> not able to get working with win32 ghc-6.8.2.
>
> ------
> {-# OPTIONS -fglasgow-exts -fffi #-}
> module Main where
> import Foreign.C.Types
>
> foreign import ccall "SleepEx" c_SleepEx :: CUInt -> CInt -> IO CInt
I seem to remember it should be "stdcall" on windows.
That might also have a role in not finding SleepEx at 8.
>
> main = do
> putStrLn "start"
> n <- c_SleepEx (2*1000) 1
> print n
> -------
>
> So, what is going on with ghc-6.8.2? Why is the gcc so hard to use
> now? Why can't I get FFI working with standard win32 functions?
> Why aren't there prebuilt win32 darcs binaries anymore?
>
> Tim Newsham
> http://www.thenewsh.com/~newsham/
More information about the Haskell-Cafe
mailing list