[commit: ghc] master: base: Fix CPUTime on Windows (286c65f)

git at git.haskell.org git at git.haskell.org
Sun Mar 20 23:32:33 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/286c65f2c7b193311d0710e7de30f4e8c76a84cf/ghc

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

commit 286c65f2c7b193311d0710e7de30f4e8c76a84cf
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sun Mar 20 22:15:46 2016 +0100

    base: Fix CPUTime on Windows
    
    Arg, silly CPP.


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

286c65f2c7b193311d0710e7de30f4e8c76a84cf
 libraries/base/System/CPUTime/Windows.hsc | 25 +++++++++++--------------
 1 file changed, 11 insertions(+), 14 deletions(-)

diff --git a/libraries/base/System/CPUTime/Windows.hsc b/libraries/base/System/CPUTime/Windows.hsc
index d1ca856..3f8c9ea 100644
--- a/libraries/base/System/CPUTime/Windows.hsc
+++ b/libraries/base/System/CPUTime/Windows.hsc
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, CApiFFI, NumDecimals #-}
+{-# LANGUAGE CPP, CApiFFI, NondecreasingIndentation, NumDecimals #-}
 
 #include "HsFFI.h"
 #include "HsBaseConfig.h"
@@ -8,7 +8,6 @@ module System.CPUTime.Windows
     , getCpuTimePrecision
     ) where
 
-import Data.Ratio
 import Foreign
 import Foreign.C
 
@@ -17,16 +16,6 @@ import Foreign.C
 #include <windows.h>
 #endif
 
-#ifdef mingw32_HOST_OS
-# if defined(i386_HOST_ARCH)
-#  define WINDOWS_CCONV stdcall
-# elif defined(x86_64_HOST_ARCH)
-#  define WINDOWS_CCONV ccall
-# else
-#  error Unknown mingw32 arch
-# endif
-#endif
-
 getCPUTime :: IO Integer
 getCPUTime = do
      -- NOTE: GetProcessTimes() is only supported on NT-based OSes.
@@ -61,6 +50,14 @@ getCpuTimePrecision = return 16e9
 
 type FILETIME = ()
 type HANDLE = ()
+
 -- need proper Haskell names (initial lower-case character)
-foreign import WINDOWS_CCONV unsafe "GetCurrentProcess" getCurrentProcess :: IO (Ptr HANDLE)
-foreign import WINDOWS_CCONV unsafe "GetProcessTimes" getProcessTimes :: Ptr HANDLE -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> IO CInt
+#if defined(i386_HOST_ARCH)
+foreign import stdcall unsafe "GetCurrentProcess" getCurrentProcess :: IO (Ptr HANDLE)
+foreign import stdcall unsafe "GetProcessTimes" getProcessTimes :: Ptr HANDLE -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> IO CInt
+#elif defined(x86_64_HOST_ARCH)
+foreign import ccall unsafe "GetCurrentProcess" getCurrentProcess :: IO (Ptr HANDLE)
+foreign import ccall unsafe "GetProcessTimes" getProcessTimes :: Ptr HANDLE -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> IO CInt
+#else
+#error Unknown mingw32 arch
+#endif



More information about the ghc-commits mailing list