[commit: packages/Win32] ghc-head: Complete support for base 4.6 (e2d75e9)

git at git.haskell.org git at git.haskell.org
Tue Mar 18 10:16:11 UTC 2014


Repository : ssh://git@git.haskell.org/Win32

On branch  : ghc-head
Link       : http://git.haskell.org/packages/Win32.git/commitdiff/e2d75e9bc3faf7377ae27601265795878f9fa44c

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

commit e2d75e9bc3faf7377ae27601265795878f9fa44c
Author: Bryan O'Sullivan <bos at serpentine.com>
Date:   Tue Feb 4 12:14:34 2014 -0800

    Complete support for base 4.6
    
    We now make a lot of imports more explicit, too.


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

e2d75e9bc3faf7377ae27601265795878f9fa44c
 Graphics/Win32/Control.hsc |   16 +++++++++-------
 Graphics/Win32/Window.hsc  |   26 ++++++++++++++++++--------
 System/Win32/Registry.hsc  |   20 ++++++++++++++------
 3 files changed, 41 insertions(+), 21 deletions(-)

diff --git a/Graphics/Win32/Control.hsc b/Graphics/Win32/Control.hsc
old mode 100644
new mode 100755
index 84842b8..6e680ab
--- a/Graphics/Win32/Control.hsc
+++ b/Graphics/Win32/Control.hsc
@@ -17,13 +17,15 @@
 
 module Graphics.Win32.Control where
 
-import Graphics.Win32.GDI.Types
-import Graphics.Win32.Window
-import System.Win32.Types
-import Graphics.Win32.Message
-
-import Foreign
-import System.IO.Unsafe
+import Data.Bits ((.|.))
+import Graphics.Win32.GDI.Types (HMENU, HWND)
+import Graphics.Win32.Message (WindowMessage)
+import Graphics.Win32.Window (ClassName, Pos, WindowStyle, maybePos)
+import Graphics.Win32.Window (c_CreateWindowEx)
+import System.IO.Unsafe (unsafePerformIO)
+import System.Win32.Types (HANDLE, UINT, maybePtr, newTString, withTString)
+import System.Win32.Types (failIfFalse_, failIfNull, failIfZero)
+import Foreign.Ptr (nullPtr)
 
 ##include "windows_cconv.h"
 
diff --git a/Graphics/Win32/Key.hsc b/Graphics/Win32/Key.hsc
old mode 100644
new mode 100755
diff --git a/Graphics/Win32/Window.hsc b/Graphics/Win32/Window.hsc
old mode 100644
new mode 100755
index 791549a..abb9e15
--- a/Graphics/Win32/Window.hsc
+++ b/Graphics/Win32/Window.hsc
@@ -18,14 +18,24 @@
 
 module Graphics.Win32.Window where
 
-import System.Win32.Types
-import Graphics.Win32.GDI.Types
-import Graphics.Win32.Message
-
-import Control.Monad
-import Data.Maybe
-import Foreign
-import System.IO.Unsafe
+import Control.Monad (liftM)
+import Data.Maybe (fromMaybe)
+import Data.Word (Word32)
+import Foreign.ForeignPtr (withForeignPtr)
+import Foreign.Marshal.Alloc (allocaBytes)
+import Foreign.Ptr (FunPtr, Ptr, castFunPtrToPtr, castPtr, nullPtr)
+import Foreign.Storable (pokeByteOff)
+import Graphics.Win32.GDI.Types (HBITMAP, HCURSOR, HDC, HDWP, HRGN, HWND, PRGN)
+import Graphics.Win32.GDI.Types (HBRUSH, HICON, HMENU, prim_ChildWindowFromPoint)
+import Graphics.Win32.GDI.Types (LPRECT, RECT, allocaRECT, peekRECT, withRECT)
+import Graphics.Win32.GDI.Types (POINT, allocaPOINT, peekPOINT, withPOINT)
+import Graphics.Win32.GDI.Types (prim_ChildWindowFromPointEx)
+import Graphics.Win32.Message (WindowMessage)
+import System.IO.Unsafe (unsafePerformIO)
+import System.Win32.Types (ATOM, maybePtr, newTString, ptrToMaybe, numToMaybe)
+import System.Win32.Types (Addr, BOOL, DWORD, INT, LONG, LRESULT, UINT, WPARAM)
+import System.Win32.Types (HINSTANCE, LPARAM, LPCTSTR, LPVOID, withTString)
+import System.Win32.Types (failIf, failIf_, failIfFalse_, failIfNull, maybeNum)
 
 ##include "windows_cconv.h"
 
diff --git a/System/Win32/Registry.hsc b/System/Win32/Registry.hsc
old mode 100644
new mode 100755
index 9d9f6ce..cb9cd8e
--- a/System/Win32/Registry.hsc
+++ b/System/Win32/Registry.hsc
@@ -60,12 +60,20 @@ module System.Win32.Registry
 
 -}
 
-import System.Win32.Time
-import System.Win32.Types
-import System.Win32.File
-
-import System.IO.Unsafe
-import Foreign
+import Data.Word (Word32)
+import Foreign.ForeignPtr (withForeignPtr)
+import Foreign.Marshal.Alloc (alloca, allocaBytes, free, mallocBytes)
+import Foreign.Marshal.Array (allocaArray0)
+import Foreign.Marshal.Utils (maybeWith, with)
+import Foreign.Ptr (Ptr, castPtr, nullPtr)
+import Foreign.Storable (peek, peekByteOff, peekElemOff, sizeOf)
+import System.IO.Unsafe (unsafePerformIO)
+import System.Win32.File (LPSECURITY_ATTRIBUTES)
+import System.Win32.Time (FILETIME)
+import System.Win32.Types (DWORD, ErrCode, HKEY, LPCTSTR, PKEY, withTString)
+import System.Win32.Types (HANDLE, LONG, LPBYTE, newForeignHANDLE, peekTString)
+import System.Win32.Types (LPTSTR, TCHAR, failUnlessSuccess, withTStringLen)
+import System.Win32.Types (castUINTPtrToPtr, failUnlessSuccessOr, maybePtr)
 
 ##include "windows_cconv.h"
 



More information about the ghc-commits mailing list