Repository : ssh://darcs.haskell.org//srv/darcs/packages/Win32

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/f065e76290149350f20eda0a24fc45f6ee0e2088

>---------------------------------------------------------------

commit f065e76290149350f20eda0a24fc45f6ee0e2088
Author: Ian Lynagh <[email protected]>
Date:   Thu Mar 15 22:48:07 2012 +0000

    Fix Graphics/Win32/Window.hsc on Win64

>---------------------------------------------------------------

 Graphics/Win32/Window.hsc |    8 +++++---
 1 files changed, 5 insertions(+), 3 deletions(-)

diff --git a/Graphics/Win32/Window.hsc b/Graphics/Win32/Window.hsc
index 39a494e..aa586c7 100644
--- a/Graphics/Win32/Window.hsc
+++ b/Graphics/Win32/Window.hsc
@@ -1,3 +1,4 @@
+{-# LANGUAGE CApiFFI #-}
 #if __GLASGOW_HASKELL__ >= 701
 {-# LANGUAGE Trustworthy #-}
 #endif
@@ -186,10 +187,11 @@ foreign import stdcall "wrapper"
 setWindowClosure :: HWND -> WindowClosure -> IO ()
 setWindowClosure wnd closure = do
   fp <- mkWindowClosure closure
-  _ <- c_SetWindowLong wnd (#{const GWL_USERDATA}) (castFunPtrToLONG fp)
+  _ <- c_SetWindowLongPtr wnd (#{const GWLP_USERDATA})
+                              (castPtr (castFunPtrToPtr fp))
   return ()
-foreign import stdcall unsafe "windows.h SetWindowLongW"
-  c_SetWindowLong :: HWND -> INT -> LONG -> IO LONG
+foreign import capi unsafe "windows.h SetWindowLongPtrW"
+  c_SetWindowLongPtr :: HWND -> INT -> Ptr LONG -> IO (Ptr LONG)
 
 createWindow
   :: ClassName -> String -> WindowStyle ->



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to