diff options
author | Ian Lynagh <ian@well-typed.com> | 2013-02-15 20:51:56 +0000 |
---|---|---|
committer | Ian Lynagh <ian@well-typed.com> | 2013-02-15 20:51:56 +0000 |
commit | 25d1eafeb41f046630f978da3655ae578c9c83b1 (patch) | |
tree | 6cb8dc7b9d0b1dfddbdec07b0f3e652b41947aa8 | |
parent | ab1d58b71736b629d28e3ce48310414880dabca3 (diff) | |
download | haskell-25d1eafeb41f046630f978da3655ae578c9c83b1.tar.gz |
Remove nhc98-specific files and content
54 files changed, 22 insertions, 1031 deletions
diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs index 04e8e9d1e0..74d33f0d57 100644 --- a/libraries/base/Control/Applicative.hs +++ b/libraries/base/Control/Applicative.hs @@ -50,21 +50,12 @@ import Prelude hiding (id,(.)) import Control.Category import Control.Arrow import Control.Monad (liftM, ap, MonadPlus(..)) -#ifndef __NHC__ import Control.Monad.ST.Safe (ST) import qualified Control.Monad.ST.Lazy.Safe as Lazy (ST) -#endif import Data.Functor ((<$>), (<$)) import Data.Monoid (Monoid(..)) -import Text.ParserCombinators.ReadP -#ifndef __NHC__ - (ReadP) -#else - (ReadPN) -#define ReadP (ReadPN b) -#endif - +import Text.ParserCombinators.ReadP (ReadP) import Text.ParserCombinators.ReadPrec (ReadPrec) #ifdef __GLASGOW_HASKELL__ @@ -181,7 +172,6 @@ instance Applicative IO where pure = return (<*>) = ap -#ifndef __NHC__ instance Applicative (ST s) where pure = return (<*>) = ap @@ -189,7 +179,6 @@ instance Applicative (ST s) where instance Applicative (Lazy.ST s) where pure = return (<*>) = ap -#endif #ifdef __GLASGOW_HASKELL__ instance Applicative STM where diff --git a/libraries/base/Control/Exception.hs b/libraries/base/Control/Exception.hs index e3a3a24b8e..35f1e8ac21 100644 --- a/libraries/base/Control/Exception.hs +++ b/libraries/base/Control/Exception.hs @@ -52,9 +52,6 @@ module Control.Exception ( NonTermination(..), NestedAtomically(..), #endif -#ifdef __NHC__ - System.ExitCode(), -- instance Exception -#endif BlockedIndefinitelyOnMVar(..), BlockedIndefinitelyOnSTM(..), @@ -111,14 +108,12 @@ module Control.Exception ( -- asynchronous exceptions during a critical region. mask, -#ifndef __NHC__ mask_, uninterruptibleMask, uninterruptibleMask_, MaskingState(..), getMaskingState, allowInterrupt, -#endif -- ** (deprecated) Asynchronous exception control @@ -159,10 +154,6 @@ import Data.Maybe import Prelude hiding (catch) #endif -#ifdef __NHC__ -import System (ExitCode()) -#endif - -- | You need this when using 'catches'. data Handler a = forall e . Exception e => Handler (e -> IO a) diff --git a/libraries/base/Control/Exception/Base.hs b/libraries/base/Control/Exception/Base.hs index 8d2d5d86bd..0f16bddcf9 100644 --- a/libraries/base/Control/Exception/Base.hs +++ b/libraries/base/Control/Exception/Base.hs @@ -84,13 +84,11 @@ module Control.Exception.Base ( -- ** Asynchronous exception control mask, -#ifndef __NHC__ mask_, uninterruptibleMask, uninterruptibleMask_, MaskingState(..), getMaskingState, -#endif -- ** (deprecated) Asynchronous exception control @@ -143,99 +141,6 @@ import Data.Dynamic import Data.Either import Data.Maybe -#ifdef __NHC__ -import qualified IO as H'98 (catch) -import IO (bracket,ioError) -import DIOError -- defn of IOError type -import System (ExitCode()) -import System.IO.Unsafe (unsafePerformIO) -import Unsafe.Coerce (unsafeCoerce) - --- minimum needed for nhc98 to pretend it has Exceptions - -{- -data Exception = IOException IOException - | ArithException ArithException - | ArrayException ArrayException - | AsyncException AsyncException - | ExitException ExitCode - deriving Show --} -class ({-Typeable e,-} Show e) => Exception e where - toException :: e -> SomeException - fromException :: SomeException -> Maybe e - -data SomeException = forall e . Exception e => SomeException e - -INSTANCE_TYPEABLE0(SomeException,someExceptionTc,"SomeException") - -instance Show SomeException where - showsPrec p (SomeException e) = showsPrec p e -instance Exception SomeException where - toException se = se - fromException = Just - -type IOException = IOError -instance Exception IOError where - toException = SomeException - fromException (SomeException e) = Just (unsafeCoerce e) - -instance Exception ExitCode where - toException = SomeException - fromException (SomeException e) = Just (unsafeCoerce e) - -data ArithException -data ArrayException -data AsyncException -data AssertionFailed -data PatternMatchFail -data NoMethodError -data Deadlock -data BlockedIndefinitelyOnMVar -data BlockedIndefinitelyOnSTM -data ErrorCall -data RecConError -data RecSelError -data RecUpdError -instance Show ArithException -instance Show ArrayException -instance Show AsyncException -instance Show AssertionFailed -instance Show PatternMatchFail -instance Show NoMethodError -instance Show Deadlock -instance Show BlockedIndefinitelyOnMVar -instance Show BlockedIndefinitelyOnSTM -instance Show ErrorCall -instance Show RecConError -instance Show RecSelError -instance Show RecUpdError - -catch :: Exception e - => IO a -- ^ The computation to run - -> (e -> IO a) -- ^ Handler to invoke if an exception is raised - -> IO a -catch io h = H'98.catch io (h . fromJust . fromException . toException) - -throwIO :: Exception e => e -> IO a -throwIO = ioError . fromJust . fromException . toException - -throw :: Exception e => e -> a -throw = unsafePerformIO . throwIO - -evaluate :: a -> IO a -evaluate x = x `seq` return x - -assert :: Bool -> a -> a -assert True x = x -assert False _ = throw (toException (UserError "" "Assertion failed")) - -mask :: ((IO a-> IO a) -> IO a) -> IO a -mask action = action restore - where restore act = act - -#endif - #ifdef __HUGS__ class (Typeable e, Show e) => Exception e where toException :: e -> SomeException @@ -380,7 +285,6 @@ blocked = return False -- might get a the opposite behaviour. This is ok, because 'catch' is an -- 'IO' computation. -- -#ifndef __NHC__ catch :: Exception e => IO a -- ^ The computation to run -> (e -> IO a) -- ^ Handler to invoke if an exception is raised @@ -393,7 +297,6 @@ catch m h = Hugs.Exception.catchException m h' Just e' -> h e' Nothing -> throwIO e #endif -#endif -- | The function 'catchJust' is like 'catch', but it takes an extra -- argument which is an /exception predicate/, a function which @@ -497,7 +400,6 @@ onException io what = io `catch` \e -> do _ <- what -- -- > withFile name mode = bracket (openFile name mode) hClose -- -#ifndef __NHC__ bracket :: IO a -- ^ computation to run first (\"acquire resource\") -> (a -> IO b) -- ^ computation to run last (\"release resource\") @@ -509,7 +411,6 @@ bracket before after thing = r <- restore (thing a) `onException` after a _ <- after a return r -#endif -- | A specialised variant of 'bracket' with just a computation to run -- afterward. @@ -541,7 +442,7 @@ bracketOnError before after thing = a <- before restore (thing a) `onException` after a -#if !(__GLASGOW_HASKELL__ || __NHC__) +#if !__GLASGOW_HASKELL__ assert :: Bool -> a -> a assert True x = x assert False _ = throw (AssertionFailed "") diff --git a/libraries/base/Control/Monad/Instances.hs b/libraries/base/Control/Monad/Instances.hs index 663536a9d9..7c31b3457c 100644 --- a/libraries/base/Control/Monad/Instances.hs +++ b/libraries/base/Control/Monad/Instances.hs @@ -1,5 +1,4 @@ {-# LANGUAGE Safe #-} -{-# OPTIONS_NHC98 --prelude #-} ----------------------------------------------------------------------------- -- | diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs index 747a481e21..63e6b811c4 100644 --- a/libraries/base/Data/Bits.hs +++ b/libraries/base/Data/Bits.hs @@ -331,17 +331,7 @@ instance Bits Int where bit = primBitInt testBit = primTestInt bitSize _ = SIZEOF_HSINT*8 -#elif defined(__NHC__) - (.&.) = nhc_primIntAnd - (.|.) = nhc_primIntOr - xor = nhc_primIntXor - complement = nhc_primIntCompl - shiftL = nhc_primIntLsh - shiftR = nhc_primIntRsh - bit = bitDefault - testBit = testBitDefault - bitSize _ = 32 -#endif /* __NHC__ */ +#endif x `rotate` i | i<0 && x<0 = let left = i+bitSize x in @@ -358,15 +348,6 @@ instance Bits Int where instance FiniteBits Int where finiteBitSize _ = WORD_SIZE_IN_BITS -#ifdef __NHC__ -foreign import ccall nhc_primIntAnd :: Int -> Int -> Int -foreign import ccall nhc_primIntOr :: Int -> Int -> Int -foreign import ccall nhc_primIntXor :: Int -> Int -> Int -foreign import ccall nhc_primIntLsh :: Int -> Int -> Int -foreign import ccall nhc_primIntRsh :: Int -> Int -> Int -foreign import ccall nhc_primIntCompl :: Int -> Int -#endif /* __NHC__ */ - #if defined(__GLASGOW_HASKELL__) instance Bits Word where {-# INLINE shift #-} diff --git a/libraries/base/Data/Bool.hs b/libraries/base/Data/Bool.hs index b60cad91b5..2f80c97167 100644 --- a/libraries/base/Data/Bool.hs +++ b/libraries/base/Data/Bool.hs @@ -29,14 +29,3 @@ module Data.Bool ( import GHC.Base #endif -#ifdef __NHC__ -import Prelude -import Prelude - ( Bool(..) - , (&&) - , (||) - , not - , otherwise - ) -#endif - diff --git a/libraries/base/Data/Char.hs b/libraries/base/Data/Char.hs index 56f6487371..abf4064100 100644 --- a/libraries/base/Data/Char.hs +++ b/libraries/base/Data/Char.hs @@ -69,15 +69,6 @@ import Hugs.Prelude (Ix) import Hugs.Char #endif -#ifdef __NHC__ -import Prelude -import Prelude(Char,String) -import Char -import Ix -import NHC.FFI (CInt) -foreign import ccall unsafe "WCsubst.h u_gencat" wgencat :: CInt -> CInt -#endif - -- | Convert a single digit 'Char' to the corresponding 'Int'. -- This function fails unless its argument satisfies 'isHexDigit', -- but recognises both upper and lower-case hexadecimal digits @@ -133,7 +124,7 @@ data GeneralCategory -- | The Unicode general category of the character. generalCategory :: Char -> GeneralCategory -#if defined(__GLASGOW_HASKELL__) || defined(__NHC__) +#if defined(__GLASGOW_HASKELL__) generalCategory c = toEnum $ fromIntegral $ wgencat $ fromIntegral $ ord c #endif #ifdef __HUGS__ @@ -203,9 +194,3 @@ isSeparator c = case generalCategory c of ParagraphSeparator -> True _ -> False -#ifdef __NHC__ --- dummy implementation -toTitle :: Char -> Char -toTitle = toUpper -#endif - diff --git a/libraries/base/Data/Dynamic.hs b/libraries/base/Data/Dynamic.hs index 03a34cf3c6..a3d331ed61 100644 --- a/libraries/base/Data/Dynamic.hs +++ b/libraries/base/Data/Dynamic.hs @@ -62,10 +62,6 @@ import Hugs.IORef import Hugs.IOExts #endif -#ifdef __NHC__ -import NHC.IOExtras (IORef,newIORef,readIORef,writeIORef,unsafePerformIO) -#endif - #include "Typeable.h" ------------------------------------------------------------- diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs index fd0ca01513..6ea9bcdfbe 100644 --- a/libraries/base/Data/Fixed.hs +++ b/libraries/base/Data/Fixed.hs @@ -1,9 +1,7 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP, ScopedTypeVariables, PatternGuards #-} {-# OPTIONS -Wall -fno-warn-unused-binds #-} -#ifndef __NHC__ {-# LANGUAGE DeriveDataTypeable #-} -#endif ----------------------------------------------------------------------------- -- | @@ -40,17 +38,13 @@ module Data.Fixed ) where import Prelude -- necessary to get dependencies right -#ifndef __NHC__ import Data.Typeable import Data.Data -#endif import GHC.Read import Text.ParserCombinators.ReadPrec import Text.Read.Lex -#ifndef __NHC__ default () -- avoid any defaulting shenanigans -#endif -- | generalisation of 'div' to any instance of Real div' :: (Real a,Integral b) => a -> a -> b @@ -68,13 +62,8 @@ mod' n d = n - (fromInteger f) * d where -- | The type parameter should be an instance of 'HasResolution'. newtype Fixed a = MkFixed Integer -#ifndef __NHC__ deriving (Eq,Ord,Typeable) -#else - deriving (Eq,Ord) -#endif -#ifndef __NHC__ -- We do this because the automatically derived Data instance requires (Data a) context. -- Our manual instance has the more general (Typeable a) context. tyFixed :: DataType @@ -86,7 +75,6 @@ instance (Typeable a) => Data (Fixed a) where gunfold k z _ = k (z MkFixed) dataTypeOf _ = tyFixed toConstr _ = conMkFixed -#endif class HasResolution a where resolution :: p a -> Integer @@ -176,63 +164,49 @@ convertFixed (Number n) convertFixed _ = pfail data E0 = E0 -#ifndef __NHC__ deriving (Typeable) -#endif instance HasResolution E0 where resolution _ = 1 -- | resolution of 1, this works the same as Integer type Uni = Fixed E0 data E1 = E1 -#ifndef __NHC__ deriving (Typeable) -#endif instance HasResolution E1 where resolution _ = 10 -- | resolution of 10^-1 = .1 type Deci = Fixed E1 data E2 = E2 -#ifndef __NHC__ deriving (Typeable) -#endif instance HasResolution E2 where resolution _ = 100 -- | resolution of 10^-2 = .01, useful for many monetary currencies type Centi = Fixed E2 data E3 = E3 -#ifndef __NHC__ deriving (Typeable) -#endif instance HasResolution E3 where resolution _ = 1000 -- | resolution of 10^-3 = .001 type Milli = Fixed E3 data E6 = E6 -#ifndef __NHC__ deriving (Typeable) -#endif instance HasResolution E6 where resolution _ = 1000000 -- | resolution of 10^-6 = .000001 type Micro = Fixed E6 data E9 = E9 -#ifndef __NHC__ deriving (Typeable) -#endif instance HasResolution E9 where resolution _ = 1000000000 -- | resolution of 10^-9 = .000000001 type Nano = Fixed E9 data E12 = E12 -#ifndef __NHC__ deriving (Typeable) -#endif instance HasResolution E12 where resolution _ = 1000000000000 -- | resolution of 10^-12 = .000000000001 diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index 0f2319523d..86c8f1098d 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -68,10 +68,6 @@ import Control.Monad (MonadPlus(..)) import Data.Maybe (fromMaybe, listToMaybe) import Data.Monoid -#ifdef __NHC__ -import Control.Arrow (ArrowZero(..)) -- work around nhc98 typechecker problem -#endif - #ifdef __GLASGOW_HASKELL__ import GHC.Exts (build) #endif @@ -80,8 +76,6 @@ import GHC.Exts (build) import GHC.Arr #elif defined(__HUGS__) import Hugs.Array -#elif defined(__NHC__) -import Array #endif -- | Data structures that can be folded. diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs index a66ce1bc0a..f1dcf97d76 100644 --- a/libraries/base/Data/IORef.hs +++ b/libraries/base/Data/IORef.hs @@ -51,16 +51,6 @@ import GHC.Weak #endif #endif /* __GLASGOW_HASKELL__ */ -#ifdef __NHC__ -import NHC.IOExtras - ( IORef - , newIORef - , readIORef - , writeIORef - , excludeFinalisers - ) -#endif - #if defined(__GLASGOW_HASKELL__) && !defined(__PARALLEL_HASKELL__) -- |Make a 'Weak' pointer to an 'IORef', using the second argument as a finalizer -- to run when 'IORef' is garbage-collected @@ -120,13 +110,6 @@ atomicModifyIORef = plainModifyIORef -- Hugs has no preemption where plainModifyIORef r f = do a <- readIORef r case f a of (a',b) -> writeIORef r a' >> return b -#elif defined(__NHC__) -atomicModifyIORef r f = - excludeFinalisers $ do - a <- readIORef r - let (a',b) = f a - writeIORef r a' - return b #endif -- | Strict version of 'atomicModifyIORef'. This forces both the value stored diff --git a/libraries/base/Data/Int.hs b/libraries/base/Data/Int.hs index 084bb0ef05..874d47ec13 100644 --- a/libraries/base/Data/Int.hs +++ b/libraries/base/Data/Int.hs @@ -35,13 +35,6 @@ import GHC.Int ( Int8, Int16, Int32, Int64 ) import Hugs.Int ( Int8, Int16, Int32, Int64 ) #endif -#ifdef __NHC__ -import Prelude -import Prelude (Int) -import NHC.FFI (Int8, Int16, Int32, Int64) -import NHC.SizedTypes (Int8, Int16, Int32, Int64) -- instances of Bits -#endif - {- $notes * All arithmetic is performed modulo 2^n, where @n@ is the number of diff --git a/libraries/base/Data/Ix.hs b/libraries/base/Data/Ix.hs index 44fc4099ba..d916f29f50 100644 --- a/libraries/base/Data/Ix.hs +++ b/libraries/base/Data/Ix.hs @@ -72,7 +72,3 @@ import GHC.Arr import Hugs.Prelude( Ix(..) ) #endif -#ifdef __NHC__ -import Ix (Ix(..)) -#endif - diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs index 0049237aac..e7e8602cba 100644 --- a/libraries/base/Data/List.hs +++ b/libraries/base/Data/List.hs @@ -17,11 +17,6 @@ module Data.List ( -#ifdef __NHC__ - [] (..) - , -#endif - -- * Basic functions (++) @@ -210,10 +205,6 @@ module Data.List ) where -#ifdef __NHC__ -import Prelude -#endif - import Data.Maybe import Data.Char ( isSpace ) diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs index 728c981755..a71c2d71b6 100644 --- a/libraries/base/Data/Maybe.hs +++ b/libraries/base/Data/Maybe.hs @@ -35,21 +35,6 @@ module Data.Maybe import GHC.Base #endif -#ifdef __NHC__ -import Prelude -import Prelude (Maybe(..), maybe) -import Maybe - ( isJust - , isNothing - , fromJust - , fromMaybe - , listToMaybe - , maybeToList - , catMaybes - , mapMaybe - ) -#else - #ifndef __HUGS__ -- --------------------------------------------------------------------------- -- The Maybe type, and instances @@ -146,5 +131,3 @@ mapMaybe f (x:xs) = Nothing -> rs Just r -> r:rs -#endif /* else not __NHC__ */ - diff --git a/libraries/base/Data/OldTypeable.hs b/libraries/base/Data/OldTypeable.hs index 9c75623322..2d5f0d464d 100644 --- a/libraries/base/Data/OldTypeable.hs +++ b/libraries/base/Data/OldTypeable.hs @@ -119,15 +119,6 @@ import Hugs.IOArray import Hugs.ConcBase ( MVar ) #endif -#ifdef __NHC__ -import NHC.IOExtras (IOArray,IORef,newIORef,readIORef,writeIORef,unsafePerformIO) -import IO (Handle) -import Ratio (Ratio) - -- For the Typeable instance -import NHC.FFI ( Ptr,FunPtr,StablePtr,ForeignPtr ) -import Array ( Array ) -#endif - #include "OldTypeable.h" {-# DEPRECATED typeRepKey "TypeRep itself is now an instance of Ord" #-} diff --git a/libraries/base/Data/OldTypeable/Internal.hs b/libraries/base/Data/OldTypeable/Internal.hs index 817dc4c68a..96bbf0ba62 100644 --- a/libraries/base/Data/OldTypeable/Internal.hs +++ b/libraries/base/Data/OldTypeable/Internal.hs @@ -508,14 +508,12 @@ INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef") INSTANCE_TYPEABLE3(STArray,sTArrayTc,"STArray") #endif -#ifndef __NHC__ INSTANCE_TYPEABLE2((,),pairTc,"(,)") INSTANCE_TYPEABLE3((,,),tup3Tc,"(,,)") INSTANCE_TYPEABLE4((,,,),tup4Tc,"(,,,)") INSTANCE_TYPEABLE5((,,,,),tup5Tc,"(,,,,)") INSTANCE_TYPEABLE6((,,,,,),tup6Tc,"(,,,,,)") INSTANCE_TYPEABLE7((,,,,,,),tup7Tc,"(,,,,,,)") -#endif /* __NHC__ */ INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr") INSTANCE_TYPEABLE1(FunPtr,funPtrTc,"FunPtr") @@ -536,9 +534,7 @@ INSTANCE_TYPEABLE0(Char,charTc,"Char") INSTANCE_TYPEABLE0(Float,floatTc,"Float") INSTANCE_TYPEABLE0(Double,doubleTc,"Double") INSTANCE_TYPEABLE0(Int,intTc,"Int") -#ifndef __NHC__ INSTANCE_TYPEABLE0(Word,wordTc,"Word" ) -#endif INSTANCE_TYPEABLE0(Integer,integerTc,"Integer") INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering") #ifndef __GLASGOW_HASKELL__ diff --git a/libraries/base/Data/Ratio.hs b/libraries/base/Data/Ratio.hs index a9f726e849..d17e0bce3f 100644 --- a/libraries/base/Data/Ratio.hs +++ b/libraries/base/Data/Ratio.hs @@ -35,10 +35,6 @@ import GHC.Real -- The basic defns for Ratio import Hugs.Prelude(Ratio(..), (%), numerator, denominator) #endif -#ifdef __NHC__ -import Ratio (Ratio(..), (%), numerator, denominator, approxRational) -#else - -- ----------------------------------------------------------------------------- -- approxRational @@ -83,5 +79,4 @@ approxRational rat eps = simplest (rat-eps) (rat+eps) nd'' = simplest' d' r' d r n'' = numerator nd'' d'' = denominator nd'' -#endif diff --git a/libraries/base/Data/String.hs b/libraries/base/Data/String.hs index 0124f13ab0..391602eb96 100644 --- a/libraries/base/Data/String.hs +++ b/libraries/base/Data/String.hs @@ -37,8 +37,6 @@ import Data.List (lines, words, unlines, unwords) class IsString a where fromString :: String -> a -#ifndef __NHC__ instance IsString [Char] where fromString xs = xs -#endif diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs index 2ae49c63ae..f5ac06086b 100644 --- a/libraries/base/Data/Traversable.hs +++ b/libraries/base/Data/Traversable.hs @@ -61,8 +61,6 @@ import Data.Monoid (Monoid) import GHC.Arr #elif defined(__HUGS__) import Hugs.Array -#elif defined(__NHC__) -import Array #endif -- | Functors representing data structures that can be traversed from diff --git a/libraries/base/Data/Tuple.hs b/libraries/base/Data/Tuple.hs index 12684c3ac4..6d7e2f7f6d 100644 --- a/libraries/base/Data/Tuple.hs +++ b/libraries/base/Data/Tuple.hs @@ -23,22 +23,6 @@ module Data.Tuple , curry , uncurry , swap -#ifdef __NHC__ - , (,)(..) - , (,,)(..) - , (,,,)(..) - , (,,,,)(..) - , (,,,,,)(..) - , (,,,,,,)(..) - , (,,,,,,,)(..) - , (,,,,,,,,)(..) - , (,,,,,,,,,)(..) - , (,,,,,,,,,,)(..) - , (,,,,,,,,,,,)(..) - , (,,,,,,,,,,,,)(..) - , (,,,,,,,,,,,,,)(..) - , (,,,,,,,,,,,,,,)(..) -#endif ) where @@ -58,35 +42,12 @@ import GHC.Tuple #endif /* __GLASGOW_HASKELL__ */ -#ifdef __NHC__ -import Prelude -import Prelude - ( (,)(..) - , (,,)(..) - , (,,,)(..) - , (,,,,)(..) - , (,,,,,)(..) - , (,,,,,,)(..) - , (,,,,,,,)(..) - , (,,,,,,,,)(..) - , (,,,,,,,,,)(..) - , (,,,,,,,,,,)(..) - , (,,,,,,,,,,,)(..) - , (,,,,,,,,,,,,)(..) - , (,,,,,,,,,,,,,)(..) - , (,,,,,,,,,,,,,,)(..) - -- nhc98's prelude only supplies tuple instances up to size 15 - , fst, snd - , curry, uncurry - ) -#endif - default () -- Double isn't available yet -- --------------------------------------------------------------------------- -- Standard functions over tuples -#if !defined(__HUGS__) && !defined(__NHC__) +#if !defined(__HUGS__) -- | Extract the first component of a pair. fst :: (a,b) -> a fst (x,_) = x @@ -102,7 +63,7 @@ curry f x y = f (x, y) -- | 'uncurry' converts a curried function to a function on pairs. uncurry :: (a -> b -> c) -> ((a, b) -> c) uncurry f p = f (fst p) (snd p) -#endif /* neither __HUGS__ nor __NHC__ */ +#endif -- | Swap the components of a pair. swap :: (a,b) -> (b,a) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 99ad0b667c..8749275554 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -324,14 +324,12 @@ INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef") INSTANCE_TYPEABLE3(STArray,sTArrayTc,"STArray") #endif -#ifndef __NHC__ INSTANCE_TYPEABLE2((,),pairTc,"(,)") INSTANCE_TYPEABLE3((,,),tup3Tc,"(,,)") INSTANCE_TYPEABLE4((,,,),tup4Tc,"(,,,)") INSTANCE_TYPEABLE5((,,,,),tup5Tc,"(,,,,)") INSTANCE_TYPEABLE6((,,,,,),tup6Tc,"(,,,,,)") INSTANCE_TYPEABLE7((,,,,,,),tup7Tc,"(,,,,,,)") -#endif /* __NHC__ */ INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr") INSTANCE_TYPEABLE1(FunPtr,funPtrTc,"FunPtr") @@ -352,9 +350,7 @@ INSTANCE_TYPEABLE0(Char,charTc,"Char") INSTANCE_TYPEABLE0(Float,floatTc,"Float") INSTANCE_TYPEABLE0(Double,doubleTc,"Double") INSTANCE_TYPEABLE0(Int,intTc,"Int") -#ifndef __NHC__ INSTANCE_TYPEABLE0(Word,wordTc,"Word" ) -#endif INSTANCE_TYPEABLE0(Integer,integerTc,"Integer") INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering") #ifndef __GLASGOW_HASKELL__ diff --git a/libraries/base/Data/Version.hs b/libraries/base/Data/Version.hs index b0dd92e9ae..02089317b3 100644 --- a/libraries/base/Data/Version.hs +++ b/libraries/base/Data/Version.hs @@ -40,7 +40,7 @@ import Prelude -- necessary to get dependencies right -- of GHC. In which case, we might need to pick up ReadP from -- Distribution.Compat.ReadP, because the version in -- Text.ParserCombinators.ReadP doesn't have all the combinators we need. -#if __GLASGOW_HASKELL__ || __HUGS__ || __NHC__ +#if __GLASGOW_HASKELL__ || __HUGS__ import Text.ParserCombinators.ReadP #else import Distribution.Compat.ReadP @@ -137,8 +137,6 @@ showVersion (Version branch tags) -- #if __GLASGOW_HASKELL__ || __HUGS__ parseVersion :: ReadP Version -#elif __NHC__ -parseVersion :: ReadPN r Version #else parseVersion :: ReadP r Version #endif diff --git a/libraries/base/Data/Word.hs b/libraries/base/Data/Word.hs index 84a4d0721c..39aa1a821d 100644 --- a/libraries/base/Data/Word.hs +++ b/libraries/base/Data/Word.hs @@ -35,12 +35,6 @@ import GHC.Word import Hugs.Word #endif -#ifdef __NHC__ -import NHC.FFI (Word8, Word16, Word32, Word64) -import NHC.SizedTypes (Word8, Word16, Word32, Word64) -- instances of Bits -type Word = Word32 -#endif - {- $notes * All arithmetic is performed modulo 2^n, where n is the number of diff --git a/libraries/base/Foreign/C/Error.hs b/libraries/base/Foreign/C/Error.hs index 17ab2d0716..4d332623cf 100644 --- a/libraries/base/Foreign/C/Error.hs +++ b/libraries/base/Foreign/C/Error.hs @@ -88,9 +88,7 @@ module Foreign.C.Error ( -- this is were we get the CONST_XXX definitions from that configure -- calculated for us -- -#ifndef __NHC__ #include "HsBaseConfig.h" -#endif import Foreign.Ptr import Foreign.C.Types @@ -154,9 +152,6 @@ eOK, e2BIG, eACCES, eADDRINUSE, eADDRNOTAVAIL, eADV, eAFNOSUPPORT, eAGAIN, -- configure -- eOK = Errno 0 -#ifdef __NHC__ -#include "Errno.hs" -#else e2BIG = Errno (CONST_E2BIG) eACCES = Errno (CONST_EACCES) eADDRINUSE = Errno (CONST_EADDRINUSE) @@ -255,7 +250,6 @@ eTXTBSY = Errno (CONST_ETXTBSY) eUSERS = Errno (CONST_EUSERS) eWOULDBLOCK = Errno (CONST_EWOULDBLOCK) eXDEV = Errno (CONST_EXDEV) -#endif -- | Yield 'True' if the given 'Errno' value is valid on the system. -- This implies that the 'Eq' instance of 'Errno' is also system dependent @@ -278,25 +272,16 @@ getErrno :: IO Errno -- We must call a C function to get the value of errno in general. On -- threaded systems, errno is hidden behind a C macro so that each OS -- thread gets its own copy. -#ifdef __NHC__ -getErrno = do e <- peek _errno; return (Errno e) -foreign import ccall unsafe "errno.h &errno" _errno :: Ptr CInt -#else getErrno = do e <- get_errno; return (Errno e) foreign import ccall unsafe "HsBase.h __hscore_get_errno" get_errno :: IO CInt -#endif -- | Reset the current thread\'s @errno@ value to 'eOK'. -- resetErrno :: IO () -- Again, setting errno has to be done via a C function. -#ifdef __NHC__ -resetErrno = poke _errno 0 -#else resetErrno = set_errno 0 foreign import ccall unsafe "HsBase.h __hscore_set_errno" set_errno :: CInt -> IO () -#endif -- throw current "errno" value -- --------------------------- diff --git a/libraries/base/Foreign/C/Types.hs b/libraries/base/Foreign/C/Types.hs index f94129ab7b..234b4edd2d 100644 --- a/libraries/base/Foreign/C/Types.hs +++ b/libraries/base/Foreign/C/Types.hs @@ -76,8 +76,6 @@ module Foreign.C.Types , CFile, CFpos, CJmpBuf ) where -#ifndef __NHC__ - import Foreign.Storable import Data.Bits ( Bits(..) ) import Data.Int ( Int8, Int16, Int32, Int64 ) @@ -277,58 +275,3 @@ representing a C type @t@: -} -#else /* __NHC__ */ - -import NHC.FFI - ( CChar(..), CSChar(..), CUChar(..) - , CShort(..), CUShort(..), CInt(..), CUInt(..) - , CLong(..), CULong(..), CLLong(..), CULLong(..) - , CPtrdiff(..), CSize(..), CWchar(..), CSigAtomic(..) - , CClock(..), CTime(..), CUSeconds(..), CSUSeconds(..) - , CFloat(..), CDouble(..), CLDouble(..) - , CIntPtr(..), CUIntPtr(..), CIntMax(..), CUIntMax(..) - , CFile, CFpos, CJmpBuf - , Storable(..) - ) -import Data.Bits -import NHC.SizedTypes - -#define INSTANCE_BITS(T) \ -instance Bits T where { \ - (T x) .&. (T y) = T (x .&. y) ; \ - (T x) .|. (T y) = T (x .|. y) ; \ - (T x) `xor` (T y) = T (x `xor` y) ; \ - complement (T x) = T (complement x) ; \ - shift (T x) n = T (shift x n) ; \ - rotate (T x) n = T (rotate x n) ; \ - bit n = T (bit n) ; \ - setBit (T x) n = T (setBit x n) ; \ - clearBit (T x) n = T (clearBit x n) ; \ - complementBit (T x) n = T (complementBit x n) ; \ - testBit (T x) n = testBit x n ; \ - bitSize (T x) = bitSize x ; \ - isSigned (T x) = isSigned x ; \ - popCount (T x) = popCount x } - -INSTANCE_BITS(CChar) -INSTANCE_BITS(CSChar) -INSTANCE_BITS(CUChar) -INSTANCE_BITS(CShort) -INSTANCE_BITS(CUShort) -INSTANCE_BITS(CInt) -INSTANCE_BITS(CUInt) -INSTANCE_BITS(CLong) -INSTANCE_BITS(CULong) -INSTANCE_BITS(CLLong) -INSTANCE_BITS(CULLong) -INSTANCE_BITS(CPtrdiff) -INSTANCE_BITS(CWchar) -INSTANCE_BITS(CSigAtomic) -INSTANCE_BITS(CSize) -INSTANCE_BITS(CIntPtr) -INSTANCE_BITS(CUIntPtr) -INSTANCE_BITS(CIntMax) -INSTANCE_BITS(CUIntMax) - -#endif - diff --git a/libraries/base/Foreign/ForeignPtr/Imp.hs b/libraries/base/Foreign/ForeignPtr/Imp.hs index 336f0321b1..f2c019ea34 100644 --- a/libraries/base/Foreign/ForeignPtr/Imp.hs +++ b/libraries/base/Foreign/ForeignPtr/Imp.hs @@ -55,29 +55,11 @@ module Foreign.ForeignPtr.Imp import Foreign.Ptr -#ifdef __NHC__ -import NHC.FFI - ( ForeignPtr - , FinalizerPtr - , newForeignPtr - , newForeignPtr_ - , addForeignPtrFinalizer - , withForeignPtr - , unsafeForeignPtrToPtr - , touchForeignPtr - , castForeignPtr - , Storable(sizeOf) - , malloc, mallocBytes, finalizerFree - ) -#endif - #ifdef __HUGS__ import Hugs.ForeignPtr #endif -#ifndef __NHC__ import Foreign.Storable ( Storable(sizeOf) ) -#endif #ifdef __GLASGOW_HASKELL__ import GHC.Base @@ -86,7 +68,7 @@ import GHC.Err ( undefined ) import GHC.ForeignPtr #endif -#if !defined(__NHC__) && !defined(__GLASGOW_HASKELL__) +#if !defined(__GLASGOW_HASKELL__) import Foreign.Marshal.Alloc ( malloc, mallocBytes, finalizerFree ) instance Eq (ForeignPtr a) where @@ -100,7 +82,6 @@ instance Show (ForeignPtr a) where #endif -#ifndef __NHC__ newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a) -- ^Turns a plain memory reference into a foreign pointer, and -- associates a finalizer with the reference. The finalizer will be @@ -136,7 +117,6 @@ withForeignPtr fo io = do r <- io (unsafeForeignPtrToPtr fo) touchForeignPtr fo return r -#endif /* ! __NHC__ */ #if defined(__HUGS__) || defined(__GLASGOW_HASKELL__) -- | This variant of 'newForeignPtr' adds a finalizer that expects an diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs index c38f0cc689..dc4e399ece 100644 --- a/libraries/base/Foreign/Marshal/Alloc.hs +++ b/libraries/base/Foreign/Marshal/Alloc.hs @@ -76,9 +76,6 @@ import GHC.Real import GHC.Ptr import GHC.Err import GHC.Base -#elif defined(__NHC__) -import NHC.FFI ( FinalizerPtr, CInt(..) ) -import IO ( bracket ) #else import Control.Exception.Base ( bracket ) #endif diff --git a/libraries/base/Foreign/Marshal/Pool.hs b/libraries/base/Foreign/Marshal/Pool.hs index 5187d757aa..bc35dcf925 100644 --- a/libraries/base/Foreign/Marshal/Pool.hs +++ b/libraries/base/Foreign/Marshal/Pool.hs @@ -56,12 +56,8 @@ import GHC.List ( elem, length ) import GHC.Num ( Num(..) ) #else import Data.IORef ( IORef, newIORef, readIORef, writeIORef ) -#if defined(__NHC__) -import IO ( bracket ) -#else import Control.Exception.Base ( bracket ) #endif -#endif import Control.Monad ( liftM ) import Data.List ( delete ) diff --git a/libraries/base/Foreign/Marshal/Utils.hs b/libraries/base/Foreign/Marshal/Utils.hs index d21222d9f9..dc6471ad17 100644 --- a/libraries/base/Foreign/Marshal/Utils.hs +++ b/libraries/base/Foreign/Marshal/Utils.hs @@ -57,10 +57,6 @@ import GHC.Num import GHC.Base #endif -#ifdef __NHC__ -import Foreign.C.Types ( CInt(..) ) -#endif - -- combined allocation and marshalling -- ----------------------------------- diff --git a/libraries/base/Foreign/Ptr.hs b/libraries/base/Foreign/Ptr.hs index b0a1a8ab8e..4632714052 100644 --- a/libraries/base/Foreign/Ptr.hs +++ b/libraries/base/Foreign/Ptr.hs @@ -47,7 +47,6 @@ module Foreign.Ptr ( freeHaskellFunPtr, -- Free the function pointer created by foreign export dynamic. -#ifndef __NHC__ -- * Integral types with lossless conversion to and from pointers IntPtr, ptrToIntPtr, @@ -55,7 +54,6 @@ module Foreign.Ptr ( WordPtr, ptrToWordPtr, wordPtrToPtr -#endif ) where #ifdef __GLASGOW_HASKELL__ @@ -75,23 +73,6 @@ import Data.Bits import Data.Typeable import Foreign.Storable ( Storable(..) ) -#ifdef __NHC__ -import NHC.FFI - ( Ptr - , nullPtr - , castPtr - , plusPtr - , alignPtr - , minusPtr - , FunPtr - , nullFunPtr - , castFunPtr - , castFunPtrToPtr - , castPtrToFunPtr - , freeHaskellFunPtr - ) -#endif - #ifdef __HUGS__ import Hugs.Ptr #endif @@ -105,11 +86,10 @@ foreign import ccall unsafe "freeHaskellFunctionPtr" freeHaskellFunPtr :: FunPtr a -> IO () #endif -#ifndef __NHC__ -# include "HsBaseConfig.h" -# include "CTypes.h" +#include "HsBaseConfig.h" +#include "CTypes.h" -# ifdef __GLASGOW_HASKELL__ +#ifdef __GLASGOW_HASKELL__ -- | An unsigned integral type that can be losslessly converted to and from -- @Ptr@. This type is also compatible with the C99 type @uintptr_t@, and -- can be marshalled to and from that type safely. @@ -138,7 +118,7 @@ ptrToIntPtr (Ptr a#) = IntPtr (I# (addr2Int# a#)) intPtrToPtr :: IntPtr -> Ptr a intPtrToPtr (IntPtr (I# i#)) = Ptr (int2Addr# i#) -# else /* !__GLASGOW_HASKELL__ */ +#else /* !__GLASGOW_HASKELL__ */ INTEGRAL_TYPE(WordPtr,tyConWordPtr,"WordPtr",CUIntPtr) INTEGRAL_TYPE(IntPtr,tyConIntPtr,"IntPtr",CIntPtr) @@ -157,6 +137,5 @@ foreign import ccall unsafe "__hscore_to_intptr" foreign import ccall unsafe "__hscore_from_intptr" intPtrToPtr :: IntPtr -> Ptr a -# endif /* !__GLASGOW_HASKELL__ */ -#endif /* !__NHC_ */ +#endif /* !__GLASGOW_HASKELL__ */ diff --git a/libraries/base/Foreign/StablePtr.hs b/libraries/base/Foreign/StablePtr.hs index 78bdc9db66..db27b06063 100644 --- a/libraries/base/Foreign/StablePtr.hs +++ b/libraries/base/Foreign/StablePtr.hs @@ -38,17 +38,6 @@ import GHC.Stable import Hugs.StablePtr #endif -#ifdef __NHC__ -import NHC.FFI - ( StablePtr - , newStablePtr - , deRefStablePtr - , freeStablePtr - , castStablePtrToPtr - , castPtrToStablePtr - ) -#endif - -- $cinterface -- -- The following definition is available to C programs inter-operating with diff --git a/libraries/base/Foreign/Storable.hs b/libraries/base/Foreign/Storable.hs index bf3735b9e0..40d5fda545 100644 --- a/libraries/base/Foreign/Storable.hs +++ b/libraries/base/Foreign/Storable.hs @@ -34,11 +34,6 @@ module Foreign.Storable ) where -#ifdef __NHC__ -import NHC.FFI (Storable(..),Ptr,FunPtr,StablePtr - ,Int8,Int16,Int32,Int64,Word8,Word16,Word32,Word64) -#else - import Control.Monad ( liftM ) #include "MachDeps.h" @@ -204,10 +199,8 @@ STORABLE(Char,SIZEOF_HSCHAR,ALIGNMENT_HSCHAR, STORABLE(Int,SIZEOF_HSINT,ALIGNMENT_HSINT, readIntOffPtr,writeIntOffPtr) -#ifndef __NHC__ STORABLE(Word,SIZEOF_HSWORD,ALIGNMENT_HSWORD, readWordOffPtr,writeWordOffPtr) -#endif STORABLE((Ptr a),SIZEOF_HSPTR,ALIGNMENT_HSPTR, readPtrOffPtr,writePtrOffPtr) @@ -248,8 +241,6 @@ STORABLE(Int32,SIZEOF_INT32,ALIGNMENT_INT32, STORABLE(Int64,SIZEOF_INT64,ALIGNMENT_INT64, readInt64OffPtr,writeInt64OffPtr) -#endif - -- XXX: here to avoid orphan instance in GHC.Fingerprint #ifdef __GLASGOW_HASKELL__ instance Storable Fingerprint where diff --git a/libraries/base/GHC/IO/Device.hs b/libraries/base/GHC/IO/Device.hs index f3f330bbcf..963cb9f9e5 100644 --- a/libraries/base/GHC/IO/Device.hs +++ b/libraries/base/GHC/IO/Device.hs @@ -35,12 +35,6 @@ import GHC.Num import GHC.IO import {-# SOURCE #-} GHC.IO.Exception ( unsupportedOperation ) #endif -#ifdef __NHC__ -import Foreign -import Ix -import Control.Exception.Base -unsupportedOperation = userError "unsupported operation" -#endif -- | A low-level I/O provider where the data is bytes in memory. class RawIO a where diff --git a/libraries/base/Makefile.nhc98 b/libraries/base/Makefile.nhc98 deleted file mode 100644 index 25fb832e37..0000000000 --- a/libraries/base/Makefile.nhc98 +++ /dev/null @@ -1,86 +0,0 @@ -THISPKG = base -SEARCH = -I$(TOPDIR)/targets/$(MACHINE) -Iinclude \ - -I../../prelude/PreludeIO -I../../prelude/`$(LOCAL)harch` -EXTRA_H_FLAGS = -H4M -K6M -EXTRA_C_FLAGS = -D__NHC__ -EXTRA_HBC_FLAGS = -H16M -A1M - -DIRS = \ - Data Debug Control Control/Monad System System/IO System/Console \ - Text Text/Html Text/Show Text/ParserCombinators Text/Regex \ - Foreign Foreign/Marshal Foreign/C NHC Unsafe System/Posix \ - Control/Exception GHC GHC/IO - -SRCS = \ - Data/Bits.hs Data/Bool.hs Data/Char.hs Data/Complex.hs \ - Data/Either.hs Data/IORef.hs Data/Int.hs \ - Data/Ix.hs Data/List.hs Data/Maybe.hs \ - Data/Ratio.hs Data/Tuple.hs Data/Word.hs \ - Data/HashTable.hs Data/Typeable.hs Data/Dynamic.hs \ - Data/Monoid.hs Data/String.hs \ - Data/Eq.hs Data/Ord.hs Data/Fixed.hs \ - Data/Functor.hs Data/Foldable.hs Data/Traversable.hs \ - Data/Function.hs \ - Control/Monad.hs Control/Monad/Fix.hs Control/Monad/Instances.hs \ - Control/Arrow.hs Control/Applicative.hs \ - Control/Exception.hs Control/Exception/Base.hs Control/Category.hs \ - Debug/Trace.hs \ - NHC/SizedTypes.hs NHC/PosixTypes.hsc \ - System/IO.hs System/IO/Error.hs System/IO/Unsafe.hs \ - System/Environment.hs System/Exit.hs \ - System/Mem.hs System/Info.hs \ - System/CPUTime.hsc \ - Foreign/Ptr.hs Foreign/StablePtr.hs Foreign/Storable.hs \ - Foreign/ForeignPtr.hs Foreign/C/Types.hs \ - Foreign/Marshal/Alloc.hs Foreign/Marshal/Array.hs \ - Foreign/Marshal/Utils.hs Foreign/Marshal/Error.hs \ - Foreign/Marshal/Pool.hs Foreign/Marshal.hs \ - Foreign/C/String.hs Foreign/C/Error.hs Foreign/C.hs Foreign.hs \ - Text/Printf.hs \ - Text/Read.hs Text/Show.hs Text/Show/Functions.hs \ - Text/ParserCombinators/ReadP.hs Data/Version.hs \ - Unsafe/Coerce.hs \ - WCsubst.c \ - GHC/IO/Device.hs \ - System/Posix/Types.hs System/Posix/Internals.hs \ - System/Console/GetOpt.hs \ - -# Data/String.hs -# Text/ParserCombinators/ReadPrec.hs -# Text/Read/Lex.hs - -# now moved to separate packages: -# System/Directory.hs \ -# System/Directory/Internals.hs \ -# Text/PrettyPrint/HughesPJ.hs Text/PrettyPrint.hs \ -# System/Random.hs System/Locale.hs System/Time.hsc \ -# System/Cmd.hs \ -# System/Timeout.hs \ - -# Text/Regex/Posix.hsc Text/Regex.hs \ -# [Data/Dynamic.hs] Data/Generics.hs Data/STRef.hs Data/Unique.hs -# System/Mem.hs System/Mem/StableName.hs System/Mem/Weak.hs -# System/Posix/Types.hs System/Posix/Signals.hsc -# System/FilePath.hs -# dirUtils.c - - -# Here are the main rules. -include ../Makefile.common - -# some extra rules -extra: - if [ -f Prelude.hs ]; then mv Prelude.hs Prelude.hs.unused; fi - if [ -f Numeric.hs ]; then mv Numeric.hs Numeric.hs.unused; fi - $(INSTALL) include/Typeable.h $(INCDIR)/packages/$(THISPKG) - $(INSTALL) include/Nhc98BaseConfig.h $(INCDIR)/packages/$(THISPKG) -extracfiles: - if [ -f Prelude.hs ]; then mv Prelude.hs Prelude.hs.unused; fi - if [ -f Numeric.hs ]; then mv Numeric.hs Numeric.hs.unused; fi - $(INSTALL) include/Typeable.h $(INCDIR)/packages/$(THISPKG) - $(INSTALL) include/Nhc98BaseConfig.h $(INCDIR)/packages/$(THISPKG) - -# Here are any extra dependencies. - -# C-files dependencies. - diff --git a/libraries/base/NHC/Makefile b/libraries/base/NHC/Makefile deleted file mode 100644 index e69de29bb2..0000000000 --- a/libraries/base/NHC/Makefile +++ /dev/null diff --git a/libraries/base/NHC/PosixTypes.hsc b/libraries/base/NHC/PosixTypes.hsc deleted file mode 100644 index efae04eeda..0000000000 --- a/libraries/base/NHC/PosixTypes.hsc +++ /dev/null @@ -1,90 +0,0 @@ -{-# LANGUAGE CPP #-} -{-# OPTIONS_NHC98 -I/usr/include #-} - ------------------------------------------------------------------------------ --- | --- Module : NHC.PosixTypes --- Copyright : (c) Malcolm Wallace 2007 --- License : BSD-style (see the file libraries/base/LICENSE) --- --- Maintainer : libraries@haskell.org --- Stability : provisional --- Portability : non-portable (requires POSIX) --- --- POSIX data types: Haskell equivalents of the types defined by the --- @\<sys\/types.h>@ C header on a POSIX system. --- ------------------------------------------------------------------------------ - -module NHC.PosixTypes ( - - -- * POSIX data types - CDev, - CIno, - CMode, - COff, - CPid, - CSsize, - - CGid, - CNlink, - CUid, - CCc, - CSpeed, - CTcflag, - CRLim, - - Fd(..), - - LinkCount, - UserID, - GroupID, - ) where - -import Foreign -import Foreign.C -import Data.Typeable -import Data.Bits -import Unsafe.Coerce - -import Control.Monad - - --- Curious hack to ensure that the CTypes macros are expanded *after* hsc2hs. -##include "CTypes.h" --- C header files that contain all the types we are looking for here. -#if __APPLE__ -#include <libc.h> -#endif -#include <stdlib.h> -#include <unistd.h> -#include <sys/resource.h> -#include <termios.h> - -ARITHMETIC_TYPE(CDev,tyConCDev,"CDev",#{type dev_t}) -INTEGRAL_TYPE(CIno,tyConCIno,"CIno",#{type ino_t}) -INTEGRAL_TYPE(CMode,tyConCMode,"CMode",#{type mode_t}) -INTEGRAL_TYPE(COff,tyConCOff,"COff",#{type off_t}) -INTEGRAL_TYPE(CPid,tyConCPid,"CPid",#{type pid_t}) - -INTEGRAL_TYPE(CSsize,tyConCSsize,"CSsize",#{type ssize_t}) - -INTEGRAL_TYPE(CGid,tyConCGid,"CGid",#{type gid_t}) -INTEGRAL_TYPE(CNlink,tyConCNlink,"CNlink",#{type nlink_t}) - -INTEGRAL_TYPE(CUid,tyConCUid,"CUid",#{type uid_t}) -ARITHMETIC_TYPE(CCc,tyConCCc,"CCc",#{type cc_t}) -ARITHMETIC_TYPE(CSpeed,tyConCSpeed,"CSpeed",#{type speed_t}) -INTEGRAL_TYPE(CTcflag,tyConCTcflag,"CTcflag",#{type tcflag_t}) -INTEGRAL_TYPE(CRLim,tyConCRlim,"CRLim",#{type rlim_t}) - --- ToDo: blksize_t, clockid_t, blkcnt_t, fsblkcnt_t, fsfilcnt_t, id_t, key_t --- suseconds_t, timer_t, useconds_t - --- Make an Fd type rather than using CInt everywhere -INTEGRAL_TYPE(Fd,tyConFd,"Fd",CInt) - --- nicer names, and backwards compatibility with POSIX library: -type LinkCount = CNlink -type UserID = CUid -type GroupID = CGid diff --git a/libraries/base/NHC/SizedTypes.hs b/libraries/base/NHC/SizedTypes.hs deleted file mode 100644 index 85b2705380..0000000000 --- a/libraries/base/NHC/SizedTypes.hs +++ /dev/null @@ -1,52 +0,0 @@ -module NHC.SizedTypes - -- This module just adds instances of Bits for Int/Word[8,16,32,64] - ( Int8, Int16, Int32, Int64 - , Word8, Word16, Word32, Word64 - ) where - -{- Note explicit braces and semicolons here - layout is corrupted by cpp. -} - -{ - import NHC.FFI (Int8,Int16,Int32,Int64,Word8,Word16,Word32,Word64) -; import Data.Bits - -#define SIZED_TYPE(T,BS,S) \ -; FOREIGNS(T) \ -; INSTANCE_BITS(T,BS,S) - - -#define FOREIGNS(T) \ -; foreign import ccall nhc_prim/**/T/**/And :: T -> T -> T \ -; foreign import ccall nhc_prim/**/T/**/Or :: T -> T -> T \ -; foreign import ccall nhc_prim/**/T/**/Xor :: T -> T -> T \ -; foreign import ccall nhc_prim/**/T/**/Lsh :: T -> Int -> T \ -; foreign import ccall nhc_prim/**/T/**/Rsh :: T -> Int -> T \ -; foreign import ccall nhc_prim/**/T/**/Compl :: T -> T - - -#define INSTANCE_BITS(T,BS,S) \ -; instance Bits T where \ - { (.&.) = nhc_prim/**/T/**/And \ - ; (.|.) = nhc_prim/**/T/**/Or \ - ; xor = nhc_prim/**/T/**/Xor \ - ; complement = nhc_prim/**/T/**/Compl \ - ; shiftL = nhc_prim/**/T/**/Lsh \ - ; shiftR = nhc_prim/**/T/**/Rsh \ - ; bitSize _ = BS \ - ; isSigned _ = S \ - ; bit = bitDefault \ - ; testBit = testBitDefault \ - ; popCount = popCountDefault \ - } - -SIZED_TYPE(Int8,8,True) -SIZED_TYPE(Int16,16,True) -SIZED_TYPE(Int32,32,True) -SIZED_TYPE(Int64,64,True) - -SIZED_TYPE(Word8,8,False) -SIZED_TYPE(Word16,16,False) -SIZED_TYPE(Word32,32,False) -SIZED_TYPE(Word64,64,False) - -} diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs index 843d772521..8ea9b91a54 100644 --- a/libraries/base/Prelude.hs +++ b/libraries/base/Prelude.hs @@ -37,13 +37,6 @@ module Prelude ( -- *** Tuples fst, snd, curry, uncurry, -#if defined(__NHC__) - []((:), []), -- Not legal Haskell 98; - -- ... available through built-in syntax - module Data.Tuple, -- Includes tuple types - ()(..), -- Not legal Haskell 98 - (->), -- ... available through built-in syntax -#endif #ifdef __HUGS__ (:), -- Not legal Haskell 98 #endif 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 diff --git a/libraries/base/Text/ParserCombinators/ReadP.hs b/libraries/base/Text/ParserCombinators/ReadP.hs index cb66e21b6d..72338848dd 100644 --- a/libraries/base/Text/ParserCombinators/ReadP.hs +++ b/libraries/base/Text/ParserCombinators/ReadP.hs @@ -1,8 +1,6 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP, NoImplicitPrelude #-} -#ifndef __NHC__ {-# LANGUAGE RankNTypes #-} -#endif #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE MagicHash #-} #endif @@ -28,11 +26,7 @@ module Text.ParserCombinators.ReadP ( -- * The 'ReadP' type -#ifndef __NHC__ ReadP, -#else - ReadPN, -#endif -- * Primitive operations get, @@ -159,12 +153,7 @@ instance MonadPlus P where -- --------------------------------------------------------------------------- -- The ReadP type -#ifndef __NHC__ newtype ReadP a = R (forall b . (a -> P b) -> P b) -#else -#define ReadP (ReadPN b) -newtype ReadPN b a = R ((a -> P b) -> P b) -#endif -- Functor, Monad, MonadPlus @@ -216,11 +205,7 @@ pfail = R (\_ -> Fail) -- ^ Symmetric choice. R f1 +++ R f2 = R (\k -> f1 k `mplus` f2 k) -#ifndef __NHC__ (<++) :: ReadP a -> ReadP a -> ReadP a -#else -(<++) :: ReadPN a a -> ReadPN a a -> ReadPN a a -#endif -- ^ Local, exclusive, left-biased choice: If left parser -- locally produces any result at all, then right parser is -- not used. @@ -252,11 +237,7 @@ R f <++ q = discard n = get >> discard (n-1) #endif -#ifndef __NHC__ gather :: ReadP a -> ReadP (String, a) -#else --- gather :: ReadPN (String->P b) a -> ReadPN (String->P b) (String, a) -#endif -- ^ Transforms a parser into one that does the same, but -- in addition returns the exact characters read. -- IMPORTANT NOTE: 'gather' gives a runtime error if its first argument @@ -421,11 +402,7 @@ chainl1 p op = p >>= rest rest (f x y) +++ return x -#ifndef __NHC__ manyTill :: ReadP a -> ReadP end -> ReadP [a] -#else -manyTill :: ReadPN [a] a -> ReadPN [a] end -> ReadPN [a] [a] -#endif -- ^ @manyTill p end@ parses zero or more occurrences of @p@, until @end@ -- succeeds. Returns a list of values returned by @p@. manyTill p end = scan @@ -434,11 +411,7 @@ manyTill p end = scan -- --------------------------------------------------------------------------- -- Converting between ReadP and Read -#ifndef __NHC__ readP_to_S :: ReadP a -> ReadS a -#else -readP_to_S :: ReadPN a a -> ReadS a -#endif -- ^ Converts a parser into a Haskell ReadS-style function. -- This is the main way in which you can \"run\" a 'ReadP' parser: -- the expanded type is diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs index 2608c7baff..4e9c65d685 100644 --- a/libraries/base/Text/Printf.hs +++ b/libraries/base/Text/Printf.hs @@ -152,10 +152,8 @@ instance PrintfArg Int32 where instance PrintfArg Int64 where toUPrintf = uInteger -#ifndef __NHC__ instance PrintfArg Word where toUPrintf = uInteger -#endif instance PrintfArg Word8 where toUPrintf = uInteger diff --git a/libraries/base/Text/Show/Functions.hs b/libraries/base/Text/Show/Functions.hs index 104f9535e7..27cdd60034 100644 --- a/libraries/base/Text/Show/Functions.hs +++ b/libraries/base/Text/Show/Functions.hs @@ -24,16 +24,6 @@ module Text.Show.Functions () where import Prelude -#ifndef __NHC__ instance Show (a -> b) where showsPrec _ _ = showString "<function>" -#else -instance (Show a,Show b) => Show (a->b) where - showsPrec d a = showString "<<function>>" - - showsType a = showChar '(' . showsType value . showString " -> " . - showsType result . showChar ')' - where (value,result) = getTypes undefined - getTypes x = (x,a x) -#endif diff --git a/libraries/base/Unsafe/Coerce.hs b/libraries/base/Unsafe/Coerce.hs index 6a68fb135b..66f64c8a32 100644 --- a/libraries/base/Unsafe/Coerce.hs +++ b/libraries/base/Unsafe/Coerce.hs @@ -63,10 +63,6 @@ unsafeCoerce x = local_id (unsafeCoerce# x) -- give usafeCoerce the same (dangerous) type as unsafeCoerce# #endif -#if defined(__NHC__) -import NonStdUnsafeCoerce (unsafeCoerce) -#endif - #if defined(__HUGS__) import Hugs.IOExts (unsafeCoerce) #endif diff --git a/libraries/base/include/HsBase.h b/libraries/base/include/HsBase.h index b1a62fd131..b70a7295da 100644 --- a/libraries/base/include/HsBase.h +++ b/libraries/base/include/HsBase.h @@ -9,11 +9,7 @@ #ifndef __HSBASE_H__ #define __HSBASE_H__ -#ifdef __NHC__ -# include "Nhc98BaseConfig.h" -#else #include "HsBaseConfig.h" -#endif /* ultra-evil... */ #undef PACKAGE_BUGREPORT |