summaryrefslogtreecommitdiff
path: root/libraries/base/System
diff options
context:
space:
mode:
authorIan Lynagh <ian@well-typed.com>2013-02-15 20:51:56 +0000
committerIan Lynagh <ian@well-typed.com>2013-02-15 20:51:56 +0000
commit25d1eafeb41f046630f978da3655ae578c9c83b1 (patch)
tree6cb8dc7b9d0b1dfddbdec07b0f3e652b41947aa8 /libraries/base/System
parentab1d58b71736b629d28e3ce48310414880dabca3 (diff)
downloadhaskell-25d1eafeb41f046630f978da3655ae578c9c83b1.tar.gz
Remove nhc98-specific files and content
Diffstat (limited to 'libraries/base/System')
-rw-r--r--libraries/base/System/CPUTime.hsc6
-rw-r--r--libraries/base/System/Environment.hs10
-rw-r--r--libraries/base/System/Exit.hs9
-rw-r--r--libraries/base/System/IO.hs77
-rw-r--r--libraries/base/System/IO/Error.hs100
-rw-r--r--libraries/base/System/IO/Unsafe.hs5
-rw-r--r--libraries/base/System/Info.hs7
-rw-r--r--libraries/base/System/Mem.hs4
-rw-r--r--libraries/base/System/Posix/Internals.hs23
-rw-r--r--libraries/base/System/Posix/Types.hs26
10 files changed, 9 insertions, 258 deletions
diff --git a/libraries/base/System/CPUTime.hsc b/libraries/base/System/CPUTime.hsc
index b74cc25884..ec0d792eda 100644
--- a/libraries/base/System/CPUTime.hsc
+++ b/libraries/base/System/CPUTime.hsc
@@ -32,10 +32,6 @@ import Data.Ratio
import Hugs.Time ( getCPUTime, clockTicks )
#endif
-#ifdef __NHC__
-import CPUTime ( getCPUTime, cpuTimePrecision )
-#endif
-
#ifdef __GLASGOW_HASKELL__
import Foreign.Safe
import Foreign.C
@@ -166,10 +162,8 @@ foreign import WINDOWS_CCONV unsafe "GetProcessTimes" getProcessTimes :: Ptr HAN
-- in CPU time that the implementation can record, and is given as an
-- integral number of picoseconds.
-#ifndef __NHC__
cpuTimePrecision :: Integer
cpuTimePrecision = round ((1000000000000::Integer) % fromIntegral (clockTicks))
-#endif
#ifdef __GLASGOW_HASKELL__
foreign import ccall unsafe clk_tck :: CLong
diff --git a/libraries/base/System/Environment.hs b/libraries/base/System/Environment.hs
index 184c910330..c66764d40b 100644
--- a/libraries/base/System/Environment.hs
+++ b/libraries/base/System/Environment.hs
@@ -22,10 +22,8 @@ module System.Environment
getExecutablePath,
getEnv,
lookupEnv,
-#ifndef __NHC__
withArgs,
withProgName,
-#endif
#ifdef __GLASGOW_HASKELL__
getEnvironment,
#endif
@@ -54,14 +52,6 @@ import Control.Monad
import Hugs.System
#endif
-#ifdef __NHC__
-import System
- ( getArgs
- , getProgName
- , getEnv
- )
-#endif
-
import System.Environment.ExecutablePath
#ifdef mingw32_HOST_OS
diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs
index 441b8c5cf5..1b5b80815e 100644
--- a/libraries/base/System/Exit.hs
+++ b/libraries/base/System/Exit.hs
@@ -35,13 +35,6 @@ import Hugs.Prelude (ExitCode(..))
import Control.Exception.Base
#endif
-#ifdef __NHC__
-import System
- ( ExitCode(..)
- , exitWith
- )
-#endif
-
-- ---------------------------------------------------------------------------
-- exitWith
@@ -71,7 +64,6 @@ import System
-- thread, 'exitWith' will throw an 'ExitException' as normal, but the
-- exception will not cause the process itself to exit.
--
-#ifndef __NHC__
exitWith :: ExitCode -> IO a
exitWith ExitSuccess = throwIO ExitSuccess
exitWith code@(ExitFailure n)
@@ -79,7 +71,6 @@ exitWith code@(ExitFailure n)
#ifdef __GLASGOW_HASKELL__
| otherwise = ioError (IOError Nothing InvalidArgument "exitWith" "ExitFailure 0" Nothing Nothing)
#endif
-#endif /* ! __NHC__ */
-- | The computation 'exitFailure' is equivalent to
-- 'exitWith' @(@'ExitFailure' /exitfail/@)@,
diff --git a/libraries/base/System/IO.hs b/libraries/base/System/IO.hs
index 3ff8396bb2..616884a9e6 100644
--- a/libraries/base/System/IO.hs
+++ b/libraries/base/System/IO.hs
@@ -97,9 +97,7 @@ module System.IO (
hSeek,
SeekMode(AbsoluteSeek,RelativeSeek,SeekFromEnd),
-#if !defined(__NHC__)
hTell,
-#endif
-- ** Handle properties
@@ -109,12 +107,10 @@ module System.IO (
-- ** Terminal operations (not portable: GHC\/Hugs only)
-#if !defined(__NHC__)
hIsTerminalDevice,
hSetEcho,
hGetEcho,
-#endif
-- ** Showing handle state (not portable: GHC only)
@@ -162,7 +158,7 @@ module System.IO (
hSetBinaryMode,
hPutBuf,
hGetBuf,
-#if !defined(__NHC__) && !defined(__HUGS__)
+#if !defined(__HUGS__)
hGetBufSome,
hPutBufNonBlocking,
hGetBufNonBlocking,
@@ -175,7 +171,7 @@ module System.IO (
openTempFileWithDefaultPermissions,
openBinaryTempFileWithDefaultPermissions,
-#if !defined(__NHC__) && !defined(__HUGS__)
+#if !defined(__HUGS__)
-- * Unicode encoding\/decoding
-- | A text-mode 'Handle' has an associated 'TextEncoding', which
@@ -207,7 +203,7 @@ module System.IO (
mkTextEncoding,
#endif
-#if !defined(__NHC__) && !defined(__HUGS__)
+#if !defined(__HUGS__)
-- * Newline conversion
-- | In Haskell, a newline is always represented by the character
@@ -236,7 +232,6 @@ module System.IO (
import Control.Exception.Base
-#ifndef __NHC__
import Data.Bits
import Data.List
import Data.Maybe
@@ -247,7 +242,6 @@ import Foreign.C.String
import Foreign.C.Types
import System.Posix.Internals
import System.Posix.Types
-#endif
#ifdef __GLASGOW_HASKELL__
import GHC.Base
@@ -272,47 +266,6 @@ import Hugs.IORef
import System.IO.Unsafe ( unsafeInterleaveIO )
#endif
-#ifdef __NHC__
-import IO
- ( Handle ()
- , HandlePosn ()
- , IOMode (ReadMode,WriteMode,AppendMode,ReadWriteMode)
- , BufferMode (NoBuffering,LineBuffering,BlockBuffering)
- , SeekMode (AbsoluteSeek,RelativeSeek,SeekFromEnd)
- , stdin, stdout, stderr
- , openFile -- :: FilePath -> IOMode -> IO Handle
- , hClose -- :: Handle -> IO ()
- , hFileSize -- :: Handle -> IO Integer
- , hIsEOF -- :: Handle -> IO Bool
- , isEOF -- :: IO Bool
- , hSetBuffering -- :: Handle -> BufferMode -> IO ()
- , hGetBuffering -- :: Handle -> IO BufferMode
- , hFlush -- :: Handle -> IO ()
- , hGetPosn -- :: Handle -> IO HandlePosn
- , hSetPosn -- :: HandlePosn -> IO ()
- , hSeek -- :: Handle -> SeekMode -> Integer -> IO ()
- , hWaitForInput -- :: Handle -> Int -> IO Bool
- , hGetChar -- :: Handle -> IO Char
- , hGetLine -- :: Handle -> IO [Char]
- , hLookAhead -- :: Handle -> IO Char
- , hGetContents -- :: Handle -> IO [Char]
- , hPutChar -- :: Handle -> Char -> IO ()
- , hPutStr -- :: Handle -> [Char] -> IO ()
- , hPutStrLn -- :: Handle -> [Char] -> IO ()
- , hPrint -- :: Handle -> [Char] -> IO ()
- , hReady -- :: Handle -> [Char] -> IO ()
- , hIsOpen, hIsClosed -- :: Handle -> IO Bool
- , hIsReadable, hIsWritable -- :: Handle -> IO Bool
- , hIsSeekable -- :: Handle -> IO Bool
- , bracket
-
- , IO ()
- , FilePath -- :: String
- )
-import NHC.IOExtras (fixIO, hPutBuf, hGetBuf)
-import NHC.FFI (Ptr)
-#endif
-
-- -----------------------------------------------------------------------------
-- Standard IO
@@ -426,7 +379,6 @@ localeEncoding :: TextEncoding
localeEncoding = initLocaleEncoding
#endif /* __GLASGOW_HASKELL__ */
-#ifndef __NHC__
-- | Computation 'hReady' @hdl@ indicates whether at least one item is
-- available for input from handle @hdl@.
--
@@ -449,7 +401,6 @@ hReady h = hWaitForInput h 0
hPrint :: Show a => Handle -> a -> IO ()
hPrint hdl = hPutStrLn hdl . show
-#endif /* !__NHC__ */
-- | @'withFile' name mode act@ opens a file using 'openFile' and passes
-- the resulting handle to the computation @act@. The handle will be
@@ -495,14 +446,6 @@ fixIO k = do
--
#endif
-#if defined(__NHC__)
--- Assume a unix platform, where text and binary I/O are identical.
-openBinaryFile = openFile
-hSetBinaryMode _ _ = return ()
-
-type CMode = Int
-#endif
-
-- | The function creates a temporary file in ReadWrite mode.
-- The created file isn\'t deleted automatically, so you need to delete it manually.
--
@@ -566,13 +509,7 @@ openTempFile' loc tmp_dir template binary mode = do
-- beginning with '.' as the second component.
_ -> error "bug in System.IO.openTempFile"
-#ifndef __NHC__
-#endif
-
-#if defined(__NHC__)
- findTempName x = do h <- openFile filepath ReadWriteMode
- return (filepath, h)
-#elif defined(__GLASGOW_HASKELL__)
+#if defined(__GLASGOW_HASKELL__)
findTempName x = do
r <- openNewFile filepath binary mode
case r of
@@ -661,17 +598,11 @@ pathSeparator = '\\'
pathSeparator = '/'
#endif
-#ifndef __NHC__
-- XXX Copied from GHC.Handle
std_flags, output_flags, rw_flags :: CInt
std_flags = o_NONBLOCK .|. o_NOCTTY
output_flags = std_flags .|. o_CREAT
rw_flags = output_flags .|. o_RDWR
-#endif
-
-#ifdef __NHC__
-foreign import ccall "getpid" c_getpid :: IO Int
-#endif
-- $locking
-- Implementations should enforce as far as possible, at least locally to the
diff --git a/libraries/base/System/IO/Error.hs b/libraries/base/System/IO/Error.hs
index 8d939c08b3..a90e031983 100644
--- a/libraries/base/System/IO/Error.hs
+++ b/libraries/base/System/IO/Error.hs
@@ -102,31 +102,6 @@ import Text.Show
import Hugs.Prelude(Handle, IOException(..), IOErrorType(..), IO)
#endif
-#ifdef __NHC__
-import IO
- ( IOError ()
- , Handle ()
- , try
- , ioError
- , userError
- , isAlreadyExistsError -- :: IOError -> Bool
- , isDoesNotExistError
- , isAlreadyInUseError
- , isFullError
- , isEOFError
- , isIllegalOperation
- , isPermissionError
- , isUserError
- , ioeGetErrorString -- :: IOError -> String
- , ioeGetHandle -- :: IOError -> Maybe Handle
- , ioeGetFileName -- :: IOError -> Maybe FilePath
- )
-import qualified NHC.Internal as NHC (IOError(..))
-import qualified NHC.DErrNo as NHC (ErrNo(..))
-import Data.Maybe (fromJust)
-import Control.Monad (MonadPlus(mplus))
-#endif
-
-- | The construct 'tryIOError' @comp@ exposes IO errors which occur within a
-- computation, and which are not fully handled.
--
@@ -157,23 +132,7 @@ mkIOError t location maybe_hdl maybe_filename =
ioe_filename = maybe_filename
}
#endif /* __GLASGOW_HASKELL__ || __HUGS__ */
-#ifdef __NHC__
-mkIOError EOF location maybe_hdl maybe_filename =
- NHC.EOFError location (fromJust maybe_hdl)
-mkIOError UserError location maybe_hdl maybe_filename =
- NHC.UserError location ""
-mkIOError t location maybe_hdl maybe_filename =
- NHC.IOError location maybe_filename maybe_hdl (ioeTypeToErrNo t)
- where
- ioeTypeToErrNo AlreadyExists = NHC.EEXIST
- ioeTypeToErrNo NoSuchThing = NHC.ENOENT
- ioeTypeToErrNo ResourceBusy = NHC.EBUSY
- ioeTypeToErrNo ResourceExhausted = NHC.ENOSPC
- ioeTypeToErrNo IllegalOperation = NHC.EPERM
- ioeTypeToErrNo PermissionDenied = NHC.EACCES
-#endif /* __NHC__ */
-
-#ifndef __NHC__
+
-- -----------------------------------------------------------------------------
-- IOErrorType
@@ -222,17 +181,10 @@ isPermissionError = isPermissionErrorType . ioeGetErrorType
-- | A programmer-defined error value constructed using 'userError'.
isUserError :: IOError -> Bool
isUserError = isUserErrorType . ioeGetErrorType
-#endif /* __NHC__ */
-- -----------------------------------------------------------------------------
-- IOErrorTypes
-#ifdef __NHC__
-data IOErrorType = AlreadyExists | NoSuchThing | ResourceBusy
- | ResourceExhausted | EOF | IllegalOperation
- | PermissionDenied | UserError
-#endif
-
-- | I\/O error where the operation failed because one of its arguments
-- already exists.
alreadyExistsErrorType :: IOErrorType
@@ -352,45 +304,6 @@ ioeSetLocation ioe str = ioe{ ioe_location = str }
ioeSetHandle ioe hdl = ioe{ ioe_handle = Just hdl }
ioeSetFileName ioe filename = ioe{ ioe_filename = Just filename }
-#elif defined(__NHC__)
-ioeGetErrorType :: IOError -> IOErrorType
-ioeGetLocation :: IOError -> String
-
-ioeGetErrorType e | isAlreadyExistsError e = AlreadyExists
- | isDoesNotExistError e = NoSuchThing
- | isAlreadyInUseError e = ResourceBusy
- | isFullError e = ResourceExhausted
- | isEOFError e = EOF
- | isIllegalOperation e = IllegalOperation
- | isPermissionError e = PermissionDenied
- | isUserError e = UserError
-
-ioeGetLocation (NHC.IOError _ _ _ _) = "unknown location"
-ioeGetLocation (NHC.EOFError _ _ ) = "unknown location"
-ioeGetLocation (NHC.PatternError loc) = loc
-ioeGetLocation (NHC.UserError loc _) = loc
-
-ioeSetErrorType :: IOError -> IOErrorType -> IOError
-ioeSetErrorString :: IOError -> String -> IOError
-ioeSetLocation :: IOError -> String -> IOError
-ioeSetHandle :: IOError -> Handle -> IOError
-ioeSetFileName :: IOError -> FilePath -> IOError
-
-ioeSetErrorType e _ = e
-ioeSetErrorString (NHC.IOError _ f h e) s = NHC.IOError s f h e
-ioeSetErrorString (NHC.EOFError _ f) s = NHC.EOFError s f
-ioeSetErrorString e@(NHC.PatternError _) _ = e
-ioeSetErrorString (NHC.UserError l _) s = NHC.UserError l s
-ioeSetLocation e@(NHC.IOError _ _ _ _) _ = e
-ioeSetLocation e@(NHC.EOFError _ _) _ = e
-ioeSetLocation (NHC.PatternError _) l = NHC.PatternError l
-ioeSetLocation (NHC.UserError _ m) l = NHC.UserError l m
-ioeSetHandle (NHC.IOError o f _ e) h = NHC.IOError o f (Just h) e
-ioeSetHandle (NHC.EOFError o _) h = NHC.EOFError o h
-ioeSetHandle e@(NHC.PatternError _) _ = e
-ioeSetHandle e@(NHC.UserError _ _) _ = e
-ioeSetFileName (NHC.IOError o _ h e) f = NHC.IOError o (Just f) h e
-ioeSetFileName e _ = e
#endif
-- | Catch any 'IOError' that occurs in the computation and throw a
@@ -420,17 +333,6 @@ annotateIOError ioe loc hdl path =
xs `mplus` _ = xs
#endif /* __GLASGOW_HASKELL__ || __HUGS__ */
-#if defined(__NHC__)
-annotateIOError (NHC.IOError msg file hdl code) msg' hdl' file' =
- NHC.IOError (msg++'\n':msg') (file`mplus`file') (hdl`mplus`hdl') code
-annotateIOError (NHC.EOFError msg hdl) msg' _ _ =
- NHC.EOFError (msg++'\n':msg') hdl
-annotateIOError (NHC.UserError loc msg) msg' _ _ =
- NHC.UserError loc (msg++'\n':msg')
-annotateIOError (NHC.PatternError loc) msg' _ _ =
- NHC.PatternError (loc++'\n':msg')
-#endif
-
#ifndef __HUGS__
-- | The 'catchIOError' function establishes a handler that receives any
-- 'IOError' raised in the action protected by 'catchIOError'.
diff --git a/libraries/base/System/IO/Unsafe.hs b/libraries/base/System/IO/Unsafe.hs
index 6ac4af61de..907e9124b5 100644
--- a/libraries/base/System/IO/Unsafe.hs
+++ b/libraries/base/System/IO/Unsafe.hs
@@ -36,11 +36,6 @@ import Hugs.IOExts (unsafePerformIO, unsafeInterleaveIO)
unsafeDupablePerformIO = unsafePerformIO
#endif
-#ifdef __NHC__
-import NHC.Internal (unsafePerformIO, unsafeInterleaveIO)
-unsafeDupablePerformIO = unsafePerformIO
-#endif
-
-- | A slightly faster version of `System.IO.fixIO` that may not be
-- safe to use with multiple threads. The unsafety arises when used
-- like this:
diff --git a/libraries/base/System/Info.hs b/libraries/base/System/Info.hs
index c475be3eb7..8655f89109 100644
--- a/libraries/base/System/Info.hs
+++ b/libraries/base/System/Info.hs
@@ -45,12 +45,7 @@ compilerName :: String
compilerVersionRaw :: Int
-#if defined(__NHC__)
-#include "OSInfo.hs"
-compilerName = "nhc98"
-compilerVersionRaw = __NHC__
-
-#elif defined(__GLASGOW_HASKELL__)
+#if defined(__GLASGOW_HASKELL__)
#include "ghcplatform.h"
os = HOST_OS
arch = HOST_ARCH
diff --git a/libraries/base/System/Mem.hs b/libraries/base/System/Mem.hs
index 665f69e0dc..c6c24b25d6 100644
--- a/libraries/base/System/Mem.hs
+++ b/libraries/base/System/Mem.hs
@@ -33,7 +33,3 @@ import Hugs.IOExts
foreign import ccall {-safe-} "performMajorGC" performGC :: IO ()
#endif
-#ifdef __NHC__
-import NHC.IOExtras (performGC)
-#endif
-
diff --git a/libraries/base/System/Posix/Internals.hs b/libraries/base/System/Posix/Internals.hs
index e006a6273f..106616822e 100644
--- a/libraries/base/System/Posix/Internals.hs
+++ b/libraries/base/System/Posix/Internals.hs
@@ -24,11 +24,7 @@
-- #hide
module System.Posix.Internals where
-#ifdef __NHC__
-#define HTYPE_TCFLAG_T
-#else
-# include "HsBaseConfig.h"
-#endif
+#include "HsBaseConfig.h"
#if ! (defined(mingw32_HOST_OS) || defined(__MINGW32__))
import Control.Monad
@@ -60,11 +56,6 @@ import qualified GHC.Foreign as GHC
#elif __HUGS__
import Hugs.Prelude (IOException(..), IOErrorType(..))
import Hugs.IO (IOMode(..))
-#elif __NHC__
-import GHC.IO.Device -- yes, I know, but its portable, really!
-import System.IO
-import Control.Exception
-import DIOError
#endif
#ifdef __HUGS__
@@ -152,16 +143,12 @@ statGetType p_stat = do
| otherwise -> ioError ioe_unknownfiletype
ioe_unknownfiletype :: IOException
-#ifndef __NHC__
ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
"unknown file type"
-# if __GLASGOW_HASKELL__
- Nothing
-# endif
+#if __GLASGOW_HASKELL__
Nothing
-#else
-ioe_unknownfiletype = UserError "fdType" "unknown file type"
#endif
+ Nothing
fdGetMode :: FD -> IO IOMode
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
@@ -319,11 +306,7 @@ setCooked fd cooked = do
ioe_unk_error :: String -> String -> IOException
ioe_unk_error loc msg
-#ifndef __NHC__
= ioeSetErrorString (mkIOError OtherError loc Nothing Nothing) msg
-#else
- = UserError loc msg
-#endif
-- Note: echoing goes hand in hand with enabling 'line input' / raw-ness
-- for Win32 consoles, hence setEcho ends up being the inverse of setCooked.
diff --git a/libraries/base/System/Posix/Types.hs b/libraries/base/System/Posix/Types.hs
index 32206aa6d6..82760c51fd 100644
--- a/libraries/base/System/Posix/Types.hs
+++ b/libraries/base/System/Posix/Types.hs
@@ -22,26 +22,7 @@
-- @\<sys\/types.h>@ C header on a POSIX system.
--
-----------------------------------------------------------------------------
-#ifdef __NHC__
-#define HTYPE_DEV_T
-#define HTYPE_INO_T
-#define HTYPE_MODE_T
-#define HTYPE_OFF_T
-#define HTYPE_PID_T
-#define HTYPE_SSIZE_T
-#define HTYPE_GID_T
-#define HTYPE_NLINK_T
-#define HTYPE_UID_T
-#define HTYPE_CC_T
-#define HTYPE_SPEED_T
-#define HTYPE_TCFLAG_T
-#define HTYPE_RLIM_T
-#define HTYPE_NLINK_T
-#define HTYPE_UID_T
-#define HTYPE_GID_T
-#else
#include "HsBaseConfig.h"
-#endif
module System.Posix.Types (
@@ -111,11 +92,6 @@ module System.Posix.Types (
Limit
) where
-#ifdef __NHC__
-import NHC.PosixTypes
-import Foreign.C
-#else
-
import Foreign
import Foreign.C
import Data.Typeable
@@ -195,8 +171,6 @@ type UserID = CUid
type GroupID = CGid
#endif
-#endif /* !__NHC__ */
-
type ByteCount = CSize
type ClockTick = CClock
type EpochTime = CTime