summaryrefslogtreecommitdiff
path: root/libraries
diff options
context:
space:
mode:
authorsimonmar <unknown>2005-01-28 13:36:34 +0000
committersimonmar <unknown>2005-01-28 13:36:34 +0000
commit2940ff3f0ca9aa4a4522ee61fea054052921c397 (patch)
treeee318335bbdc5d44e3dd51918d93c0c6a8de1edf /libraries
parent3a682aa855ace3304e7ce1c7bd965316053ebb25 (diff)
downloadhaskell-2940ff3f0ca9aa4a4522ee61fea054052921c397.tar.gz
[project @ 2005-01-28 13:36:25 by simonmar]
Catch up with updates to platform #defines. Generally: use _HOST_ rather than _TARGET_ (except in Cabal where we have to retain compatibility with previous GHC versions).
Diffstat (limited to 'libraries')
-rw-r--r--libraries/base/Debug/Trace.hs6
-rw-r--r--libraries/base/Foreign/C/String.hs6
-rw-r--r--libraries/base/GHC/Conc.lhs14
-rw-r--r--libraries/base/GHC/ConsoleHandler.hs4
-rw-r--r--libraries/base/GHC/Handle.hs24
-rw-r--r--libraries/base/GHC/IO.hs6
-rw-r--r--libraries/base/GHC/Unicode.hs2
-rw-r--r--libraries/base/System/CPUTime.hsc4
-rw-r--r--libraries/base/System/Cmd.hs6
-rw-r--r--libraries/base/System/Directory.hs14
-rw-r--r--libraries/base/System/Directory/Internals.hs8
-rw-r--r--libraries/base/System/Environment.hs2
-rw-r--r--libraries/base/System/Info.hs28
-rw-r--r--libraries/base/System/Posix/Internals.hs10
-rw-r--r--libraries/base/System/Posix/Signals.hsc12
-rw-r--r--libraries/base/System/Process.hs14
-rw-r--r--libraries/base/System/Process/Internals.hs8
-rw-r--r--libraries/base/System/Time.hsc8
-rw-r--r--libraries/base/cbits/consUtils.c6
-rw-r--r--libraries/base/cbits/dirUtils.c6
-rw-r--r--libraries/base/cbits/execvpe.c2
-rw-r--r--libraries/base/cbits/inputReady.c4
-rw-r--r--libraries/base/cbits/lockFile.c4
-rw-r--r--libraries/base/cbits/runProcess.c4
-rw-r--r--libraries/base/cbits/timeUtils.c2
-rw-r--r--libraries/base/include/HsBase.h40
-rw-r--r--libraries/base/include/lockFile.h4
-rw-r--r--libraries/base/include/runProcess.h4
-rw-r--r--libraries/base/package.conf.in4
29 files changed, 137 insertions, 119 deletions
diff --git a/libraries/base/Debug/Trace.hs b/libraries/base/Debug/Trace.hs
index 8b85f62f20..b442a11f60 100644
--- a/libraries/base/Debug/Trace.hs
+++ b/libraries/base/Debug/Trace.hs
@@ -22,7 +22,7 @@ module Debug.Trace (
-- ** Tracers
-- | The tracer is a function that monitors the trace messages.
fileTracer, -- :: Handle -> String -> IO ()
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
winDebugTracer, -- :: String -> IO ()
#endif
addTracer, -- :: String -> (String -> IO ()) -> IO ()
@@ -38,7 +38,7 @@ import Data.IORef
import System.IO.Unsafe
import System.IO
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
import Foreign.C.String
#endif
@@ -54,7 +54,7 @@ fileTracer handle msg = do
hPutStr handle msg
hPutChar handle '\n'
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
-- | A tracer function that outputs the message to the debuger (Windows only)
winDebugTracer :: String -- ^ trace message
-> IO ()
diff --git a/libraries/base/Foreign/C/String.hs b/libraries/base/Foreign/C/String.hs
index 03826dd438..56548839a0 100644
--- a/libraries/base/Foreign/C/String.hs
+++ b/libraries/base/Foreign/C/String.hs
@@ -444,7 +444,7 @@ wNUL = 0
cWcharsToChars :: [CWchar] -> [Char]
charsToCWchars :: [Char] -> [CWchar]
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
-- On Windows, wchar_t is 16 bits wide and CWString uses the UTF-16 encoding.
@@ -465,7 +465,7 @@ charsToCWchars = foldr utf16Char [] . map ord
fromIntegral (c' `div` 0x400 + 0xd800) :
fromIntegral (c' `mod` 0x400 + 0xdc00) : wcs
-#else /* !mingw32_TARGET_OS */
+#else /* !mingw32_HOST_OS */
cWcharsToChars xs = map castCWcharToChar xs
charsToCWchars xs = map castCharToCWchar xs
@@ -479,4 +479,4 @@ castCWcharToChar ch = chr (fromIntegral ch )
castCharToCWchar :: Char -> CWchar
castCharToCWchar ch = fromIntegral (ord ch)
-#endif /* !mingw32_TARGET_OS */
+#endif /* !mingw32_HOST_OS */
diff --git a/libraries/base/GHC/Conc.lhs b/libraries/base/GHC/Conc.lhs
index 7c65383785..5fd03709b4 100644
--- a/libraries/base/GHC/Conc.lhs
+++ b/libraries/base/GHC/Conc.lhs
@@ -55,7 +55,7 @@ module GHC.Conc
, writeTVar -- :: a -> TVar a -> STM ()
, unsafeIOToSTM -- :: IO a -> STM a
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
, asyncRead -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
, asyncWrite -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
, asyncDoProc -- :: FunPtr (Ptr a -> IO Int) -> Ptr a -> IO Int
@@ -388,7 +388,7 @@ addMVarFinalizer (MVar m) finalizer =
%************************************************************************
\begin{code}
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
-- Note: threadDelay, threadWaitRead and threadWaitWrite aren't really functional
-- on Win32, but left in there because lib code (still) uses them (the manner
@@ -432,7 +432,7 @@ asyncWriteBA fd isSock len off bufB =
-- given file descriptor (GHC only).
threadWaitRead :: Fd -> IO ()
threadWaitRead fd
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
| threaded = waitForReadEvent fd
#endif
| otherwise = IO $ \s ->
@@ -444,7 +444,7 @@ threadWaitRead fd
-- given file descriptor (GHC only).
threadWaitWrite :: Fd -> IO ()
threadWaitWrite fd
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
| threaded = waitForWriteEvent fd
#endif
| otherwise = IO $ \s ->
@@ -465,7 +465,7 @@ threadWaitWrite fd
--
threadDelay :: Int -> IO ()
threadDelay time
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
| threaded = waitForDelayEvent time
#else
| threaded = c_Sleep (fromIntegral (time `quot` 1000))
@@ -476,7 +476,7 @@ threadDelay time
}}
-- On Windows, we just make a safe call to 'Sleep' to implement threadDelay.
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
foreign import ccall safe "Sleep" c_Sleep :: CInt -> IO ()
#endif
@@ -514,7 +514,7 @@ foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
-- - forkProcess will kill the IO manager thread. Let's just
-- hope we don't need to do any blocking IO between fork & exec.
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
data IOReq
= Read {-# UNPACK #-} !Fd {-# UNPACK #-} !(MVar ())
diff --git a/libraries/base/GHC/ConsoleHandler.hs b/libraries/base/GHC/ConsoleHandler.hs
index 761926db4f..8a9e2e0f77 100644
--- a/libraries/base/GHC/ConsoleHandler.hs
+++ b/libraries/base/GHC/ConsoleHandler.hs
@@ -13,7 +13,7 @@
--
-----------------------------------------------------------------------------
module GHC.ConsoleHandler
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
where
import Prelude -- necessary to get dependencies right
#else /* whole file */
@@ -88,4 +88,4 @@ installHandler handler =
foreign import ccall unsafe "Signals.h stg_InstallConsoleEvent"
rts_installHandler :: CInt -> Ptr (StablePtr (CInt -> IO ())) -> IO CInt
-#endif /* mingw32_TARGET_OS */
+#endif /* mingw32_HOST_OS */
diff --git a/libraries/base/GHC/Handle.hs b/libraries/base/GHC/Handle.hs
index d433962687..223c94e2ab 100644
--- a/libraries/base/GHC/Handle.hs
+++ b/libraries/base/GHC/Handle.hs
@@ -27,7 +27,7 @@ module GHC.Handle (
readRawBuffer, readRawBufferPtr,
writeRawBuffer, writeRawBufferPtr,
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
unlockFile,
#endif
@@ -374,7 +374,7 @@ newEmptyBuffer b state size
allocateBuffer :: Int -> BufferState -> IO Buffer
allocateBuffer sz@(I# size) state = IO $ \s ->
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
-- To implement asynchronous I/O under Win32, we have to pass
-- buffer references to external threads that handles the
-- filling/emptying of their contents. Hence, the buffer cannot
@@ -525,7 +525,7 @@ fillReadBufferWithoutBlocking fd is_stream
-- Low level routines for reading/writing to (raw)buffers:
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
readRawBuffer :: String -> FD -> Bool -> RawBuffer -> Int -> CInt -> IO CInt
readRawBuffer loc fd is_stream buf off len =
throwErrnoIfMinus1RetryMayBlock loc
@@ -568,7 +568,7 @@ foreign import ccall unsafe "__hscore_PrelHandle_write"
foreign import ccall unsafe "__hscore_PrelHandle_write"
write_off :: CInt -> Ptr CChar -> Int -> CInt -> IO CInt
-#else /* mingw32_TARGET_OS.... */
+#else /* mingw32_HOST_OS.... */
readRawBuffer :: String -> FD -> Bool -> RawBuffer -> Int -> CInt -> IO CInt
readRawBuffer loc fd is_stream buf off len
@@ -787,7 +787,7 @@ openFile' filepath mode binary =
let
oflags1 = case mode of
ReadMode -> read_flags
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
WriteMode -> write_flags .|. o_TRUNC
#else
WriteMode -> write_flags
@@ -818,7 +818,7 @@ openFile' filepath mode binary =
-- ASSERT: if we just created the file, then openFd won't fail
-- (so we don't need to worry about removing the newly created file
-- in the event of an error).
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
if mode == WriteMode
then throwErrnoIf (/=0) "openFile"
(c_ftruncate (fromIntegral fd) 0)
@@ -913,7 +913,7 @@ openFd fd mb_fd_type is_socket filepath mode binary = do
-- regular files need to be locked
RegularFile -> do
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
r <- lockFile (fromIntegral fd) (fromBool write) 1{-exclusive-}
when (r == -1) $
ioException (IOError Nothing ResourceBusy "openFile"
@@ -929,7 +929,7 @@ fdToHandle fd = do
openFd fd Nothing False{-XXX!-} fd_str mode True{-bin mode-}
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
foreign import ccall unsafe "lockFile"
lockFile :: CInt -> CInt -> CInt -> IO CInt
@@ -1043,7 +1043,7 @@ hClose_handle_ handle_ = do
case haOtherSide handle_ of
Nothing ->
throwErrnoIfMinus1Retry_ "hClose"
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
(closeFd (haIsStream handle_) c_fd)
#else
(c_close c_fd)
@@ -1053,7 +1053,7 @@ hClose_handle_ handle_ = do
-- free the spare buffers
writeIORef (haBuffers handle_) BufferListNil
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
-- unlock it
unlockFile c_fd
#endif
@@ -1205,7 +1205,7 @@ hSetBuffering handle mode =
is_tty <- fdIsTTY (haFD handle_)
when (is_tty && isReadableHandleType (haType handle_)) $
case mode of
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
-- 'raw' mode under win32 is a bit too specialised (and troublesome
-- for most common uses), so simply disable its use here.
NoBuffering -> setCooked (haFD handle_) False
@@ -1358,7 +1358,7 @@ hTell :: Handle -> IO Integer
hTell handle =
wantSeekableHandle "hGetPosn" handle $ \ handle_ -> do
-#if defined(mingw32_TARGET_OS)
+#if defined(mingw32_HOST_OS)
-- urgh, on Windows we have to worry about \n -> \r\n translation,
-- so we can't easily calculate the file position using the
-- current buffer size. Just flush instead.
diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs
index 9959914945..aa4c0c8f7e 100644
--- a/libraries/base/GHC/IO.hs
+++ b/libraries/base/GHC/IO.hs
@@ -47,7 +47,7 @@ import GHC.Show
import GHC.List
import GHC.Exception ( ioError, catch )
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
import GHC.Conc
#endif
@@ -727,7 +727,7 @@ writeChunkNonBlocking fd is_stream ptr bytes = loop 0 bytes
loop :: Int -> Int -> IO Int
loop off bytes | bytes <= 0 = return off
loop off bytes = do
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
ssize <- c_write (fromIntegral fd) (ptr `plusPtr` off) (fromIntegral bytes)
let r = fromIntegral ssize :: Int
if (r == -1)
@@ -901,7 +901,7 @@ bufReadNonBlocking fd ref is_stream ptr so_far count =
readChunkNonBlocking :: FD -> Bool -> Ptr a -> Int -> IO Int
readChunkNonBlocking fd is_stream ptr bytes = do
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
ssize <- c_read (fromIntegral fd) (castPtr ptr) (fromIntegral bytes)
let r = fromIntegral ssize :: Int
if (r == -1)
diff --git a/libraries/base/GHC/Unicode.hs b/libraries/base/GHC/Unicode.hs
index e190cc16e1..e3ce2bdbcf 100644
--- a/libraries/base/GHC/Unicode.hs
+++ b/libraries/base/GHC/Unicode.hs
@@ -122,7 +122,7 @@ toLower :: Char -> Char
-- -----------------------------------------------------------------------------
-- Win32 implementation
-#if (defined(HAVE_WCTYPE_H) && HAVE_ISWSPACE && defined(HTYPE_WINT_T)) || mingw32_TARGET_OS
+#if (defined(HAVE_WCTYPE_H) && HAVE_ISWSPACE && defined(HTYPE_WINT_T)) || mingw32_HOST_OS
-- Use the wide-char classification functions if available. Glibc
-- seems to implement these properly, even for chars > 0xffff, as long
diff --git a/libraries/base/System/CPUTime.hsc b/libraries/base/System/CPUTime.hsc
index 6c58d8ecf2..603afce798 100644
--- a/libraries/base/System/CPUTime.hsc
+++ b/libraries/base/System/CPUTime.hsc
@@ -46,7 +46,7 @@ import Foreign.C
getCPUTime :: IO Integer
getCPUTime = do
-#if !defined(mingw32_TARGET_OS) && !defined(cygwin32_TARGET_OS)
+#if !defined(mingw32_HOST_OS) && !defined(cygwin32_HOST_OS)
-- getrusage() is right royal pain to deal with when targetting multiple
-- versions of Solaris, since some versions supply it in libc (2.3 and 2.5),
-- while 2.4 has got it in libucb (I wouldn't be too surprised if it was back
@@ -54,7 +54,7 @@ getCPUTime = do
--
-- Avoid the problem by resorting to times() instead.
--
-#if defined(HAVE_GETRUSAGE) && ! irix_TARGET_OS && ! solaris2_TARGET_OS
+#if defined(HAVE_GETRUSAGE) && ! irix_HOST_OS && ! solaris2_HOST_OS
allocaBytes (#const sizeof(struct rusage)) $ \ p_rusage -> do
getrusage (#const RUSAGE_SELF) p_rusage
diff --git a/libraries/base/System/Cmd.hs b/libraries/base/System/Cmd.hs
index 1eaaf786b8..cf1dc5ba9c 100644
--- a/libraries/base/System/Cmd.hs
+++ b/libraries/base/System/Cmd.hs
@@ -83,16 +83,16 @@ rawSystem cmd args = do
rawSystem cmd args = system (unwords (map translate (cmd:args)))
translate :: String -> String
-#if defined(mingw32_TARGET_OS)
+#if defined(mingw32_HOST_OS)
-- copied from System.Process (qv)
translate str = '"' : snd (foldr escape (True,"\"") str)
where escape '"' (b, str) = (True, '\\' : '"' : str)
escape '\\' (True, str) = (True, '\\' : '\\' : str)
escape '\\' (False, str) = (False, '\\' : str)
escape c (b, str) = (False, c : str)
-#else /* ! mingw32_TARGET_OS */
+#else /* ! mingw32_HOST_OS */
translate str = '\'' : foldr escape "'" str
where escape '\'' cs = '\'' : '\\' : '\'' : '\'' : cs
escape c cs = c : cs
-#endif /* ! mingw32_TARGET_OS */
+#endif /* ! mingw32_HOST_OS */
#endif /* ! __GLASGOW_HASKELL__ */
diff --git a/libraries/base/System/Directory.hs b/libraries/base/System/Directory.hs
index e2fd121e83..a7839ea6b8 100644
--- a/libraries/base/System/Directory.hs
+++ b/libraries/base/System/Directory.hs
@@ -526,7 +526,7 @@ canonicalizePath :: FilePath -> IO FilePath
canonicalizePath fpath =
withCString fpath $ \pInPath ->
allocaBytes long_path_size $ \pOutPath ->
-#if defined(mingw32_TARGET_OS)
+#if defined(mingw32_HOST_OS)
alloca $ \ppFilePart ->
do c_GetFullPathName pInPath (fromIntegral long_path_size) pOutPath ppFilePart
#else
@@ -534,7 +534,7 @@ canonicalizePath fpath =
#endif
peekCString pOutPath
-#if defined(mingw32_TARGET_OS)
+#if defined(mingw32_HOST_OS)
foreign import stdcall unsafe "GetFullPathName"
c_GetFullPathName :: CString
-> CInt
@@ -832,7 +832,7 @@ cannot be found.
-}
getHomeDirectory :: IO FilePath
getHomeDirectory =
-#if __GLASGOW_HASKELL__ && defined(mingw32_TARGET_OS)
+#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
allocaBytes long_path_size $ \pPath -> do
r <- c_SHGetFolderPath nullPtr csidl_PROFILE nullPtr 0 pPath
if (r < 0)
@@ -872,7 +872,7 @@ cannot be found.
-}
getAppUserDataDirectory :: String -> IO FilePath
getAppUserDataDirectory appName = do
-#if __GLASGOW_HASKELL__ && defined(mingw32_TARGET_OS)
+#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
allocaBytes long_path_size $ \pPath -> do
r <- c_SHGetFolderPath nullPtr csidl_APPDATA nullPtr 0 pPath
s <- peekCString pPath
@@ -905,7 +905,7 @@ cannot be found.
-}
getUserDocumentsDirectory :: IO FilePath
getUserDocumentsDirectory = do
-#if __GLASGOW_HASKELL__ && defined(mingw32_TARGET_OS)
+#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
allocaBytes long_path_size $ \pPath -> do
r <- c_SHGetFolderPath nullPtr csidl_PERSONAL nullPtr 0 pPath
peekCString pPath
@@ -941,7 +941,7 @@ The function doesn\'t verify whether the path exists.
-}
getTemporaryDirectory :: IO FilePath
getTemporaryDirectory = do
-#if __GLASGOW_HASKELL__ && defined(mingw32_TARGET_OS)
+#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
allocaBytes long_path_size $ \pPath -> do
r <- c_GetTempPath (fromIntegral long_path_size) pPath
peekCString pPath
@@ -949,7 +949,7 @@ getTemporaryDirectory = do
catch (getEnv "TMPDIR") (\ex -> return "/tmp")
#endif
-#if __GLASGOW_HASKELL__ && defined(mingw32_TARGET_OS)
+#if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
foreign import stdcall unsafe "SHGetFolderPath"
c_SHGetFolderPath :: Ptr ()
-> CInt
diff --git a/libraries/base/System/Directory/Internals.hs b/libraries/base/System/Directory/Internals.hs
index 7c7f8a5640..761b7714d7 100644
--- a/libraries/base/System/Directory/Internals.hs
+++ b/libraries/base/System/Directory/Internals.hs
@@ -91,7 +91,7 @@ pathParents :: FilePath -> [FilePath]
pathParents p =
root'' : map ((++) root') (dropEmptyPath $ inits path')
where
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
(root,path) = case break (== ':') p of
(path, "") -> ("",path)
(root,_:path) -> (root++":",path)
@@ -150,7 +150,7 @@ isPathSeparator ch = ch == pathSeparator || ch == '/'
-- separator is a slash (@\"\/\"@) on Unix and Macintosh, and a backslash
-- (@\"\\\"@) on the Windows operating system.
pathSeparator :: Char
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
pathSeparator = '\\'
#else
pathSeparator = '/'
@@ -161,7 +161,7 @@ pathSeparator = '/'
-- environment variables. The separator is a colon (@\":\"@) on Unix and
-- Macintosh, and a semicolon (@\";\"@) on the Windows operating system.
searchPathSeparator :: Char
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
searchPathSeparator = ';'
#else
searchPathSeparator = ':'
@@ -171,7 +171,7 @@ searchPathSeparator = ':'
-- | Extension for executable files
-- (typically @\"\"@ on Unix and @\"exe\"@ on Windows or OS\/2)
exeExtension :: String
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
exeExtension = "exe"
#else
exeExtension = ""
diff --git a/libraries/base/System/Environment.hs b/libraries/base/System/Environment.hs
index de60de890f..1235920edd 100644
--- a/libraries/base/System/Environment.hs
+++ b/libraries/base/System/Environment.hs
@@ -102,7 +102,7 @@ unpackProgName argv = do
isPathSeparator :: Char -> Bool
isPathSeparator '/' = True
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
isPathSeparator '\\' = True
#endif
isPathSeparator _ = False
diff --git a/libraries/base/System/Info.hs b/libraries/base/System/Info.hs
index 02cd45de0b..dfb30188d4 100644
--- a/libraries/base/System/Info.hs
+++ b/libraries/base/System/Info.hs
@@ -13,20 +13,21 @@
--
-----------------------------------------------------------------------------
-#ifndef __NHC__
-#include "MachDeps.h"
-#endif
-
module System.Info
(
os, -- :: String
- arch -- :: String
+ arch, -- :: String
+ compilerName, -- :: String
+ compilerVersion -- :: Version
) where
import Prelude
+import Data.Version
#ifndef __NHC__
+#include "ghcplatform.h"
+
arch :: String
arch = HOST_ARCH
@@ -37,3 +38,20 @@ os = HOST_OS
os,arch ::String
#include "OSInfo.hs"
#endif
+
+compilerName :: String
+#if defined(__NHC__)
+compilerName = "nhc98"
+#elif defined(__GLASGOW_HASKELL__)
+compilerName = "ghc"
+#elif defined(__HUGS__)
+compilerName = "hugs"
+#else
+#error Unknown compiler name
+#endif
+
+compilerVersion :: Version
+#ifdef __GLASGOW_HASKELL__
+compilerVersion = Version {versionBranch=[maj,min], versionTags=[]}
+ where (maj,min) = __GLASGOW_HASKELL__ `divMod` 100
+#endif
diff --git a/libraries/base/System/Posix/Internals.hs b/libraries/base/System/Posix/Internals.hs
index 28b85f1ee5..7e3ba5852e 100644
--- a/libraries/base/System/Posix/Internals.hs
+++ b/libraries/base/System/Posix/Internals.hs
@@ -118,7 +118,7 @@ statGetType p_stat = do
ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
"unknown file type" Nothing
-#if defined(mingw32_TARGET_OS) || defined(__MINGW32__)
+#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
closeFd :: Bool -> CInt -> IO CInt
closeFd isStream fd
| isStream = c_closesocket fd
@@ -130,7 +130,7 @@ foreign import stdcall unsafe "HsBase.h closesocket"
fdGetMode :: Int -> IO IOMode
fdGetMode fd = do
-#if defined(mingw32_TARGET_OS) || defined(__MINGW32__)
+#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
-- XXX: this code is *BROKEN*, _setmode only deals with O_TEXT/O_BINARY
flags1 <- throwErrnoIfMinus1Retry "fdGetMode"
(c__setmode (fromIntegral fd) (fromIntegral o_WRONLY))
@@ -285,7 +285,7 @@ foreign import ccall unsafe "consUtils.h get_console_echo__"
-- ---------------------------------------------------------------------------
-- Turning on non-blocking for a file descriptor
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
setNonBlockingFD fd = do
flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
@@ -384,7 +384,7 @@ foreign import ccall unsafe "HsBase.h unlink"
foreign import ccall unsafe "HsBase.h getpid"
c_getpid :: IO CPid
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
foreign import ccall unsafe "HsBase.h fcntl"
c_fcntl_read :: CInt -> CInt -> IO CInt
@@ -496,7 +496,7 @@ foreign import ccall unsafe "HsBase.h __hscore_poke_lflag" poke_c_lflag :: Ptr C
foreign import ccall unsafe "HsBase.h __hscore_ptr_c_cc" ptr_c_cc :: Ptr CTermios -> IO (Ptr Word8)
#endif
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
foreign import ccall unsafe "HsBase.h __hscore_s_issock" s_issock :: CMode -> Bool
#else
s_issock :: CMode -> Bool
diff --git a/libraries/base/System/Posix/Signals.hsc b/libraries/base/System/Posix/Signals.hsc
index 7318e5deb3..3f3db776fe 100644
--- a/libraries/base/System/Posix/Signals.hsc
+++ b/libraries/base/System/Posix/Signals.hsc
@@ -15,7 +15,7 @@
#include "ghcconfig.h"
module System.Posix.Signals (
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
-- * The Signal type
Signal,
@@ -76,7 +76,7 @@ module System.Posix.Signals (
-- * Waiting for signals
getPendingSignals,
-#ifndef cygwin32_TARGET_OS
+#ifndef cygwin32_HOST_OS
awaitSignal,
#endif
@@ -108,7 +108,7 @@ import System.IO.Unsafe
import System.Posix.Types
import System.Posix.Internals
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
-- WHOLE FILE...
-- -----------------------------------------------------------------------------
@@ -289,7 +289,7 @@ foreign import ccall unsafe "killpg"
raiseSignal :: Signal -> IO ()
raiseSignal sig = throwErrnoIfMinus1_ "raiseSignal" (c_raise sig)
-#if defined(__GLASGOW_HASKELL__) && (defined(openbsd_TARGET_OS) || defined(freebsd_TARGET_OS))
+#if defined(__GLASGOW_HASKELL__) && (defined(openbsd_HOST_OS) || defined(freebsd_HOST_OS))
foreign import ccall unsafe "genericRaise"
c_raise :: CInt -> IO CInt
#else
@@ -457,7 +457,7 @@ getPendingSignals = do
throwErrnoIfMinus1_ "getPendingSignals" (c_sigpending p)
return (SignalSet fp)
-#ifndef cygwin32_TARGET_OS
+#ifndef cygwin32_HOST_OS
awaitSignal :: Maybe SignalSet -> IO ()
awaitSignal maybe_sigset = do
fp <- case maybe_sigset of
@@ -506,5 +506,5 @@ foreign import ccall unsafe "__hsposix_SIG_SETMASK" c_SIG_SETMASK :: CInt
foreign import ccall unsafe "__hsposix_SIG_UNBLOCK" c_SIG_UNBLOCK :: CInt
#endif /* __HUGS__ */
-#endif /* mingw32_TARGET_OS */
+#endif /* mingw32_HOST_OS */
diff --git a/libraries/base/System/Process.hs b/libraries/base/System/Process.hs
index 3ae8fec0d7..a3594fbcdf 100644
--- a/libraries/base/System/Process.hs
+++ b/libraries/base/System/Process.hs
@@ -71,7 +71,7 @@ runCommand
runCommand string = do
(cmd,args) <- commandToProcess string
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
runProcess1 "runCommand" cmd args Nothing Nothing Nothing Nothing Nothing
#else
runProcess1 "runCommand" cmd [] Nothing Nothing Nothing Nothing Nothing args
@@ -97,7 +97,7 @@ runProcess
-> Maybe Handle -- ^ Handle to use for @stderr@
-> IO ProcessHandle
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
runProcess cmd args mb_cwd mb_env mb_stdin mb_stdout mb_stderr
= runProcess1 "runProcess" cmd args mb_cwd mb_env mb_stdin mb_stdout mb_stderr
@@ -183,7 +183,7 @@ runInteractiveCommand
runInteractiveCommand string = do
(cmd,args) <- commandToProcess string
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
runInteractiveProcess1 "runInteractiveCommand" cmd args Nothing Nothing
#else
runInteractiveProcess1 "runInteractiveCommand" cmd [] Nothing Nothing args
@@ -207,7 +207,7 @@ runInteractiveProcess
-> Maybe [(String,String)] -- ^ Optional environment (otherwise inherit)
-> IO (Handle,Handle,Handle,ProcessHandle)
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
runInteractiveProcess cmd args mb_cwd mb_env =
runInteractiveProcess1 "runInteractiveProcess" cmd args mb_cwd mb_env
@@ -350,7 +350,7 @@ getProcessExitCode (ProcessHandle handle) =
Windows isn't required (or desirable) here.
-}
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
commandToProcess
:: String
@@ -388,7 +388,7 @@ withFilePathException fpath act = handle mapEx act
mapEx (IOException (IOError h iot fun str _)) = ioError (IOError h iot fun str (Just fpath))
mapEx e = throwIO e
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
withCEnvironment :: [(String,String)] -> (Ptr CString -> IO a) -> IO a
withCEnvironment env act =
let env' = map (\(name, val) -> name ++ ('=':val)) env
@@ -475,7 +475,7 @@ expects (namely the application name). So it seems simpler to just
use lpCommandLine alone, which CreateProcess supports.
-}
-#if defined(mingw32_TARGET_OS)
+#if defined(mingw32_HOST_OS)
-- Translate command-line arguments for passing to CreateProcess().
translate :: String -> String
diff --git a/libraries/base/System/Process/Internals.hs b/libraries/base/System/Process/Internals.hs
index 9943bc007b..22caedbd58 100644
--- a/libraries/base/System/Process/Internals.hs
+++ b/libraries/base/System/Process/Internals.hs
@@ -16,14 +16,14 @@
-- #hide
module System.Process.Internals (
ProcessHandle(..), PHANDLE,
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
pPrPr_disableITimers, c_execvpe
#endif
) where
import Prelude -- necessary to get dependencies right
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
import System.Posix.Types ( CPid )
#else
import Data.Word ( Word32 )
@@ -46,7 +46,7 @@ import Foreign.Ptr ( Ptr )
termination: they all return a 'ProcessHandle' which may be used
to wait for the process later.
-}
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
type PHANDLE = CPid
#else
type PHANDLE = Word32
@@ -56,7 +56,7 @@ newtype ProcessHandle = ProcessHandle PHANDLE
-- ----------------------------------------------------------------------------
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
-- this function disables the itimer, which would otherwise cause confusing
-- signals to be sent to the new process.
diff --git a/libraries/base/System/Time.hsc b/libraries/base/System/Time.hsc
index d884e879ec..b4a623e605 100644
--- a/libraries/base/System/Time.hsc
+++ b/libraries/base/System/Time.hsc
@@ -353,10 +353,10 @@ gmtoff x = (#peek struct tm,tm_gmtoff) x
#else /* ! HAVE_TM_ZONE */
# if HAVE_TZNAME || defined(_WIN32)
-# if cygwin32_TARGET_OS
+# if cygwin32_HOST_OS
# define tzname _tzname
# endif
-# ifndef mingw32_TARGET_OS
+# ifndef mingw32_HOST_OS
foreign import ccall unsafe "time.h &tzname" tzname :: Ptr (Ptr CChar)
# else
foreign import ccall unsafe "__hscore_timezone" timezone :: Ptr CLong
@@ -381,7 +381,7 @@ gmtoff x = do
return (-fromIntegral (realToInteger tz))
# else /* ! HAVE_DECL_ALTZONE */
-#if !defined(mingw32_TARGET_OS)
+#if !defined(mingw32_HOST_OS)
foreign import ccall "time.h &timezone" timezone :: Ptr CLong
#endif
@@ -744,7 +744,7 @@ foreign import ccall unsafe "time.h gettimeofday"
#if HAVE_FTIME
type CTimeB = ()
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
foreign import ccall unsafe "time.h ftime" ftime :: Ptr CTimeB -> IO CInt
#else
foreign import ccall unsafe "time.h ftime" ftime :: Ptr CTimeB -> IO ()
diff --git a/libraries/base/cbits/consUtils.c b/libraries/base/cbits/consUtils.c
index 63665d0a0e..af29b599f4 100644
--- a/libraries/base/cbits/consUtils.c
+++ b/libraries/base/cbits/consUtils.c
@@ -4,14 +4,14 @@
* Win32 Console API support
*/
#include "ghcconfig.h"
-#if defined(mingw32_TARGET_OS) || defined(cygwin32_TARGET_OS) || defined(__MINGW32__) || defined(_MSC_VER)
+#if defined(mingw32_HOST_OS) || defined(cygwin32_HOST_OS) || defined(__MINGW32__) || defined(_MSC_VER)
/* to the end */
#include "consUtils.h"
#include <windows.h>
#include <io.h>
-#if defined(cygwin32_TARGET_OS)
+#if defined(cygwin32_HOST_OS)
#define _get_osfhandle get_osfhandle
#endif
@@ -64,4 +64,4 @@ get_console_echo__(int fd)
return -1;
}
-#endif /* defined(mingw32_TARGET_OS) || ... */
+#endif /* defined(mingw32_HOST_OS) || ... */
diff --git a/libraries/base/cbits/dirUtils.c b/libraries/base/cbits/dirUtils.c
index 08ea54e550..fdcdf295d3 100644
--- a/libraries/base/cbits/dirUtils.c
+++ b/libraries/base/cbits/dirUtils.c
@@ -8,13 +8,13 @@
// The following is required on Solaris to force the POSIX versions of
// the various _r functions instead of the Solaris versions.
-#ifdef solaris2_TARGET_OS
+#ifdef solaris2_HOST_OS
#define _POSIX_PTHREAD_SEMANTICS
#endif
#include "HsBase.h"
-#if defined(mingw32_TARGET_OS) || defined(__MINGW32__) || defined(_MSC_VER)
+#if defined(mingw32_HOST_OS) || defined(__MINGW32__) || defined(_MSC_VER)
#include <windows.h>
static
@@ -117,7 +117,7 @@ HsInt
__hscore_renameFile( HsAddr src,
HsAddr dest)
{
-#if defined(mingw32_TARGET_OS) || defined(__MINGW32__) || defined(_MSC_VER)
+#if defined(mingw32_HOST_OS) || defined(__MINGW32__) || defined(_MSC_VER)
static int forNT = -1;
/* ToDo: propagate error codes back */
diff --git a/libraries/base/cbits/execvpe.c b/libraries/base/cbits/execvpe.c
index 6de234ed66..2234f098dc 100644
--- a/libraries/base/cbits/execvpe.c
+++ b/libraries/base/cbits/execvpe.c
@@ -5,7 +5,7 @@
-------------------------------------------------------------------------- */
#include "HsBase.h"
-#if !defined(mingw32_TARGET_OS) /* to the end */
+#if !defined(mingw32_HOST_OS) /* to the end */
/* Evidently non-Posix. */
/* #include "PosixSource.h" */
diff --git a/libraries/base/cbits/inputReady.c b/libraries/base/cbits/inputReady.c
index a86f961d5e..2949e9494b 100644
--- a/libraries/base/cbits/inputReady.c
+++ b/libraries/base/cbits/inputReady.c
@@ -17,7 +17,7 @@ int
inputReady(int fd, int msecs, int isSock)
{
if
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
( 1 ) {
#else
( isSock ) {
@@ -45,7 +45,7 @@ inputReady(int fd, int msecs, int isSock)
/* 1 => Input ready, 0 => not ready, -1 => error */
return (ready);
}
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
else {
DWORD rc;
HANDLE hFile = (HANDLE)_get_osfhandle(fd);
diff --git a/libraries/base/cbits/lockFile.c b/libraries/base/cbits/lockFile.c
index 7756616304..e892ed4ee8 100644
--- a/libraries/base/cbits/lockFile.c
+++ b/libraries/base/cbits/lockFile.c
@@ -1,12 +1,12 @@
/*
* (c) The GRASP/AQUA Project, Glasgow University, 1994-2004
*
- * $Id: lockFile.c,v 1.4 2005/01/01 23:59:59 krasimir Exp $
+ * $Id: lockFile.c,v 1.5 2005/01/28 13:36:32 simonmar Exp $
*
* stdin/stout/stderr Runtime Support
*/
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
#include "HsBase.h"
#include "Rts.h"
diff --git a/libraries/base/cbits/runProcess.c b/libraries/base/cbits/runProcess.c
index 320f3bf87e..56d4eab90d 100644
--- a/libraries/base/cbits/runProcess.c
+++ b/libraries/base/cbits/runProcess.c
@@ -6,7 +6,7 @@
#include "HsBase.h"
-#if defined(mingw32_TARGET_OS)
+#if defined(mingw32_HOST_OS)
#include <windows.h>
#include <stdlib.h>
#endif
@@ -23,7 +23,7 @@
#include <signal.h>
#endif
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
/* ----------------------------------------------------------------------------
UNIX versions
------------------------------------------------------------------------- */
diff --git a/libraries/base/cbits/timeUtils.c b/libraries/base/cbits/timeUtils.c
index ca868e23f7..eb7df209e8 100644
--- a/libraries/base/cbits/timeUtils.c
+++ b/libraries/base/cbits/timeUtils.c
@@ -5,7 +5,7 @@
*/
#include "HsBase.h"
-#if defined(mingw32_TARGET_OS) /* to the end */
+#if defined(mingw32_HOST_OS) /* to the end */
HsAddr __hscore_timezone( void )
{ return (HsAddr)&_timezone; }
diff --git a/libraries/base/include/HsBase.h b/libraries/base/include/HsBase.h
index abc26d085f..e8b7ae3a3c 100644
--- a/libraries/base/include/HsBase.h
+++ b/libraries/base/include/HsBase.h
@@ -86,7 +86,7 @@
#if HAVE_SYS_TIMES_H
#include <sys/times.h>
#endif
-#if HAVE_WINSOCK_H && defined(mingw32_TARGET_OS)
+#if HAVE_WINSOCK_H && defined(mingw32_HOST_OS)
#include <winsock.h>
#endif
#if HAVE_LIMITS_H
@@ -96,13 +96,13 @@
#include <wctype.h>
#endif
-#if !defined(mingw32_TARGET_OS) && !defined(irix_TARGET_OS)
+#if !defined(mingw32_HOST_OS) && !defined(irix_HOST_OS)
# if HAVE_SYS_RESOURCE_H
# include <sys/resource.h>
# endif
#endif
-#ifdef hpux_TARGET_OS
+#ifdef hpux_HOST_OS
#include <sys/syscall.h>
#define getrusage(a, b) syscall(SYS_GETRUSAGE, a, b)
#define HAVE_GETRUSAGE
@@ -120,7 +120,7 @@
#include "runProcess.h"
-#if defined(mingw32_TARGET_OS)
+#if defined(mingw32_HOST_OS)
#include <io.h>
#include <fcntl.h>
#include "timeUtils.h"
@@ -141,7 +141,7 @@ void writeErrString__(HsAddr msg, HsInt len);
/* in Signals.c */
extern HsInt nocldstop;
-#if !defined(mingw32_TARGET_OS)
+#if !defined(mingw32_HOST_OS)
/* in execvpe.c */
extern int execvpe(char *name, char *const argv[], char **envp);
extern void pPrPr_disableITimers (void);
@@ -233,7 +233,7 @@ INLINE int __hscore_s_issock(m) { return S_ISSOCK(m); }
#endif
#endif
-#if !defined(mingw32_TARGET_OS) && !defined(_MSC_VER)
+#if !defined(mingw32_HOST_OS) && !defined(_MSC_VER)
INLINE int
__hscore_sigemptyset( sigset_t *set )
{ return sigemptyset(set); }
@@ -266,7 +266,7 @@ __hscore_memcpy_src_off( char *dst, char *src, int src_off, size_t sz )
INLINE HsBool
__hscore_supportsTextMode()
{
-#if defined(mingw32_TARGET_OS)
+#if defined(mingw32_HOST_OS)
return HS_BOOL_FALSE;
#else
return HS_BOOL_TRUE;
@@ -412,7 +412,7 @@ __hscore_ftruncate( int fd, off_t where )
INLINE HsInt
__hscore_setmode( HsInt fd, HsBool toBin )
{
-#if defined(mingw32_TARGET_OS) || defined(_MSC_VER)
+#if defined(mingw32_HOST_OS) || defined(_MSC_VER)
return setmode(fd,(toBin == HS_BOOL_TRUE) ? _O_BINARY : _O_TEXT);
#else
return 0;
@@ -432,7 +432,7 @@ __hscore_PrelHandle_read( HsInt fd, HsAddr ptr, HsInt off, int sz )
}
-#if defined(mingw32_TARGET_OS) || defined(_MSC_VER)
+#if defined(mingw32_HOST_OS) || defined(_MSC_VER)
INLINE HsInt
__hscore_PrelHandle_send( HsInt fd, HsAddr ptr, HsInt off, int sz )
{
@@ -446,7 +446,7 @@ __hscore_PrelHandle_recv( HsInt fd, HsAddr ptr, HsInt off, int sz )
}
#endif
-#if defined(mingw32_TARGET_OS) || defined(_MSC_VER)
+#if defined(mingw32_HOST_OS) || defined(_MSC_VER)
INLINE long *
__hscore_Time_ghcTimezone( void ) { return &_timezone; }
@@ -457,7 +457,7 @@ __hscore_Time_ghcTzname( void ) { return _tzname; }
INLINE HsInt
__hscore_mkdir( HsAddr pathName, HsInt mode )
{
-#if defined(mingw32_TARGET_OS) || defined(_MSC_VER)
+#if defined(mingw32_HOST_OS) || defined(_MSC_VER)
return mkdir(pathName);
#else
return mkdir(pathName,mode);
@@ -549,7 +549,7 @@ __hscore_ptr_c_cc( struct termios* ts )
INLINE HsInt
__hscore_sizeof_termios( void )
{
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
return sizeof(struct termios);
#else
return 0;
@@ -557,7 +557,7 @@ __hscore_sizeof_termios( void )
}
#endif
-#if !defined(mingw32_TARGET_OS) && !defined(_MSC_VER)
+#if !defined(mingw32_HOST_OS) && !defined(_MSC_VER)
INLINE HsInt
__hscore_sizeof_sigset_t( void )
{
@@ -668,7 +668,7 @@ extern void __hscore_set_saved_termios(int fd, void* ts);
INLINE int __hscore_hs_fileno (FILE *f) { return fileno (f); }
-#if !defined(mingw32_TARGET_OS) && !defined(_MSC_VER)
+#if !defined(mingw32_HOST_OS) && !defined(_MSC_VER)
INLINE int __hsposix_SIGABRT() { return SIGABRT; }
INLINE int __hsposix_SIGALRM() { return SIGALRM; }
INLINE int __hsposix_SIGBUS() { return SIGBUS; }
@@ -704,10 +704,10 @@ INLINE int __hsposix_SIG_BLOCK() { return SIG_BLOCK; }
INLINE int __hsposix_SIG_UNBLOCK() { return SIG_UNBLOCK; }
INLINE int __hsposix_SIG_SETMASK() { return SIG_SETMASK; }
-#endif /* mingw32_TARGET_OS */
+#endif /* mingw32_HOST_OS */
INLINE int __hscore_open(char *file, int how, mode_t mode) {
-#ifdef mingw32_TARGET_OS
+#ifdef mingw32_HOST_OS
if ((how & O_WRONLY) || (how & O_RDWR) || (how & O_APPEND))
return _sopen(file,how,_SH_DENYRW,mode);
else
@@ -735,7 +735,7 @@ INLINE int __hscore_fstat(int fd, struct stat *buf) {
// select-related stuff
-#if !defined(mingw32_TARGET_OS)
+#if !defined(mingw32_HOST_OS)
INLINE void hsFD_CLR(int fd, fd_set *fds) { FD_CLR(fd, fds); }
INLINE int hsFD_ISSET(int fd, fd_set *fds) { return FD_ISSET(fd, fds); }
INLINE void hsFD_SET(int fd, fd_set *fds) { FD_SET(fd, fds); }
@@ -745,7 +745,7 @@ extern void hsFD_ZERO(fd_set *fds);
// gettimeofday()-related
-#if !defined(mingw32_TARGET_OS)
+#if !defined(mingw32_HOST_OS)
#define TICK_FREQ 50
INLINE HsInt sizeofTimeVal(void) { return sizeof(struct timeval); }
@@ -763,11 +763,11 @@ INLINE void setTimevalTicks(struct timeval *p, HsInt ticks)
p->tv_sec = ticks / TICK_FREQ;
p->tv_usec = (ticks % TICK_FREQ) * (1000000 / TICK_FREQ);
}
-#endif // !defined(mingw32_TARGET_OS)
+#endif // !defined(mingw32_HOST_OS)
// Directory-related
-#if defined(mingw32_TARGET_OS)
+#if defined(mingw32_HOST_OS)
/* Make sure we've got the reqd CSIDL_ constants in scope;
* w32api header files are lagging a bit in defining the full set.
diff --git a/libraries/base/include/lockFile.h b/libraries/base/include/lockFile.h
index bcaa7fda17..1140787edd 100644
--- a/libraries/base/include/lockFile.h
+++ b/libraries/base/include/lockFile.h
@@ -1,12 +1,12 @@
/*
* (c) The University of Glasgow 2001
*
- * $Id: lockFile.h,v 1.2 2005/01/02 00:00:00 krasimir Exp $
+ * $Id: lockFile.h,v 1.3 2005/01/28 13:36:34 simonmar Exp $
*
* lockFile header
*/
-#ifndef mingw32_TARGET_OS
+#ifndef mingw32_HOST_OS
int lockFile(int fd, int for_writing, int exclusive);
int unlockFile(int fd);
diff --git a/libraries/base/include/runProcess.h b/libraries/base/include/runProcess.h
index fbbd4a5bdc..cda5c4656b 100644
--- a/libraries/base/include/runProcess.h
+++ b/libraries/base/include/runProcess.h
@@ -4,14 +4,14 @@
Interface for code in runProcess.c (providing support for System.Process)
------------------------------------------------------------------------- */
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
typedef pid_t ProcHandle;
#else
// Should really be intptr_t, but we don't have that type on the Haskell side
typedef long ProcHandle;
#endif
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
extern ProcHandle runProcess( char *const args[],
char *workingDirectory, char **environment,
diff --git a/libraries/base/package.conf.in b/libraries/base/package.conf.in
index 8d75ce2be7..159612748d 100644
--- a/libraries/base/package.conf.in
+++ b/libraries/base/package.conf.in
@@ -168,7 +168,7 @@ library-dirs: LIB_DIR
, LIB_DIR"/cbits"
#endif
-#if !defined(mingw32_TARGET_OS) && !defined(cygwin32_TARGET_OS)
+#if !defined(mingw32_HOST_OS) && !defined(cygwin32_HOST_OS)
hs-libraries: "HSbase"
#else
/*
@@ -181,7 +181,7 @@ hs-libraries: "HSbase1", "HSbase2", "HSbase3"
#endif
extra-libs: "HSbase_cbits"
-#if defined(mingw32_TARGET_OS) || defined(__MINGW32__) || defined(_MSC_VER)
+#if defined(mingw32_HOST_OS) || defined(__MINGW32__) || defined(_MSC_VER)
, "wsock32", "msvcrt", "kernel32", "user32", "shell32"
#endif