[Git][ghc/ghc][wip/rip-stdcall] 3 commits: testsuite: adapt the testsuite for stdcall removal

Cheng Shao (@TerrorJack) gitlab at gitlab.haskell.org
Sat Jun 1 02:02:09 UTC 2024



Cheng Shao pushed to branch wip/rip-stdcall at Glasgow Haskell Compiler / GHC


Commits:
c422bc8f by Cheng Shao at 2024-06-01T02:01:26+00:00
testsuite: adapt the testsuite for stdcall removal

This patch adjusts test cases to handle the stdcall removal:

- Some stdcall usages are replaced with ccall since stdcall doesn't
  make sense anymore.
- We also preserve some stdcall usages, and check in the expected
  warning messages to ensure GHC always warn about stdcall usages
  (-Wunsupported-calling-conventions) as expected.
- Error code testsuite coverage is slightly improved,
  -Wunsupported-calling-conventions is now tested.
- Obsolete code paths related to i386 windows are also removed.

- - - - -
4cfbee50 by Cheng Shao at 2024-06-01T02:01:51+00:00
docs: minor adjustments for stdcall removal

This commit include minor adjustments of documentation related to
stdcall removal.

- - - - -
52c56d53 by Cheng Shao at 2024-06-01T02:01:51+00:00
docs: mention i386 Windows removal in 9.12 changelog

This commit mentions removal of i386 Windows support and stdcall
related change in the 9.12 changelog.

- - - - -


30 changed files:

- docs/users_guide/9.12.1-notes.rst
- docs/users_guide/using-warnings.rst
- docs/users_guide/win32-dlls.rst
- testsuite/tests/concurrent/should_run/T5611.hs
- testsuite/tests/concurrent/should_run/T5611a.hs
- testsuite/tests/concurrent/should_run/conc036.hs
- testsuite/tests/concurrent/should_run/conc037.hs
- testsuite/tests/concurrent/should_run/conc038.hs
- testsuite/tests/concurrent/should_run/foreignInterruptible.hs
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/ffi/should_compile/all.T
- testsuite/tests/ffi/should_compile/cc004.hs
- testsuite/tests/ffi/should_run/T1288.hs
- testsuite/tests/ffi/should_run/T1288_c.c
- testsuite/tests/ffi/should_run/T1288_ghci.hs
- testsuite/tests/ffi/should_run/T1288_ghci_c.c
- testsuite/tests/ffi/should_run/T22159.hs
- testsuite/tests/ffi/should_run/T2276.hs
- testsuite/tests/ffi/should_run/T2276_c.c
- testsuite/tests/ffi/should_run/T2276_ghci.hs
- testsuite/tests/ffi/should_run/T2276_ghci_c.c
- testsuite/tests/ffi/should_run/all.T
- + testsuite/tests/ffi/should_run/ffi012.ghc.stderr
- testsuite/tests/rts/Makefile
- testsuite/tests/rts/T12497.hs
- testsuite/tests/rts/T7037_main.c
- testsuite/tests/rts/all.T
- testsuite/tests/rts/linker/T11223/all.T
- testsuite/tests/th/T23309A.hs
- testsuite/timeout/WinCBindings.hsc


Changes:

=====================================
docs/users_guide/9.12.1-notes.rst
=====================================
@@ -60,6 +60,15 @@ Compiler
 
 - :ghc-flag:`-Wderiving-typeable` has been added to :ghc-flag:`-Wall`.
 
+- i386 Windows support is now completely removed amid massive cleanup
+  of legacy code to pave way for Arm64 Windows support (`#24883
+  <https://gitlab.haskell.org/ghc/ghc/-/issues/24883>`_). Rest
+  assured, this does not impact existing support for x86_64 Windows or
+  i386 Linux. For end users, the ``stdcall`` C calling convention is
+  now fully deprecated and GHC will unconditionally produce a warning
+  and treat it as ``ccall``. All C import/export declarations on
+  Windows should now use ``ccall``.
+
 GHCi
 ~~~~
 


=====================================
docs/users_guide/using-warnings.rst
=====================================
@@ -694,8 +694,7 @@ of ``-W(no-)*``.
 
     Causes a warning to be emitted for foreign declarations that use
     unsupported calling conventions. In particular, if the ``stdcall``
-    calling convention is used on an architecture other than i386 then
-    it will be treated as ``ccall``.
+    calling convention is used then it will be treated as ``ccall``.
 
 .. ghc-flag:: -Wdodgy-foreign-imports
     :shortdesc: warn about dodgy foreign imports


=====================================
docs/users_guide/win32-dlls.rst
=====================================
@@ -319,7 +319,7 @@ to call from the outside. For example:
     adder :: Int -> Int -> IO Int  -- gratuitous use of IO
     adder x y = return (x+y)
 
-    foreign export stdcall adder :: Int -> Int -> IO Int
+    foreign export ccall adder :: Int -> Int -> IO Int
 
 Add some helper code that starts up and shuts down the Haskell RTS:
 


=====================================
testsuite/tests/concurrent/should_run/T5611.hs
=====================================
@@ -7,7 +7,7 @@ import System.IO
 
 #if defined(mingw32_HOST_OS)
 sleep n = sleepBlock (n*1000)
-foreign import stdcall safe "Sleep" sleepBlock :: Int -> IO ()
+foreign import ccall safe "Sleep" sleepBlock :: Int -> IO ()
 #else
 sleep n = void $ sleepBlock n
 foreign import ccall safe "sleep" sleepBlock :: Int -> IO Int


=====================================
testsuite/tests/concurrent/should_run/T5611a.hs
=====================================
@@ -9,7 +9,7 @@ import System.IO
 
 #if defined(mingw32_HOST_OS)
 sleep n = sleepBlock (n*1000)
-foreign import stdcall unsafe "Sleep" sleepBlock :: Int -> IO ()
+foreign import ccall unsafe "Sleep" sleepBlock :: Int -> IO ()
 #else
 sleep n = void $ sleepBlock n
 foreign import ccall unsafe "sleep" sleepBlock :: Int -> IO Int


=====================================
testsuite/tests/concurrent/should_run/conc036.hs
=====================================
@@ -10,7 +10,7 @@ import System.IO
 
 #if defined(mingw32_HOST_OS)
 sleep n = sleepBlock (n*1000)
-foreign import stdcall unsafe "Sleep" sleepBlock :: Int -> IO ()
+foreign import ccall unsafe "Sleep" sleepBlock :: Int -> IO ()
 #else
 sleep n = sleepBlock n
 foreign import ccall unsafe "sleep" sleepBlock :: Int -> IO ()


=====================================
testsuite/tests/concurrent/should_run/conc037.hs
=====================================
@@ -5,7 +5,7 @@ module Main where
 import Control.Concurrent
 
 #if defined(mingw32_HOST_OS)
-foreign import stdcall safe "Sleep" _sleepBlock :: Int -> IO ()
+foreign import ccall safe "Sleep" _sleepBlock :: Int -> IO ()
 sleepBlock n = _sleepBlock (n*1000)
 #else
 foreign import ccall safe "sleep" sleepBlock :: Int -> IO ()
@@ -24,4 +24,3 @@ main = do
   x <- takeMVar th
   putStrLn x
   putStrLn "\nshutting down"
-  


=====================================
testsuite/tests/concurrent/should_run/conc038.hs
=====================================
@@ -11,7 +11,7 @@ foreign export ccall "hFun"  haskellFun :: Int -> IO ()
 foreign import ccall safe "hFun"  hFun :: Int -> IO ()
 
 #if defined(mingw32_HOST_OS)
-foreign import stdcall safe "Sleep" _sleepBlock :: Int -> IO ()
+foreign import ccall safe "Sleep" _sleepBlock :: Int -> IO ()
 sleepBlock n = _sleepBlock (n*1000)
 #else
 foreign import ccall safe "sleep" sleepBlock :: Int -> IO ()
@@ -34,4 +34,3 @@ main = do
   x <- takeMVar th
   putStrLn x
   putStrLn "\nshutting down"
-


=====================================
testsuite/tests/concurrent/should_run/foreignInterruptible.hs
=====================================
@@ -8,7 +8,7 @@ import System.IO
 
 #if defined(mingw32_HOST_OS)
 sleep n = sleepBlock (n*1000)
-foreign import stdcall interruptible "Sleep" sleepBlock :: Int -> IO ()
+foreign import ccall interruptible "Sleep" sleepBlock :: Int -> IO ()
 #else
 sleep n = sleepBlock n
 foreign import ccall interruptible "sleep" sleepBlock :: Int -> IO ()


=====================================
testsuite/tests/diagnostic-codes/codes.stdout
=====================================
@@ -56,7 +56,6 @@
 [GHC-63055] is untested (constructor = TcRnFieldUpdateInvalidType)
 [GHC-26133] is untested (constructor = TcRnForeignImportPrimSafeAnn)
 [GHC-03355] is untested (constructor = TcRnIllegalForeignDeclBackend)
-[GHC-01245] is untested (constructor = TcRnUnsupportedCallConv)
 [GHC-01570] is untested (constructor = TcRnExpectedValueId)
 [GHC-96665] is untested (constructor = TcRnMultipleInlinePragmas)
 [GHC-88293] is untested (constructor = TcRnUnexpectedPragmas)
@@ -119,5 +118,3 @@
 [GHC-75721] is untested (constructor = CannotRepresentType)
 [GHC-17599] is untested (constructor = AddTopDeclsUnexpectedDeclarationSplice)
 [GHC-86934] is untested (constructor = ClassPE)
-
-


=====================================
testsuite/tests/ffi/should_compile/all.T
=====================================
@@ -6,13 +6,7 @@ setTestOpts(ffi)
 
 test('cc001', normal, compile, [''])
 
-# Non-static C call
-# cc004 test also uses stdcall, so it only works on i386.
-if config.platform.startswith('i386-'):
-    ways = normal
-else:
-    ways = expect_fail
-test('cc004', ways, compile, [''])
+test('cc004', expect_fail, compile, [''])
 
 test('cc005', normal, compile, [''])
 test('cc007', normal, compile, [''])


=====================================
testsuite/tests/ffi/should_compile/cc004.hs
=====================================
@@ -9,15 +9,9 @@ import Data.Word
 
 -- importing functions
 
--- We can't import the same function using both stdcall and ccall
--- calling conventions in the same file when compiling via C (this is a
--- restriction in the C backend caused by the need to emit a prototype
--- for stdcall functions).
 foreign import stdcall        "p" m_stdcall :: StablePtr a -> IO (StablePtr b)
 foreign import ccall   unsafe "q" m_ccall   :: ByteArray# -> IO Int
 
--- We can't redefine the calling conventions of certain functions (those from
--- math.h).
 foreign import stdcall "my_sin" my_sin :: Double -> IO Double
 foreign import stdcall "my_cos" my_cos :: Double -> IO Double
 
@@ -65,4 +59,3 @@ type Sink2 b = Ptr b
 
 foreign import ccall unsafe "dynamic"
   sink2 :: Ptr (Sink2 b) -> Sink2 b
-


=====================================
testsuite/tests/ffi/should_run/T1288.hs
=====================================
@@ -1,6 +1,6 @@
 import Foreign
 import Foreign.C
 
-foreign import stdcall "test" ctest :: CInt -> IO ()
+foreign import ccall "test" ctest :: CInt -> IO ()
 
 main = ctest 3


=====================================
testsuite/tests/ffi/should_run/T1288_c.c
=====================================
@@ -1,6 +1,6 @@
 #include <stdio.h>
 
-void __attribute__((stdcall)) test(int arg)
+void test(int arg)
 {
    printf("The argument passed was %i\n", arg );
 }


=====================================
testsuite/tests/ffi/should_run/T1288_ghci.hs
=====================================
@@ -1,6 +1,6 @@
 import Foreign
 import Foreign.C
 
-foreign import stdcall "test" ctest :: CInt -> IO ()
+foreign import ccall "test" ctest :: CInt -> IO ()
 
 main = ctest 3


=====================================
testsuite/tests/ffi/should_run/T1288_ghci_c.c
=====================================
@@ -1,6 +1,6 @@
 #include <stdio.h>
 
-void __attribute__((stdcall)) test(int arg)
+void test(int arg)
 {
    printf("The argument passed was %i\n", arg );
 }


=====================================
testsuite/tests/ffi/should_run/T22159.hs
=====================================
@@ -1,20 +1,12 @@
 {-# LANGUAGE CPP #-}
 module Main (main) where
 
-#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
-
 import Foreign.C.String (peekCWString)
 import Foreign.C.Types (CWchar)
 import Foreign.Marshal.Alloc (allocaBytes)
 import Foreign.Ptr (Ptr)
 
-foreign import WINDOWS_CCONV "hello" c_hello :: Ptr CWchar -> IO ()
+foreign import ccall "hello" c_hello :: Ptr CWchar -> IO ()
 
 main :: IO ()
 main = allocaBytes 12 $ \buf -> do


=====================================
testsuite/tests/ffi/should_run/T2276.hs
=====================================
@@ -1,7 +1,7 @@
 import Foreign
 import Foreign.C
 
-foreign import stdcall "&test" ptest :: FunPtr (CInt -> IO ())
-foreign import stdcall "dynamic" ctest :: FunPtr (CInt -> IO ()) -> CInt -> IO ()
+foreign import ccall "&test" ptest :: FunPtr (CInt -> IO ())
+foreign import ccall "dynamic" ctest :: FunPtr (CInt -> IO ()) -> CInt -> IO ()
 
 main = ctest ptest 3


=====================================
testsuite/tests/ffi/should_run/T2276_c.c
=====================================
@@ -1,6 +1,6 @@
 #include <stdio.h>
 
-void __attribute__((stdcall)) test(int arg)
+void test(int arg)
 {
    printf("The argument passed was %i\n", arg );
 }


=====================================
testsuite/tests/ffi/should_run/T2276_ghci.hs
=====================================
@@ -1,7 +1,7 @@
 import Foreign
 import Foreign.C
 
-foreign import stdcall "&test" ptest :: FunPtr (CInt -> IO ())
-foreign import stdcall "dynamic" ctest :: FunPtr (CInt -> IO ()) -> CInt -> IO ()
+foreign import ccall "&test" ptest :: FunPtr (CInt -> IO ())
+foreign import ccall "dynamic" ctest :: FunPtr (CInt -> IO ()) -> CInt -> IO ()
 
 main = ctest ptest 3


=====================================
testsuite/tests/ffi/should_run/T2276_ghci_c.c
=====================================
@@ -1,6 +1,6 @@
 #include <stdio.h>
 
-void __attribute__((stdcall)) test(int arg)
+void test(int arg)
 {
    printf("The argument passed was %i\n", arg );
 }


=====================================
testsuite/tests/ffi/should_run/all.T
=====================================
@@ -61,17 +61,7 @@ else:
 test('ffi010', normal, compile_and_run, [''])
 test('ffi011', normal, compile_and_run, [''])
 
-# The stdcall calling convention works on Windows, and sometimes on
-# Linux, and fails everywhhere else.  For now, we test only on Windows,
-# because it's difficult to discover whether a given Linux supports
-# it.
-
-if config.os == 'mingw32':
-    skip_if_not_windows = normal
-else:
-    skip_if_not_windows = skip
-
-test('ffi012', skip_if_not_windows, compile_and_run, [''])
+test('ffi012', normal, warn_and_run, [''])
 test('ffi013', [normal, js_broken(22363)], compile_and_run, [''])
 
 # threaded2 sometimes gives ffi014: Main_dDu: interrupted


=====================================
testsuite/tests/ffi/should_run/ffi012.ghc.stderr
=====================================
@@ -0,0 +1,52 @@
+[1 of 2] Compiling Main             ( ffi012.hs, ffi012.o )
+ffi012.hs:11:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)]
+    • the 'stdcall' calling convention is unsupported on this platform,
+      treating as ccall
+    • When checking declaration:
+        foreign import stdcall safe "wrapper" wrap_f :: F -> IO (FunPtr F)
+
+ffi012.hs:12:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)]
+    • the 'stdcall' calling convention is unsupported on this platform,
+      treating as ccall
+    • When checking declaration:
+        foreign import stdcall safe "wrapper" wrap_f_io
+          :: IOF -> IO (FunPtr IOF)
+
+ffi012.hs:14:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)]
+    • the 'stdcall' calling convention is unsupported on this platform,
+      treating as ccall
+    • When checking declaration:
+        foreign import stdcall safe "dynamic" f :: FunPtr F -> F
+
+ffi012.hs:15:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)]
+    • the 'stdcall' calling convention is unsupported on this platform,
+      treating as ccall
+    • When checking declaration:
+        foreign import stdcall safe "dynamic" f_io :: FunPtr IOF -> IOF
+
+ffi012.hs:28:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)]
+    • the 'stdcall' calling convention is unsupported on this platform,
+      treating as ccall
+    • When checking declaration:
+        foreign import stdcall safe "wrapper" wrap_d :: D -> IO (FunPtr D)
+
+ffi012.hs:29:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)]
+    • the 'stdcall' calling convention is unsupported on this platform,
+      treating as ccall
+    • When checking declaration:
+        foreign import stdcall safe "wrapper" wrap_d_io
+          :: IOD -> IO (FunPtr IOD)
+
+ffi012.hs:31:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)]
+    • the 'stdcall' calling convention is unsupported on this platform,
+      treating as ccall
+    • When checking declaration:
+        foreign import stdcall safe "dynamic" d :: FunPtr D -> D
+
+ffi012.hs:32:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)]
+    • the 'stdcall' calling convention is unsupported on this platform,
+      treating as ccall
+    • When checking declaration:
+        foreign import stdcall safe "dynamic" d_io :: FunPtr IOD -> IOD
+
+[2 of 2] Linking ffi012


=====================================
testsuite/tests/rts/Makefile
=====================================
@@ -64,16 +64,11 @@ T6006_setup :
 T8124_setup :
 	'$(TEST_HC)' $(TEST_HC_OPTS) -c T8124.hs
 
-ifeq "$(TARGETPLATFORM)" "i386-unknown-mingw32"
-T7037_CONST = const
-else
-T7037_CONST =
-endif
 .PHONY: T7037
 T7037:
 	$(RM) 7037.o 7037.hi 7037$(exeext)
 	"$(TEST_HC)" $(TEST_HC_OPTS) T7037.hs -v0
-	"$(TEST_HC)" -optc-DT7037_CONST=$(T7037_CONST) $(filter-out -rtsopts, $(TEST_HC_OPTS)) T7037_main.c -v0 -o T7037_main -no-hs-main
+	"$(TEST_HC)" $(filter-out -rtsopts, $(TEST_HC_OPTS)) T7037_main.c -v0 -o T7037_main -no-hs-main
 	./T7037_main
 
 T7040_ghci_setup :


=====================================
testsuite/tests/rts/T12497.hs
=====================================
@@ -1,17 +1,7 @@
-{-# LANGUAGE CPP #-}
-
-#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
-
 import Foreign.C.String
 
-foreign import WINDOWS_CCONV "_strdup" strdup :: CString -> IO CString
-foreign import WINDOWS_CCONV "strdup" strdup2 :: CString -> IO CString
+foreign import ccall "_strdup" strdup :: CString -> IO CString
+foreign import ccall "strdup" strdup2 :: CString -> IO CString
 
 dupString :: String -> IO String
 dupString str = newCString str >>= strdup >>= peekCString


=====================================
testsuite/tests/rts/T7037_main.c
=====================================
@@ -2,6 +2,6 @@
 #include <unistd.h>
 
 int main(int argc, char *argv[]) {
-    char * T7037_CONST args[2] = {"T7037", NULL};
+    char * args[2] = {"T7037", NULL};
     execv("./T7037", args);
 }


=====================================
testsuite/tests/rts/all.T
=====================================
@@ -239,8 +239,6 @@ def config_T5250(name, opts):
 
 test('T5250', [extra_files(['spalign.c']),
                 config_T5250,
-                # stack ptr is not 16-byte aligned on 32-bit Windows
-                when(platform('i386-unknown-mingw32'), expect_fail),
                 when(platform('i386-unknown-linux'),
                             expect_broken_for(4211,['llvm']))],
               compile_and_run, ['spalign.c'])


=====================================
testsuite/tests/rts/linker/T11223/all.T
=====================================
@@ -5,7 +5,7 @@ import re
 # Python normalization functions
 #--------------------------------------
 def normalise_duplicate_errmsg( msg ):
-     return re.sub(r"((?:[a-z, A-Z]+):|)[\/\\\\]+(?:.+[\/\\\\]+?)?(.+?)[\/\\\\]+", "    ", 
+     return re.sub(r"((?:[a-z, A-Z]+):|)[\/\\\\]+(?:.+[\/\\\\]+?)?(.+?)[\/\\\\]+", "    ",
                re.sub(r"version\s(\d+\.\d+\.\d+)\sfor\s[a-z,A-Z,0-9,_,-]+(?=\))", r"", msg))
 
 #--------------------------------------
@@ -33,7 +33,6 @@ test('T11223_simple_duplicate',
 
 test('T11223_simple_duplicate_lib',
      [extra_files(['bar.c', 'foo.c', 'foo.hs']),
-      when(platform('i386-unknown-mingw32'), expect_broken(13515)),
       when(ghc_dynamic(), skip), normalise_errmsg_fun(normalise_duplicate_errmsg),
       req_c],
      makefile_test, ['t_11223_simple_duplicate_lib'])


=====================================
testsuite/tests/th/T23309A.hs
=====================================
@@ -1,19 +1,6 @@
-{-# LANGUAGE CPP #-}
 module T23309A (c_foo) where
 
 import Foreign.C.String
 import Foreign.C.Types
 
-#if defined(mingw32_HOST_OS)
-# if defined(i386_HOST_ARCH)
-#  define CALLCONV stdcall
-# elif defined(x86_64_HOST_ARCH)
-#  define CALLCONV ccall
-# else
-#  error Unknown mingw32 arch
-# endif
-#else
-# define CALLCONV ccall
-#endif
-
-foreign import CALLCONV unsafe "foo" c_foo :: CInt -> IO CString
+foreign import ccall unsafe "foo" c_foo :: CInt -> IO CString


=====================================
testsuite/timeout/WinCBindings.hsc
=====================================
@@ -3,14 +3,6 @@ module WinCBindings where
 
 #if defined(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
-
 import Foreign
 import Foreign.C.Types
 import System.Win32.File
@@ -253,7 +245,7 @@ instance Storable JOBOBJECT_ASSOCIATE_COMPLETION_PORT where
             jacpCompletionPort = vCompletionPort}
 
 
-foreign import WINDOWS_CCONV unsafe "windows.h WaitForSingleObject"
+foreign import ccall unsafe "windows.h WaitForSingleObject"
     waitForSingleObject :: HANDLE -> DWORD -> IO DWORD
 
 type JOBOBJECTINFOCLASS = CInt
@@ -294,22 +286,22 @@ cCREATE_SUSPENDED = #const CREATE_SUSPENDED
 cHANDLE_FLAG_INHERIT :: DWORD
 cHANDLE_FLAG_INHERIT = #const HANDLE_FLAG_INHERIT
 
-foreign import WINDOWS_CCONV unsafe "windows.h GetExitCodeProcess"
+foreign import ccall unsafe "windows.h GetExitCodeProcess"
     getExitCodeProcess :: HANDLE -> LPDWORD -> IO BOOL
 
-foreign import WINDOWS_CCONV unsafe "windows.h CloseHandle"
+foreign import ccall unsafe "windows.h CloseHandle"
     closeHandle :: HANDLE -> IO BOOL
 
-foreign import WINDOWS_CCONV unsafe "windows.h TerminateJobObject"
+foreign import ccall unsafe "windows.h TerminateJobObject"
     terminateJobObject :: HANDLE -> UINT -> IO BOOL
 
-foreign import WINDOWS_CCONV unsafe "windows.h AssignProcessToJobObject"
+foreign import ccall unsafe "windows.h AssignProcessToJobObject"
     assignProcessToJobObject :: HANDLE -> HANDLE -> IO BOOL
 
-foreign import WINDOWS_CCONV unsafe "windows.h CreateJobObjectW"
+foreign import ccall unsafe "windows.h CreateJobObjectW"
     createJobObjectW :: LPSECURITY_ATTRIBUTES -> LPCTSTR -> IO HANDLE
 
-foreign import WINDOWS_CCONV unsafe "windows.h CreateProcessW"
+foreign import ccall unsafe "windows.h CreateProcessW"
     createProcessW :: LPCTSTR -> LPTSTR
                    -> LPSECURITY_ATTRIBUTES -> LPSECURITY_ATTRIBUTES
                    -> BOOL -> DWORD -> LPVOID -> LPCTSTR -> LPSTARTUPINFO
@@ -317,16 +309,16 @@ foreign import WINDOWS_CCONV unsafe "windows.h CreateProcessW"
 
 foreign import ccall unsafe "string.h" memset :: Ptr a -> CInt -> CSize -> IO (Ptr a)
 
-foreign import WINDOWS_CCONV unsafe "windows.h SetInformationJobObject"
+foreign import ccall unsafe "windows.h SetInformationJobObject"
     setInformationJobObject :: HANDLE -> JOBOBJECTINFOCLASS -> LPVOID -> DWORD -> IO BOOL
 
-foreign import WINDOWS_CCONV unsafe "windows.h CreateIoCompletionPort"
+foreign import ccall unsafe "windows.h CreateIoCompletionPort"
     createIoCompletionPort :: HANDLE -> HANDLE -> ULONG_PTR -> DWORD -> IO HANDLE
 
-foreign import WINDOWS_CCONV unsafe "windows.h GetQueuedCompletionStatus"
+foreign import ccall unsafe "windows.h GetQueuedCompletionStatus"
     getQueuedCompletionStatus :: HANDLE -> LPDWORD -> PULONG_PTR -> Ptr LPOVERLAPPED -> DWORD -> IO BOOL
 
-foreign import WINDOWS_CCONV unsafe "windows.h SetHandleInformation"
+foreign import ccall unsafe "windows.h SetHandleInformation"
     setHandleInformation :: HANDLE -> DWORD -> DWORD -> IO BOOL
 
 setJobParameters :: HANDLE -> IO BOOL
@@ -394,4 +386,3 @@ waitForJobCompletion _hJob ioPort timeout
                 then False -- Timeout occurred. *dark voice* YOU HAVE FAILED THIS TEST!.
                 else True
 #endif
-



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/efd3176cf386bd5ec2da8d07766ffb9f2871a48d...52c56d53b4ceecab7ee178497166be79b0b5918e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/efd3176cf386bd5ec2da8d07766ffb9f2871a48d...52c56d53b4ceecab7ee178497166be79b0b5918e
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240531/6090cd0f/attachment-0001.html>


More information about the ghc-commits mailing list