From 65fe75a42c0bb6e145916e4dc4693a94d212850e Mon Sep 17 00:00:00 2001 From: Cheng Shao <terrorjack@type.dance> Date: Fri, 31 May 2024 17:05:07 +0000 Subject: [PATCH] libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. --- .../ghc-internal/include/windows_cconv.h | 12 ---------- .../src/GHC/Internal/Conc/POSIX.hs | 6 +---- .../src/GHC/Internal/Conc/Windows.hs | 3 --- .../src/GHC/Internal/Environment.hs | 10 -------- .../src/GHC/Internal/Event/Windows.hsc | 3 +-- .../src/GHC/Internal/Event/Windows/FFI.hsc | 24 +++++++++---------- .../src/GHC/Internal/IO/Encoding/CodePage.hs | 7 ++---- .../GHC/Internal/IO/Encoding/CodePage/API.hs | 10 ++++---- .../ghc-internal/src/GHC/Internal/IO/FD.hs | 16 +++---------- .../GHC/Internal/IO/Handle/Lock/Windows.hsc | 5 ++-- .../src/GHC/Internal/IO/Windows/Encoding.hs | 10 ++++---- .../src/GHC/Internal/IO/Windows/Handle.hsc | 19 +++++++-------- .../src/GHC/Internal/IO/Windows/Paths.hs | 2 -- .../src/GHC/Internal/System/Environment.hs | 20 ++++------------ .../GHC/Internal/System/Environment/Blank.hsc | 16 ++----------- .../System/Environment/ExecutablePath.hsc | 18 ++++---------- .../ghc-internal/src/GHC/Internal/Windows.hs | 6 ++--- utils/ghc-pkg/Main.hs | 10 -------- utils/runghc/Main.hs | 12 +--------- 19 files changed, 52 insertions(+), 157 deletions(-) delete mode 100644 libraries/ghc-internal/include/windows_cconv.h diff --git a/libraries/ghc-internal/include/windows_cconv.h b/libraries/ghc-internal/include/windows_cconv.h deleted file mode 100644 index 4fa84071c8a8..000000000000 --- a/libraries/ghc-internal/include/windows_cconv.h +++ /dev/null @@ -1,12 +0,0 @@ -#if !defined(__WINDOWS_CCONV_H) -#define __WINDOWS_CCONV_H - -#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 diff --git a/libraries/ghc-internal/src/GHC/Internal/Conc/POSIX.hs b/libraries/ghc-internal/src/GHC/Internal/Conc/POSIX.hs index 6be9ef2c7af8..fbe959661aa7 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Conc/POSIX.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Conc/POSIX.hs @@ -44,9 +44,6 @@ module GHC.Internal.Conc.POSIX , module GHC.Internal.Event.Windows.ConsoleEvent ) where - -#include "windows_cconv.h" - import GHC.Internal.Data.Bits (shiftR) import GHC.Internal.Base import GHC.Internal.Clock @@ -302,6 +299,5 @@ foreign import ccall unsafe "readIOManagerEvent" -- in the RTS (ThrIOManager.c) foreign import ccall unsafe "sendIOManagerEvent" -- in the RTS (ThrIOManager.c) c_sendIOManagerEvent :: Word32 -> IO () -foreign import WINDOWS_CCONV "WaitForSingleObject" +foreign import ccall "WaitForSingleObject" c_WaitForSingleObject :: HANDLE -> DWORD -> IO DWORD - diff --git a/libraries/ghc-internal/src/GHC/Internal/Conc/Windows.hs b/libraries/ghc-internal/src/GHC/Internal/Conc/Windows.hs index 9dcaac4a1eaa..8a1cea1265af 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Conc/Windows.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Conc/Windows.hs @@ -41,9 +41,6 @@ module GHC.Internal.Conc.Windows , module GHC.Internal.Event.Windows.ConsoleEvent ) where - -#include "windows_cconv.h" - import GHC.Internal.Base import GHC.Internal.Conc.Sync import qualified GHC.Internal.Conc.POSIX as POSIX diff --git a/libraries/ghc-internal/src/GHC/Internal/Environment.hs b/libraries/ghc-internal/src/GHC/Internal/Environment.hs index 6c78554c3052..8a9d21835f57 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Environment.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Environment.hs @@ -15,16 +15,6 @@ import GHC.Internal.Base import GHC.Internal.Real ( fromIntegral ) import GHC.Internal.IO.Encoding -#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 -#endif - -- | Computation 'getFullArgs' is the "raw" version of -- 'GHC.Internal.System.Environment.getArgs', similar to @argv@ in other languages. It -- returns a list of the program's command line arguments, starting with the diff --git a/libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc b/libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc index a882e2a62620..6d3042e2a5ef 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc +++ b/libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc @@ -72,7 +72,6 @@ module GHC.Internal.Event.Windows ( -- #define DEBUG_TRACE 1 -##include "windows_cconv.h" #include <windows.h> #include <ntstatus.h> #include <Rts.h> @@ -1225,7 +1224,7 @@ foreign import ccall unsafe "ioManagerFinished" -- in the RTS (ThrIOManager.c) foreign import ccall unsafe "rtsSupportsBoundThreads" threadedIOMgr :: Bool -- | Sleep for n ms -foreign import WINDOWS_CCONV unsafe "Sleep" sleepBlock :: Int -> IO () +foreign import ccall unsafe "Sleep" sleepBlock :: Int -> IO () -- --------------------------------------------------------------------------- -- I/O manager event notifications diff --git a/libraries/ghc-internal/src/GHC/Internal/Event/Windows/FFI.hsc b/libraries/ghc-internal/src/GHC/Internal/Event/Windows/FFI.hsc index 7c9619c079af..f4160da23fd0 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Event/Windows/FFI.hsc +++ b/libraries/ghc-internal/src/GHC/Internal/Event/Windows/FFI.hsc @@ -70,8 +70,6 @@ module GHC.Internal.Event.Windows.FFI ( #include <windows.h> #include "winio_structs.h" -##include "windows_cconv.h" - import GHC.Internal.Data.Maybe import GHC.Internal.Base import GHC.Internal.Num ((*)) @@ -109,7 +107,7 @@ type CompletionKey = ULONG_PTR -- cannot be easily changed. Associating a Handle with a Completion Port -- allows the I/O manager's worker threads to handle requests to the given -- handle. -foreign import WINDOWS_CCONV unsafe "windows.h CreateIoCompletionPort" +foreign import ccall unsafe "windows.h CreateIoCompletionPort" c_CreateIoCompletionPort :: HANDLE -> IOCP -> ULONG_PTR -> DWORD -> IO IOCP @@ -124,7 +122,7 @@ associateHandleWithIOCP iocp handle completionKey = failIf_ (/= iocp) "associateHandleWithIOCP" $ c_CreateIoCompletionPort handle iocp completionKey 0 -foreign import WINDOWS_CCONV safe "windows.h GetOverlappedResult" +foreign import ccall safe "windows.h GetOverlappedResult" c_GetOverlappedResult :: HANDLE -> LPOVERLAPPED -> Ptr DWORD -> BOOL -> IO BOOL @@ -137,7 +135,7 @@ getOverlappedResult handle lp block then fmap Just $ peek bytes else return Nothing -foreign import WINDOWS_CCONV safe "windows.h GetQueuedCompletionStatusEx" +foreign import ccall safe "windows.h GetQueuedCompletionStatusEx" c_GetQueuedCompletionStatusEx :: IOCP -> LPOVERLAPPED_ENTRY -> Word32 -> Ptr ULONG -> DWORD -> BOOL -> IO BOOL @@ -215,7 +213,7 @@ overlappedIONumBytes lpol = do return bytes {-# INLINE overlappedIONumBytes #-} -foreign import WINDOWS_CCONV unsafe "windows.h PostQueuedCompletionStatus" +foreign import ccall unsafe "windows.h PostQueuedCompletionStatus" c_PostQueuedCompletionStatus :: IOCP -> DWORD -> ULONG_PTR -> LPOVERLAPPED -> IO BOOL @@ -443,11 +441,11 @@ withRequest async offset hdl cb f = do -- | Create an event object for use when the HANDLE isn't asynchronous -foreign import WINDOWS_CCONV unsafe "windows.h CreateEventW" +foreign import ccall unsafe "windows.h CreateEventW" c_CreateEvent :: Ptr () -> Bool -> Bool -> LPCWSTR -> IO HANDLE -- | Close a handle object -foreign import WINDOWS_CCONV unsafe "windows.h CloseHandle" +foreign import ccall unsafe "windows.h CloseHandle" c_CloseHandle :: HANDLE -> IO Bool ------------------------------------------------------------------------ @@ -455,7 +453,7 @@ foreign import WINDOWS_CCONV unsafe "windows.h CloseHandle" -- | CancelIo shouldn't block, but cancellation happens infrequently, -- so we might as well be on the safe side. -foreign import WINDOWS_CCONV unsafe "windows.h CancelIoEx" +foreign import ccall unsafe "windows.h CancelIoEx" c_CancelIoEx :: HANDLE -> LPOVERLAPPED -> IO BOOL -- | Cancel all pending overlapped I/O for the given file that was initiated by @@ -471,7 +469,7 @@ cancelIoEx' = c_CancelIoEx ------------------------------------------------------------------------ -- Monotonic time -foreign import WINDOWS_CCONV "windows.h GetTickCount64" +foreign import ccall "windows.h GetTickCount64" c_GetTickCount64 :: IO #{type ULONGLONG} -- | Call the @GetTickCount64@ function, which returns a monotonic time in @@ -519,10 +517,10 @@ queryPerformanceFrequency = do type QPFunc = Ptr Int64 -> IO BOOL -foreign import WINDOWS_CCONV "Windows.h QueryPerformanceCounter" +foreign import ccall "Windows.h QueryPerformanceCounter" c_QueryPerformanceCounter :: QPFunc -foreign import WINDOWS_CCONV "Windows.h QueryPerformanceFrequency" +foreign import ccall "Windows.h QueryPerformanceFrequency" c_QueryPerformanceFrequency :: QPFunc callQP :: QPFunc -> IO (Maybe Int64) @@ -548,5 +546,5 @@ throwWinErr loc err = do setLastError :: ErrCode -> IO () setLastError = c_SetLastError -foreign import WINDOWS_CCONV unsafe "windows.h SetLastError" +foreign import ccall unsafe "windows.h SetLastError" c_SetLastError :: ErrCode -> IO () diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs b/libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs index f9d78e60fedf..3c6468f4a8ba 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs +++ b/libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage.hs @@ -41,8 +41,6 @@ import GHC.Internal.IO.Encoding.UTF32 (mkUTF32le, mkUTF32be) import GHC.Internal.Windows (DWORD) -#include "windows_cconv.h" - type CodePage = DWORD -- note CodePage = UInt which might not work on Win64. But the Win32 package @@ -55,10 +53,10 @@ getCurrentCodePage = do else getACP -- Since the Win32 package depends on base, we have to import these ourselves: -foreign import WINDOWS_CCONV unsafe "windows.h GetConsoleCP" +foreign import ccall unsafe "windows.h GetConsoleCP" getConsoleCP :: IO Word32 -foreign import WINDOWS_CCONV unsafe "windows.h GetACP" +foreign import ccall unsafe "windows.h GetACP" getACP :: IO Word32 {-# NOINLINE currentCodePage #-} @@ -184,4 +182,3 @@ indexChar :: ConvArray Char -> Int -> Char indexChar (ConvArray p) (I# i) = C# (chr# (int16ToInt# (indexInt16OffAddr# p i))) #endif - diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/API.hs b/libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/API.hs index 2c4532360e2c..bbee22cfa852 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/API.hs +++ b/libraries/ghc-internal/src/GHC/Internal/IO/Encoding/CodePage/API.hs @@ -47,8 +47,6 @@ debugIO s | c_DEBUG_DUMP = puts s | otherwise = return () -#include "windows_cconv.h" - type LPCSTR = Ptr Word8 @@ -88,12 +86,12 @@ pokeArray' msg sz ptr xs | length xs == sz = pokeArray ptr xs | otherwise = errorWithoutStackTrace $ msg ++ ": expected " ++ show sz ++ " elements in list but got " ++ show (length xs) -foreign import WINDOWS_CCONV unsafe "windows.h GetCPInfo" +foreign import ccall unsafe "windows.h GetCPInfo" c_GetCPInfo :: UINT -- ^ CodePage -> Ptr CPINFO -- ^ lpCPInfo -> IO BOOL -foreign import WINDOWS_CCONV unsafe "windows.h MultiByteToWideChar" +foreign import ccall unsafe "windows.h MultiByteToWideChar" c_MultiByteToWideChar :: UINT -- ^ CodePage -> DWORD -- ^ dwFlags -> LPCSTR -- ^ lpMultiByteStr @@ -102,7 +100,7 @@ foreign import WINDOWS_CCONV unsafe "windows.h MultiByteToWideChar" -> CInt -- ^ cchWideChar -> IO CInt -foreign import WINDOWS_CCONV unsafe "windows.h WideCharToMultiByte" +foreign import ccall unsafe "windows.h WideCharToMultiByte" c_WideCharToMultiByte :: UINT -- ^ CodePage -> DWORD -- ^ dwFlags -> LPWSTR -- ^ lpWideCharStr @@ -113,7 +111,7 @@ foreign import WINDOWS_CCONV unsafe "windows.h WideCharToMultiByte" -> LPBOOL -- ^ lpUsedDefaultChar -> IO CInt -foreign import WINDOWS_CCONV unsafe "windows.h IsDBCSLeadByteEx" +foreign import ccall unsafe "windows.h IsDBCSLeadByteEx" c_IsDBCSLeadByteEx :: UINT -- ^ CodePage -> BYTE -- ^ TestChar -> IO BOOL diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/FD.hs b/libraries/ghc-internal/src/GHC/Internal/IO/FD.hs index de227b20aa39..37b5edb37434 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/FD.hs +++ b/libraries/ghc-internal/src/GHC/Internal/IO/FD.hs @@ -62,16 +62,6 @@ import qualified GHC.Internal.System.Posix.Internals import GHC.Internal.System.Posix.Internals hiding (FD, setEcho, getEcho) import GHC.Internal.System.Posix.Types -#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 -#endif - c_DEBUG_DUMP :: Bool c_DEBUG_DUMP = False @@ -421,7 +411,7 @@ release fd = do _ <- unlockFile (fromIntegral $ fdFD fd) return () #if defined(mingw32_HOST_OS) -foreign import WINDOWS_CCONV unsafe "HsBase.h closesocket" +foreign import ccall unsafe "HsBase.h closesocket" c_closesocket :: CInt -> IO CInt #endif @@ -774,10 +764,10 @@ blockingWriteRawBufferPtr loc !fd !buf !off !len -- NOTE: "safe" versions of the read/write calls for use by the threaded RTS. -- These calls may block, but that's ok. -foreign import WINDOWS_CCONV safe "recv" +foreign import ccall safe "recv" c_safe_recv :: CInt -> Ptr Word8 -> CInt -> CInt{-flags-} -> IO CInt -foreign import WINDOWS_CCONV safe "send" +foreign import ccall safe "send" c_safe_send :: CInt -> Ptr Word8 -> CInt -> CInt{-flags-} -> IO CInt #endif diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc b/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc index ecc4f46a4cdc..400bcbef75b4 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc +++ b/libraries/ghc-internal/src/GHC/Internal/IO/Handle/Lock/Windows.hsc @@ -14,7 +14,6 @@ module GHC.Internal.IO.Handle.Lock.Windows where import GHC.Types () #else -##include <windows_cconv.h> #include <windows.h> import GHC.Internal.Data.Bits @@ -128,12 +127,12 @@ foreign import ccall unsafe "_get_osfhandle" c_get_osfhandle :: CInt -> IO HANDLE -- https://msdn.microsoft.com/en-us/library/windows/desktop/aa365203.aspx -foreign import WINDOWS_CCONV interruptible "LockFileEx" +foreign import ccall interruptible "LockFileEx" c_LockFileEx :: HANDLE -> DWORD -> DWORD -> DWORD -> DWORD -> LPOVERLAPPED -> IO BOOL -- https://msdn.microsoft.com/en-us/library/windows/desktop/aa365716.aspx -foreign import WINDOWS_CCONV interruptible "UnlockFileEx" +foreign import ccall interruptible "UnlockFileEx" c_UnlockFileEx :: HANDLE -> DWORD -> DWORD -> DWORD -> LPOVERLAPPED -> IO BOOL #endif diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Encoding.hs b/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Encoding.hs index 2fdfe216dd46..3dd595cc9f70 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Encoding.hs +++ b/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Encoding.hs @@ -37,8 +37,6 @@ import GHC.Internal.IO import GHC.Internal.Base import GHC.Internal.Real -#include "windows_cconv.h" - -- | The "System.IO" output functions (e.g. `putStr`) don't -- automatically convert to multibyte string on Windows, so this -- function is provided to make the conversion from a Unicode string @@ -83,7 +81,7 @@ encodeMultiByteRawIO _ "" = return (nullPtr, 0) encodeMultiByteRawIO cp s = encodeMultiByteIO' cp s toSizedCString where toSizedCString (st,l) = return (st, fromIntegral l) -foreign import WINDOWS_CCONV "WideCharToMultiByte" +foreign import ccall "WideCharToMultiByte" wideCharToMultiByte :: CodePage -> DWORD -- dwFlags, @@ -121,7 +119,7 @@ stringToUnicode cp mbstr = cwstr wchars peekCWStringLen (cwstr,fromIntegral wchars') -- converts UTF-16 to [Char] -foreign import WINDOWS_CCONV unsafe "MultiByteToWideChar" +foreign import ccall unsafe "MultiByteToWideChar" multiByteToWideChar :: CodePage -> DWORD -- dwFlags, @@ -140,7 +138,7 @@ decodeMultiByteIO :: CodePage -> String -> IO String decodeMultiByteIO = stringToUnicode {-# INLINE decodeMultiByteIO #-} -foreign import WINDOWS_CCONV unsafe "MultiByteToWideChar" +foreign import ccall unsafe "MultiByteToWideChar" multiByteToWideChar' :: CodePage -> DWORD -- dwFlags, @@ -165,7 +163,7 @@ withGhcInternalToUTF16 ptr len fn multiByteToWideChar' cp 0 ptr (fromIntegral len) cwstr wchars fn (cwstr, wchars') -foreign import WINDOWS_CCONV "WideCharToMultiByte" +foreign import ccall "WideCharToMultiByte" wideCharToMultiByte' :: CodePage -> DWORD -- dwFlags, diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc b/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc index d47c2b90fb00..5113ff0f44e0 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc +++ b/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc @@ -53,7 +53,6 @@ module GHC.Internal.IO.Windows.Handle #include <windows.h> #include <ntstatus.h> #include <winnt.h> -##include "windows_cconv.h" -- Can't avoid these semantics leaks, they are base constructs import GHC.Internal.Data.Bits ((.|.), (.&.), shiftL) @@ -344,23 +343,23 @@ type PINPUT_RECORD = Ptr () -- Foreign imports -foreign import WINDOWS_CCONV safe "windows.h CreateFileW" +foreign import ccall safe "windows.h CreateFileW" c_CreateFile :: LPCTSTR -> DWORD -> DWORD -> LPSECURITY_ATTRIBUTES -> DWORD -> DWORD -> HANDLE -> IO HANDLE -foreign import WINDOWS_CCONV safe "windows.h SetFileCompletionNotificationModes" +foreign import ccall safe "windows.h SetFileCompletionNotificationModes" c_SetFileCompletionNotificationModes :: HANDLE -> UCHAR -> IO BOOL -foreign import WINDOWS_CCONV safe "windows.h ReadFile" +foreign import ccall safe "windows.h ReadFile" c_ReadFile :: HANDLE -> LPVOID -> DWORD -> LPDWORD -> LPOVERLAPPED -> IO BOOL -foreign import WINDOWS_CCONV safe "windows.h WriteFile" +foreign import ccall safe "windows.h WriteFile" c_WriteFile :: HANDLE -> LPVOID -> DWORD -> LPDWORD -> LPOVERLAPPED -> IO BOOL -foreign import WINDOWS_CCONV safe "windows.h GetStdHandle" +foreign import ccall safe "windows.h GetStdHandle" c_GetStdHandle :: StdHandleId -> IO HANDLE foreign import ccall safe "__handle_ready" @@ -411,18 +410,18 @@ foreign import ccall safe "__get_console_buffer_size" foreign import ccall safe "__set_console_buffer_size" c_set_console_buffer_size :: HANDLE -> CLong -> IO BOOL -foreign import WINDOWS_CCONV safe "windows.h ReadConsoleW" +foreign import ccall safe "windows.h ReadConsoleW" c_read_console :: HANDLE -> Ptr Word16 -> DWORD -> Ptr DWORD -> PCONSOLE_READCONSOLE_CONTROL -> IO BOOL -foreign import WINDOWS_CCONV safe "windows.h WriteConsoleW" +foreign import ccall safe "windows.h WriteConsoleW" c_write_console :: HANDLE -> Ptr Word16 -> DWORD -> Ptr DWORD -> Ptr () -> IO BOOL -foreign import WINDOWS_CCONV safe "windows.h ReadConsoleInputW" +foreign import ccall safe "windows.h ReadConsoleInputW" c_read_console_input :: HANDLE -> PINPUT_RECORD -> DWORD -> LPDWORD -> IO BOOL -foreign import WINDOWS_CCONV safe "windows.h GetNumberOfConsoleInputEvents" +foreign import ccall safe "windows.h GetNumberOfConsoleInputEvents" c_get_num_console_inputs :: HANDLE -> LPDWORD -> IO BOOL type LPSECURITY_ATTRIBUTES = LPVOID diff --git a/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Paths.hs b/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Paths.hs index e8ef6ba28487..532cf1fc5ad7 100644 --- a/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Paths.hs +++ b/libraries/ghc-internal/src/GHC/Internal/IO/Windows/Paths.hs @@ -22,8 +22,6 @@ module GHC.Internal.IO.Windows.Paths (getDevicePath ) where -#include "windows_cconv.h" - import GHC.Internal.Base import GHC.Internal.IO diff --git a/libraries/ghc-internal/src/GHC/Internal/System/Environment.hs b/libraries/ghc-internal/src/GHC/Internal/System/Environment.hs index fa89b0d3327e..df95a3bd6470 100644 --- a/libraries/ghc-internal/src/GHC/Internal/System/Environment.hs +++ b/libraries/ghc-internal/src/GHC/Internal/System/Environment.hs @@ -64,16 +64,6 @@ import GHC.Internal.System.Posix.Internals (withFilePath) import GHC.Internal.System.Environment.ExecutablePath -#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 -#endif - #include "HsBaseConfig.h" -- --------------------------------------------------------------------------- @@ -158,7 +148,7 @@ getEnv name = lookupEnv name >>= maybe handleError return eRROR_ENVVAR_NOT_FOUND :: DWORD eRROR_ENVVAR_NOT_FOUND = 203 -foreign import WINDOWS_CCONV unsafe "windows.h GetLastError" +foreign import ccall unsafe "windows.h GetLastError" c_GetLastError:: IO DWORD #else @@ -182,7 +172,7 @@ lookupEnv name = withCWString name $ \s -> try_size s 256 _ | res > size -> try_size s res -- Rare: size increased between calls to GetEnvironmentVariable | otherwise -> peekCWString p_value >>= return . Just -foreign import WINDOWS_CCONV unsafe "windows.h GetEnvironmentVariableW" +foreign import ccall unsafe "windows.h GetEnvironmentVariableW" c_GetEnvironmentVariable :: LPWSTR -> LPWSTR -> DWORD -> IO DWORD #else lookupEnv name = @@ -249,7 +239,7 @@ setEnv_ key value = withCWString key $ \k -> withCWString value $ \v -> do success <- c_SetEnvironmentVariable k v unless success (throwGetLastError "setEnv") -foreign import WINDOWS_CCONV unsafe "windows.h SetEnvironmentVariableW" +foreign import ccall unsafe "windows.h SetEnvironmentVariableW" c_SetEnvironmentVariable :: LPTSTR -> LPTSTR -> IO Bool #else @@ -380,10 +370,10 @@ getEnvironment = bracket c_GetEnvironmentStrings c_FreeEnvironmentStrings $ \pBl c <- peek pBlock' seekNull pBlock' (c == (0 :: Word8 )) -foreign import WINDOWS_CCONV unsafe "windows.h GetEnvironmentStringsW" +foreign import ccall unsafe "windows.h GetEnvironmentStringsW" c_GetEnvironmentStrings :: IO (Ptr CWchar) -foreign import WINDOWS_CCONV unsafe "windows.h FreeEnvironmentStringsW" +foreign import ccall unsafe "windows.h FreeEnvironmentStringsW" c_FreeEnvironmentStrings :: Ptr CWchar -> IO Bool #else getEnvironment = do diff --git a/libraries/ghc-internal/src/GHC/Internal/System/Environment/Blank.hsc b/libraries/ghc-internal/src/GHC/Internal/System/Environment/Blank.hsc index 4c5360220ae8..75362fb2c591 100644 --- a/libraries/ghc-internal/src/GHC/Internal/System/Environment/Blank.hsc +++ b/libraries/ghc-internal/src/GHC/Internal/System/Environment/Blank.hsc @@ -73,18 +73,6 @@ import GHC.Internal.System.Environment import qualified GHC.Internal.System.Environment as Environment #endif --- TODO: include windows_cconv.h when it's merged, instead of duplicating --- this C macro block. -#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 -#endif - #include "HsBaseConfig.h" throwInvalidArgument :: String -> IO a @@ -142,7 +130,7 @@ setEnv_ key value = withCWString key $ \k -> withCWString value $ \v -> do success <- c_SetEnvironmentVariable k v unless success (throwGetLastError "setEnv") -foreign import WINDOWS_CCONV unsafe "windows.h SetEnvironmentVariableW" +foreign import ccall unsafe "windows.h SetEnvironmentVariableW" c_SetEnvironmentVariable :: LPTSTR -> LPTSTR -> IO Bool #else setEnv_ key value = @@ -179,7 +167,7 @@ unsetEnv key = withCWString key $ \k -> do eRROR_ENVVAR_NOT_FOUND :: DWORD eRROR_ENVVAR_NOT_FOUND = 203 -foreign import WINDOWS_CCONV unsafe "windows.h GetLastError" +foreign import ccall unsafe "windows.h GetLastError" c_GetLastError:: IO DWORD #elif HAVE_UNSETENV # if !UNSETENV_RETURNS_VOID diff --git a/libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc b/libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc index a06b39f8f8b6..5e1daa944205 100644 --- a/libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc +++ b/libraries/ghc-internal/src/GHC/Internal/System/Environment/ExecutablePath.hsc @@ -304,14 +304,6 @@ executablePath = Just (fmap Just getExecutablePath `catch` f) #elif 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 - getExecutablePath = go 2048 -- plenty, PATH_MAX is 512 under Win32 where go size = allocaArray (fromIntegral size) $ \ buf -> do @@ -366,13 +358,13 @@ getFinalPath path = withCWString path $ \s -> -- is large enough. bufSize = 1024 -foreign import WINDOWS_CCONV unsafe "windows.h GetModuleFileNameW" +foreign import ccall unsafe "windows.h GetModuleFileNameW" c_GetModuleFileName :: Ptr () -> CWString -> Word32 -> IO Word32 -foreign import WINDOWS_CCONV unsafe "windows.h PathFileExistsW" +foreign import ccall unsafe "windows.h PathFileExistsW" c_pathFileExists :: CWString -> IO Bool -foreign import WINDOWS_CCONV unsafe "windows.h CreateFileW" +foreign import ccall unsafe "windows.h CreateFileW" c_createFile :: CWString -> Word32 -> Word32 @@ -391,10 +383,10 @@ createFile file = (#const FILE_ATTRIBUTE_NORMAL) nullPtr -foreign import WINDOWS_CCONV unsafe "windows.h CloseHandle" +foreign import ccall unsafe "windows.h CloseHandle" c_closeHandle :: Ptr () -> IO Bool -foreign import WINDOWS_CCONV unsafe "windows.h GetFinalPathNameByHandleW" +foreign import ccall unsafe "windows.h GetFinalPathNameByHandleW" c_getFinalPathHandle :: Ptr () -> CWString -> Word32 -> Word32 -> IO Word32 -------------------------------------------------------------------------------- diff --git a/libraries/ghc-internal/src/GHC/Internal/Windows.hs b/libraries/ghc-internal/src/GHC/Internal/Windows.hs index cf970a4c061d..c1ba44c95c33 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Windows.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Windows.hs @@ -97,8 +97,6 @@ import GHC.Internal.System.IO.Error import qualified GHC.Internal.Numeric -#include "windows_cconv.h" - type BOOL = Bool type LPBOOL = Ptr BOOL type BYTE = Word8 @@ -222,11 +220,11 @@ foreign import ccall unsafe "maperrno_func" -- in Win32Utils.c foreign import ccall unsafe "base_getErrorMessage" -- in Win32Utils.c c_getErrorMessage :: DWORD -> IO LPWSTR -foreign import WINDOWS_CCONV unsafe "windows.h LocalFree" +foreign import ccall unsafe "windows.h LocalFree" localFree :: Ptr a -> IO (Ptr a) -- | Get the last system error produced in the current thread. -foreign import WINDOWS_CCONV unsafe "windows.h GetLastError" +foreign import ccall unsafe "windows.h GetLastError" getLastError :: IO ErrCode ---------------------------------------------------------------- diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index 767fa69129f9..9192959b9a2b 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -96,16 +96,6 @@ import System.Posix hiding (fdToHandle) import qualified System.Info(os) #endif -#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 -#endif - -- | Short-circuit 'any' with a \"monadic predicate\". anyM :: (Monad m) => (a -> m Bool) -> [a] -> m Bool anyM _ [] = return False diff --git a/utils/runghc/Main.hs b/utils/runghc/Main.hs index 858f199abafb..a7170c8701d5 100644 --- a/utils/runghc/Main.hs +++ b/utils/runghc/Main.hs @@ -34,16 +34,6 @@ import Foreign.C.String import System.Posix.Process (executeFile) #endif -#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 -#endif - main :: IO () main = do args <- getArgs @@ -209,7 +199,7 @@ getExecPath = try_size 2048 -- plenty, PATH_MAX is 512 under Win32. _ | ret < size -> fmap Just $ peekCWString buf | otherwise -> try_size (size * 2) -foreign import WINDOWS_CCONV unsafe "windows.h GetModuleFileNameW" +foreign import ccall unsafe "windows.h GetModuleFileNameW" c_GetModuleFileName :: Ptr () -> CWString -> Word32 -> IO Word32 #else getExecPath = Just <$> getExecutablePath -- GitLab