[commit: packages/Win32] ghc-head: Fix examples/hello.lhs to actually work (!) (881c4f4)

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


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

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

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

commit 881c4f40bd1307de975bb9d2f049879ba9c9a73b
Author: Bryan O'Sullivan <bos at serpentine.com>
Date:   Tue Feb 4 12:50:15 2014 -0800

    Fix examples/hello.lhs to actually work (!)


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

881c4f40bd1307de975bb9d2f049879ba9c9a73b
 examples/hello.lhs |   23 ++++++++---------------
 1 file changed, 8 insertions(+), 15 deletions(-)

diff --git a/examples/hello.lhs b/examples/hello.lhs
old mode 100644
new mode 100755
index c81b83b..7d20d01
--- a/examples/hello.lhs
+++ b/examples/hello.lhs
@@ -5,23 +5,16 @@
 Haskell version of "Hello, World" using the Win32 library.
 Demonstrates how the Win32 library can be put to use.
 
-Works with Hugs and GHC. To compile it up using the latter,
-do: "ghc -o main hello.lhs -syslib win32 -fglasgow-exts"
-
-For GHC 5.03:
-
-  ghc -package win32 hello.lhs -o hello.exe -optl "-Wl,--subsystem,windows"
-
 \begin{code}
+{-# LANGUAGE ScopedTypeVariables #-}
 module Main(main) where
 
+import Control.Exception (SomeException, bracket, catch)
+import Foreign.Ptr (nullPtr)
+import System.Exit (ExitCode(ExitSuccess), exitWith)
+import System.Win32.DLL (getModuleHandle)
 import qualified Graphics.Win32
-import qualified System.Win32.DLL
-import qualified System.Win32.Types
-import Control.Exception (bracket)
-import Foreign
-import System.Exit
-{-import Addr-}
+
 \end{code}
 
 Toplevel main just creates a window and pumps messages.
@@ -82,7 +75,7 @@ createWindow width height wndProc = do
   icon         <- Graphics.Win32.loadIcon   Nothing Graphics.Win32.iDI_APPLICATION
   cursor       <- Graphics.Win32.loadCursor Nothing Graphics.Win32.iDC_ARROW
   bgBrush      <- Graphics.Win32.createSolidBrush (Graphics.Win32.rgb 0 0 255)
-  mainInstance <- System.Win32.DLL.getModuleHandle Nothing
+  mainInstance <- getModuleHandle Nothing
   Graphics.Win32.registerClass
   	  ( Graphics.Win32.cS_VREDRAW + Graphics.Win32.cS_HREDRAW
 	  , mainInstance
@@ -112,7 +105,7 @@ messagePump :: Graphics.Win32.HWND -> IO ()
 messagePump hwnd = Graphics.Win32.allocaMessage $ \ msg ->
   let pump = do
         Graphics.Win32.getMessage msg (Just hwnd)
-		`catch` \ _ -> exitWith ExitSuccess
+		`catch` \ (_::SomeException) -> exitWith ExitSuccess
 	Graphics.Win32.translateMessage msg
 	Graphics.Win32.dispatchMessage msg
 	pump



More information about the ghc-commits mailing list