summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorHerbert Valerio Riedel <hvr@gnu.org>2013-09-15 10:58:00 +0200
committerHerbert Valerio Riedel <hvr@gnu.org>2013-09-17 09:47:55 +0200
commit43ece172e7045d5ba633be6193f3e908eaa81f00 (patch)
treef1e25c06b710a5087173daf5eb01b94ab8517917
parent907cd8c36b6c249dcb8af19f05303e34eb4e8de4 (diff)
downloadhaskell-43ece172e7045d5ba633be6193f3e908eaa81f00.tar.gz
Remove Hugs98 specific code
For rationale. see http://permalink.gmane.org/gmane.comp.lang.haskell.ghc.devel/2349 Signed-off-by: Herbert Valerio Riedel <hvr@gnu.org>
-rw-r--r--libraries/base/Control/Concurrent.hs10
-rw-r--r--libraries/base/Control/Concurrent/MVar.hs8
-rw-r--r--libraries/base/Control/Exception.hs6
-rw-r--r--libraries/base/Control/Exception/Base.hs164
-rw-r--r--libraries/base/Control/Monad/Fix.hs5
-rw-r--r--libraries/base/Control/Monad/ST/Imp.hs16
-rw-r--r--libraries/base/Control/Monad/ST/Lazy/Imp.hs4
-rw-r--r--libraries/base/Data/Bits.hs17
-rw-r--r--libraries/base/Data/Char.hs8
-rw-r--r--libraries/base/Data/Complex.hs10
-rw-r--r--libraries/base/Data/Data.hs3
-rw-r--r--libraries/base/Data/Dynamic.hs11
-rw-r--r--libraries/base/Data/Foldable.hs5
-rw-r--r--libraries/base/Data/IORef.hs12
-rw-r--r--libraries/base/Data/Int.hs4
-rw-r--r--libraries/base/Data/Ix.hs5
-rw-r--r--libraries/base/Data/Maybe.hs2
-rw-r--r--libraries/base/Data/OldTypeable.hs11
-rw-r--r--libraries/base/Data/OldTypeable/Internal.hs6
-rw-r--r--libraries/base/Data/Ratio.hs4
-rw-r--r--libraries/base/Data/STRef.hs8
-rw-r--r--libraries/base/Data/Traversable.hs4
-rw-r--r--libraries/base/Data/Tuple.hs2
-rw-r--r--libraries/base/Data/Typeable/Internal.hs6
-rw-r--r--libraries/base/Data/Version.hs4
-rw-r--r--libraries/base/Data/Word.hs19
-rw-r--r--libraries/base/Foreign/C/Error.hs8
-rw-r--r--libraries/base/Foreign/C/Types.hs4
-rw-r--r--libraries/base/Foreign/ForeignPtr.hs4
-rw-r--r--libraries/base/Foreign/ForeignPtr/Imp.hs13
-rw-r--r--libraries/base/Foreign/ForeignPtr/Safe.hs4
-rw-r--r--libraries/base/Foreign/Marshal/Alloc.hs10
-rw-r--r--libraries/base/Foreign/Ptr.hs4
-rw-r--r--libraries/base/Foreign/StablePtr.hs4
-rw-r--r--libraries/base/Foreign/Storable.hs9
-rw-r--r--libraries/base/GHC/Conc/Sync.lhs2
-rw-r--r--libraries/base/Numeric.hs5
-rw-r--r--libraries/base/Prelude.hs14
-rw-r--r--libraries/base/System/CPUTime.hsc4
-rw-r--r--libraries/base/System/Environment.hs4
-rw-r--r--libraries/base/System/Exit.hs5
-rw-r--r--libraries/base/System/IO.hs21
-rw-r--r--libraries/base/System/IO/Error.hs11
-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/Mem/StableName.hs4
-rw-r--r--libraries/base/System/Mem/Weak.hs5
-rw-r--r--libraries/base/System/Posix/Internals.hs8
-rw-r--r--libraries/base/Text/Read.hs21
-rw-r--r--libraries/base/Text/Read/Lex.hs3
-rw-r--r--libraries/base/Unsafe/Coerce.hs5
52 files changed, 24 insertions, 518 deletions
diff --git a/libraries/base/Control/Concurrent.hs b/libraries/base/Control/Concurrent.hs
index ce08faa600..09674f7064 100644
--- a/libraries/base/Control/Concurrent.hs
+++ b/libraries/base/Control/Concurrent.hs
@@ -138,19 +138,11 @@ import Data.Maybe (Maybe(..))
#endif
#endif
-#ifdef __HUGS__
-import Hugs.ConcBase
-#endif
-
import Control.Concurrent.MVar
import Control.Concurrent.Chan
import Control.Concurrent.QSem
import Control.Concurrent.QSemN
-#ifdef __HUGS__
-type ThreadId = ()
-#endif
-
{- $conc_intro
The concurrency extension for Haskell is described in the paper
@@ -201,8 +193,6 @@ all other Haskell threads in the system, although I\/O operations will
not. With the @-threaded@ option, only foreign calls with the @unsafe@
attribute will block all other threads.
-Using Hugs, all I\/O operations and foreign calls will block all other
-Haskell threads.
-}
-- | fork a thread and call the supplied function when the thread is about
diff --git a/libraries/base/Control/Concurrent/MVar.hs b/libraries/base/Control/Concurrent/MVar.hs
index 63c3837ccd..e8b2ce52b1 100644
--- a/libraries/base/Control/Concurrent/MVar.hs
+++ b/libraries/base/Control/Concurrent/MVar.hs
@@ -141,19 +141,11 @@ module Control.Concurrent.MVar
, modifyMVar
, modifyMVarMasked_
, modifyMVarMasked
-#ifndef __HUGS__
, tryReadMVar
, mkWeakMVar
, addMVarFinalizer
-#endif
) where
-#ifdef __HUGS__
-import Hugs.ConcBase ( MVar, newEmptyMVar, newMVar, takeMVar, putMVar,
- tryTakeMVar, tryPutMVar, isEmptyMVar,
- )
-#endif
-
#ifdef __GLASGOW_HASKELL__
import GHC.MVar ( MVar(..), newEmptyMVar, newMVar, takeMVar, putMVar,
tryTakeMVar, tryPutMVar, isEmptyMVar, readMVar,
diff --git a/libraries/base/Control/Exception.hs b/libraries/base/Control/Exception.hs
index b2b8b61343..36a8efe15b 100644
--- a/libraries/base/Control/Exception.hs
+++ b/libraries/base/Control/Exception.hs
@@ -34,11 +34,7 @@
module Control.Exception (
-- * The Exception type
-#ifdef __HUGS__
- SomeException,
-#else
SomeException(..),
-#endif
Exception(..), -- class
IOException, -- instance Eq, Ord, Show, Typeable, Exception
ArithException(..), -- instance Eq, Ord, Show, Typeable, Exception
@@ -48,7 +44,7 @@ module Control.Exception (
AsyncException(..), -- instance Eq, Ord, Show, Typeable, Exception
asyncExceptionToException, asyncExceptionFromException,
-#if __GLASGOW_HASKELL__ || __HUGS__
+#if __GLASGOW_HASKELL__
NonTermination(..),
NestedAtomically(..),
#endif
diff --git a/libraries/base/Control/Exception/Base.hs b/libraries/base/Control/Exception/Base.hs
index 6ee734842e..a16ce8e9cf 100644
--- a/libraries/base/Control/Exception/Base.hs
+++ b/libraries/base/Control/Exception/Base.hs
@@ -23,11 +23,7 @@
module Control.Exception.Base (
-- * The Exception type
-#ifdef __HUGS__
- SomeException,
-#else
SomeException(..),
-#endif
Exception(..),
IOException,
ArithException(..),
@@ -36,7 +32,7 @@ module Control.Exception.Base (
SomeAsyncException(..), AsyncException(..),
asyncExceptionToException, asyncExceptionFromException,
-#if __GLASGOW_HASKELL__ || __HUGS__
+#ifdef __GLASGOW_HASKELL__
NonTermination(..),
NestedAtomically(..),
#endif
@@ -121,117 +117,10 @@ import GHC.Show
import GHC.Conc.Sync
#endif
-#ifdef __HUGS__
-import Prelude hiding (catch)
-import Hugs.Prelude (ExitCode(..))
-import Hugs.IOExts (unsafePerformIO)
-import Hugs.Exception (SomeException(DynamicException, IOException,
- ArithException, ArrayException, ExitException),
- evaluate, IOException, ArithException, ArrayException)
-import qualified Hugs.Exception
-#endif
-
import Data.Dynamic
import Data.Either
import Data.Maybe
-#ifdef __HUGS__
-class (Typeable e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
-
- toException e = DynamicException (toDyn e) (flip showsPrec e)
- fromException (DynamicException dyn _) = fromDynamic dyn
- fromException _ = Nothing
-
-INSTANCE_TYPEABLE0(SomeException,someExceptionTc,"SomeException")
-INSTANCE_TYPEABLE0(IOException,iOExceptionTc,"IOException")
-INSTANCE_TYPEABLE0(ArithException,arithExceptionTc,"ArithException")
-INSTANCE_TYPEABLE0(ArrayException,arrayExceptionTc,"ArrayException")
-INSTANCE_TYPEABLE0(ExitCode,exitCodeTc,"ExitCode")
-INSTANCE_TYPEABLE0(ErrorCall,errorCallTc,"ErrorCall")
-INSTANCE_TYPEABLE0(AssertionFailed,assertionFailedTc,"AssertionFailed")
-INSTANCE_TYPEABLE0(AsyncException,asyncExceptionTc,"AsyncException")
-INSTANCE_TYPEABLE0(BlockedIndefinitelyOnMVar,blockedIndefinitelyOnMVarTc,"BlockedIndefinitelyOnMVar")
-INSTANCE_TYPEABLE0(BlockedIndefinitelyOnSTM,blockedIndefinitelyOnSTM,"BlockedIndefinitelyOnSTM")
-INSTANCE_TYPEABLE0(Deadlock,deadlockTc,"Deadlock")
-
-instance Exception SomeException where
- toException se = se
- fromException = Just
-
-instance Exception IOException where
- toException = IOException
- fromException (IOException e) = Just e
- fromException _ = Nothing
-
-instance Exception ArrayException where
- toException = ArrayException
- fromException (ArrayException e) = Just e
- fromException _ = Nothing
-
-instance Exception ArithException where
- toException = ArithException
- fromException (ArithException e) = Just e
- fromException _ = Nothing
-
-instance Exception ExitCode where
- toException = ExitException
- fromException (ExitException e) = Just e
- fromException _ = Nothing
-
-data ErrorCall = ErrorCall String
-
-instance Show ErrorCall where
- showsPrec _ (ErrorCall err) = showString err
-
-instance Exception ErrorCall where
- toException (ErrorCall s) = Hugs.Exception.ErrorCall s
- fromException (Hugs.Exception.ErrorCall s) = Just (ErrorCall s)
- fromException _ = Nothing
-
-data BlockedIndefinitelyOnMVar = BlockedIndefinitelyOnMVar
-data BlockedIndefinitelyOnSTM = BlockedIndefinitelyOnSTM
-data Deadlock = Deadlock
-data AssertionFailed = AssertionFailed String
-data AsyncException
- = StackOverflow
- | HeapOverflow
- | ThreadKilled
- | UserInterrupt
- deriving (Eq, Ord)
-
-instance Show BlockedIndefinitelyOnMVar where
- showsPrec _ BlockedIndefinitelyOnMVar = showString "thread blocked indefinitely"
-
-instance Show BlockedIndefinitely where
- showsPrec _ BlockedIndefinitely = showString "thread blocked indefinitely"
-
-instance Show Deadlock where
- showsPrec _ Deadlock = showString "<<deadlock>>"
-
-instance Show AssertionFailed where
- showsPrec _ (AssertionFailed err) = showString err
-
-instance Show AsyncException where
- showsPrec _ StackOverflow = showString "stack overflow"
- showsPrec _ HeapOverflow = showString "heap overflow"
- showsPrec _ ThreadKilled = showString "thread killed"
- showsPrec _ UserInterrupt = showString "user interrupt"
-
-instance Exception BlockedOnDeadMVar
-instance Exception BlockedIndefinitely
-instance Exception Deadlock
-instance Exception AssertionFailed
-instance Exception AsyncException
-
-throw :: Exception e => e -> a
-throw e = Hugs.Exception.throw (toException e)
-
-throwIO :: Exception e => e -> IO a
-throwIO e = Hugs.Exception.throwIO (toException e)
-#endif
-
-----------------------------------------------------------------------------
-- Catching exceptions
@@ -274,11 +163,6 @@ catch :: Exception e
-> IO a
#if __GLASGOW_HASKELL__
catch = catchException
-#elif __HUGS__
-catch m h = Hugs.Exception.catchException m h'
- where h' e = case fromException e of
- Just e' -> h e'
- Nothing -> throwIO e
#endif
-- | The function 'catchJust' is like 'catch', but it takes an extra
@@ -433,7 +317,7 @@ assert False _ = throw (AssertionFailed "")
-----
-#if __GLASGOW_HASKELL__ || __HUGS__
+#if __GLASGOW_HASKELL__
-- |A pattern match failed. The @String@ gives information about the
-- source location of the pattern.
data PatternMatchFail = PatternMatchFail String
@@ -442,14 +326,7 @@ INSTANCE_TYPEABLE0(PatternMatchFail,patternMatchFailTc,"PatternMatchFail")
instance Show PatternMatchFail where
showsPrec _ (PatternMatchFail err) = showString err
-#ifdef __HUGS__
-instance Exception PatternMatchFail where
- toException (PatternMatchFail err) = Hugs.Exception.PatternMatchFail err
- fromException (Hugs.Exception.PatternMatchFail err) = Just (PatternMatchFail err)
- fromException _ = Nothing
-#else
instance Exception PatternMatchFail
-#endif
-----
@@ -464,14 +341,7 @@ INSTANCE_TYPEABLE0(RecSelError,recSelErrorTc,"RecSelError")
instance Show RecSelError where
showsPrec _ (RecSelError err) = showString err
-#ifdef __HUGS__
-instance Exception RecSelError where
- toException (RecSelError err) = Hugs.Exception.RecSelError err
- fromException (Hugs.Exception.RecSelError err) = Just (RecSelError err)
- fromException _ = Nothing
-#else
instance Exception RecSelError
-#endif
-----
@@ -484,14 +354,7 @@ INSTANCE_TYPEABLE0(RecConError,recConErrorTc,"RecConError")
instance Show RecConError where
showsPrec _ (RecConError err) = showString err
-#ifdef __HUGS__
-instance Exception RecConError where
- toException (RecConError err) = Hugs.Exception.RecConError err
- fromException (Hugs.Exception.RecConError err) = Just (RecConError err)
- fromException _ = Nothing
-#else
instance Exception RecConError
-#endif
-----
@@ -506,14 +369,7 @@ INSTANCE_TYPEABLE0(RecUpdError,recUpdErrorTc,"RecUpdError")
instance Show RecUpdError where
showsPrec _ (RecUpdError err) = showString err
-#ifdef __HUGS__
-instance Exception RecUpdError where
- toException (RecUpdError err) = Hugs.Exception.RecUpdError err
- fromException (Hugs.Exception.RecUpdError err) = Just (RecUpdError err)
- fromException _ = Nothing
-#else
instance Exception RecUpdError
-#endif
-----
@@ -526,14 +382,7 @@ INSTANCE_TYPEABLE0(NoMethodError,noMethodErrorTc,"NoMethodError")
instance Show NoMethodError where
showsPrec _ (NoMethodError err) = showString err
-#ifdef __HUGS__
-instance Exception NoMethodError where
- toException (NoMethodError err) = Hugs.Exception.NoMethodError err
- fromException (Hugs.Exception.NoMethodError err) = Just (NoMethodError err)
- fromException _ = Nothing
-#else
instance Exception NoMethodError
-#endif
-----
@@ -547,14 +396,7 @@ INSTANCE_TYPEABLE0(NonTermination,nonTerminationTc,"NonTermination")
instance Show NonTermination where
showsPrec _ NonTermination = showString "<<loop>>"
-#ifdef __HUGS__
-instance Exception NonTermination where
- toException NonTermination = Hugs.Exception.NonTermination
- fromException Hugs.Exception.NonTermination = Just NonTermination
- fromException _ = Nothing
-#else
instance Exception NonTermination
-#endif
-----
@@ -570,7 +412,7 @@ instance Exception NestedAtomically
-----
-#endif /* __GLASGOW_HASKELL__ || __HUGS__ */
+#endif /* __GLASGOW_HASKELL__ */
#ifdef __GLASGOW_HASKELL__
recSelError, recConError, irrefutPatError, runtimeError,
diff --git a/libraries/base/Control/Monad/Fix.hs b/libraries/base/Control/Monad/Fix.hs
index 1508d62653..fb43b91d2d 100644
--- a/libraries/base/Control/Monad/Fix.hs
+++ b/libraries/base/Control/Monad/Fix.hs
@@ -26,14 +26,10 @@ module Control.Monad.Fix (
import Prelude
import System.IO
import Data.Function (fix)
-#ifdef __HUGS__
-import Hugs.Prelude (MonadFix(mfix))
-#endif
#if defined(__GLASGOW_HASKELL__)
import GHC.ST
#endif
-#ifndef __HUGS__
-- | Monads having fixed points with a \'knot-tying\' semantics.
-- Instances of 'MonadFix' should satisfy the following laws:
--
@@ -58,7 +54,6 @@ class (Monad m) => MonadFix m where
-- output fed back as the input. Hence @f@ should not be strict,
-- for then @'mfix' f@ would diverge.
mfix :: (a -> m a) -> m a
-#endif /* !__HUGS__ */
-- Instances of MonadFix for Prelude monads
diff --git a/libraries/base/Control/Monad/ST/Imp.hs b/libraries/base/Control/Monad/ST/Imp.hs
index 9f58af3711..4876028fac 100644
--- a/libraries/base/Control/Monad/ST/Imp.hs
+++ b/libraries/base/Control/Monad/ST/Imp.hs
@@ -45,22 +45,6 @@ import Control.Monad.Fix
import GHC.ST ( ST, runST, fixST, unsafeInterleaveST )
import GHC.Base ( RealWorld )
import GHC.IO ( stToIO, unsafeIOToST, unsafeSTToIO )
-#elif defined(__HUGS__)
-import Data.Typeable
-import Hugs.ST
-import qualified Hugs.LazyST as LazyST
-#endif
-
-#if defined(__HUGS__)
-INSTANCE_TYPEABLE2(ST,sTTc,"ST")
-INSTANCE_TYPEABLE0(RealWorld,realWorldTc,"RealWorld")
-
-fixST :: (a -> ST s a) -> ST s a
-fixST f = LazyST.lazyToStrictST (LazyST.fixST (LazyST.strictToLazyST . f))
-
-unsafeInterleaveST :: ST s a -> ST s a
-unsafeInterleaveST =
- LazyST.lazyToStrictST . LazyST.unsafeInterleaveST . LazyST.strictToLazyST
#endif
#if !defined(__GLASGOW_HASKELL__)
diff --git a/libraries/base/Control/Monad/ST/Lazy/Imp.hs b/libraries/base/Control/Monad/ST/Lazy/Imp.hs
index 702185e90c..d5e4695cbb 100644
--- a/libraries/base/Control/Monad/ST/Lazy/Imp.hs
+++ b/libraries/base/Control/Monad/ST/Lazy/Imp.hs
@@ -49,10 +49,6 @@ import qualified GHC.ST as GHC.ST
import GHC.Base
#endif
-#ifdef __HUGS__
-import Hugs.LazyST
-#endif
-
#ifdef __GLASGOW_HASKELL__
-- | The lazy state-transformer monad.
-- A computation of type @'ST' s a@ transforms an internal state indexed
diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs
index 2385ab9ae5..2d13b8bb22 100644
--- a/libraries/base/Data/Bits.hs
+++ b/libraries/base/Data/Bits.hs
@@ -49,7 +49,7 @@ module Data.Bits (
-- See library document for details on the semantics of the
-- individual operations.
-#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
+#ifdef __GLASGOW_HASKELL__
#include "MachDeps.h"
#endif
@@ -60,10 +60,6 @@ import GHC.Num
import GHC.Base
#endif
-#ifdef __HUGS__
-import Hugs.Bits
-#endif
-
infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR`
infixl 7 .&.
infixl 6 `xor`
@@ -322,17 +318,6 @@ instance Bits Int where
popCount = popCountDefault
-#ifdef __HUGS__
- (.&.) = primAndInt
- (.|.) = primOrInt
- xor = primXorInt
- complement = primComplementInt
- shift = primShiftInt
- bit = primBitInt
- testBit = primTestInt
- bitSize _ = SIZEOF_HSINT*8
-#endif
-
x `rotate` i
| i<0 && x<0 = let left = i+bitSize x in
((x `shift` i) .&. complement ((-1) `shift` left))
diff --git a/libraries/base/Data/Char.hs b/libraries/base/Data/Char.hs
index abf4064100..ad38c12c9b 100644
--- a/libraries/base/Data/Char.hs
+++ b/libraries/base/Data/Char.hs
@@ -64,11 +64,6 @@ import GHC.Num
import GHC.Enum
#endif
-#ifdef __HUGS__
-import Hugs.Prelude (Ix)
-import Hugs.Char
-#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
@@ -127,9 +122,6 @@ generalCategory :: Char -> GeneralCategory
#if defined(__GLASGOW_HASKELL__)
generalCategory c = toEnum $ fromIntegral $ wgencat $ fromIntegral $ ord c
#endif
-#ifdef __HUGS__
-generalCategory c = toEnum (primUniGenCat c)
-#endif
-- derived character classifiers
diff --git a/libraries/base/Data/Complex.hs b/libraries/base/Data/Complex.hs
index b0f549e14f..95bb9a2aff 100644
--- a/libraries/base/Data/Complex.hs
+++ b/libraries/base/Data/Complex.hs
@@ -43,10 +43,6 @@ import Data.Typeable
import Data.Data (Data)
#endif
-#ifdef __HUGS__
-import Hugs.Prelude(Num(fromInt), Fractional(fromDouble))
-#endif
-
infix 6 :+
-- -----------------------------------------------------------------------------
@@ -135,9 +131,6 @@ instance (RealFloat a) => Num (Complex a) where
signum (0:+0) = 0
signum z@(x:+y) = x/r :+ y/r where r = magnitude z
fromInteger n = fromInteger n :+ 0
-#ifdef __HUGS__
- fromInt n = fromInt n :+ 0
-#endif
instance (RealFloat a) => Fractional (Complex a) where
{-# SPECIALISE instance Fractional (Complex Float) #-}
@@ -149,9 +142,6 @@ instance (RealFloat a) => Fractional (Complex a) where
d = x'*x'' + y'*y''
fromRational a = fromRational a :+ 0
-#ifdef __HUGS__
- fromDouble a = fromDouble a :+ 0
-#endif
instance (RealFloat a) => Floating (Complex a) where
{-# SPECIALISE instance Floating (Complex Float) #-}
diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs
index 281388655c..309b704643 100644
--- a/libraries/base/Data/Data.hs
+++ b/libraries/base/Data/Data.hs
@@ -126,9 +126,6 @@ import GHC.ForeignPtr -- So we can give Data instance for ForeignPtr
--import GHC.Conc -- So we can give Data instance for MVar & Co.
import GHC.Arr -- So we can give Data instance for Array
#else
-# ifdef __HUGS__
-import Hugs.Prelude( Ratio(..) )
-# endif
import Foreign.Ptr
import Foreign.ForeignPtr
import Data.Array
diff --git a/libraries/base/Data/Dynamic.hs b/libraries/base/Data/Dynamic.hs
index a3d331ed61..4492dd39bb 100644
--- a/libraries/base/Data/Dynamic.hs
+++ b/libraries/base/Data/Dynamic.hs
@@ -55,13 +55,6 @@ import GHC.Show
import GHC.Exception
#endif
-#ifdef __HUGS__
-import Hugs.Prelude
-import Hugs.IO
-import Hugs.IORef
-import Hugs.IOExts
-#endif
-
#include "Typeable.h"
-------------------------------------------------------------
@@ -80,9 +73,7 @@ import Hugs.IOExts
'Show'ing a value of type 'Dynamic' returns a pretty-printed representation
of the object\'s type; useful for debugging.
-}
-#ifndef __HUGS__
data Dynamic = Dynamic TypeRep Obj
-#endif
INSTANCE_TYPEABLE0(Dynamic,dynamicTc,"Dynamic")
@@ -107,7 +98,7 @@ type Obj = Any
-- when evaluating it, and this will go wrong if the object is really a
-- function. Using Any forces GHC to use
-- a fallback convention for evaluating it that works for all types.
-#elif !defined(__HUGS__)
+#else
data Obj = Obj
#endif
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index bb131e8bf1..3bc521481c 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -71,12 +71,7 @@ import Data.Proxy
#ifdef __GLASGOW_HASKELL__
import GHC.Exts (build)
-#endif
-
-#if defined(__GLASGOW_HASKELL__)
import GHC.Arr
-#elif defined(__HUGS__)
-import Hugs.Array
#endif
-- | Data structures that can be folded.
diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs
index f1dcf97d76..131c73a6d9 100644
--- a/libraries/base/Data/IORef.hs
+++ b/libraries/base/Data/IORef.hs
@@ -37,10 +37,6 @@ module Data.IORef
) where
-#ifdef __HUGS__
-import Hugs.IORef
-#endif
-
#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.STRef
@@ -102,14 +98,8 @@ modifyIORef' ref f = do
-- Use 'atomicModifyIORef'' or 'atomicWriteIORef' to avoid this problem.
--
atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
-#if defined(__GLASGOW_HASKELL__)
+#ifdef __GLASGOW_HASKELL__
atomicModifyIORef = GHC.IORef.atomicModifyIORef
-
-#elif defined(__HUGS__)
-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
#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 874d47ec13..810bd32745 100644
--- a/libraries/base/Data/Int.hs
+++ b/libraries/base/Data/Int.hs
@@ -31,10 +31,6 @@ import GHC.Base ( Int )
import GHC.Int ( Int8, Int16, Int32, Int64 )
#endif
-#ifdef __HUGS__
-import Hugs.Int ( Int8, Int16, Int32, Int64 )
-#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 d916f29f50..2eb42c1394 100644
--- a/libraries/base/Data/Ix.hs
+++ b/libraries/base/Data/Ix.hs
@@ -67,8 +67,3 @@ module Data.Ix
#ifdef __GLASGOW_HASKELL__
import GHC.Arr
#endif
-
-#ifdef __HUGS__
-import Hugs.Prelude( Ix(..) )
-#endif
-
diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs
index a71c2d71b6..05e6a87cb9 100644
--- a/libraries/base/Data/Maybe.hs
+++ b/libraries/base/Data/Maybe.hs
@@ -35,7 +35,6 @@ module Data.Maybe
import GHC.Base
#endif
-#ifndef __HUGS__
-- ---------------------------------------------------------------------------
-- The Maybe type, and instances
@@ -76,7 +75,6 @@ instance Monad Maybe where
maybe :: b -> (a -> b) -> Maybe a -> b
maybe n _ Nothing = n
maybe _ f (Just x) = f x
-#endif /* __HUGS__ */
-- | The 'isJust' function returns 'True' iff its argument is of the
-- form @Just _@.
diff --git a/libraries/base/Data/OldTypeable.hs b/libraries/base/Data/OldTypeable.hs
index 32372a1f41..3690f97473 100644
--- a/libraries/base/Data/OldTypeable.hs
+++ b/libraries/base/Data/OldTypeable.hs
@@ -103,17 +103,6 @@ import GHC.Fingerprint
#endif
-#ifdef __HUGS__
-import Hugs.Prelude ( Key(..), TypeRep(..), TyCon(..), Ratio,
- Handle, Ptr, FunPtr, ForeignPtr, StablePtr )
-import Hugs.IORef ( IORef, newIORef, readIORef, writeIORef )
-import Hugs.IOExts ( unsafePerformIO )
- -- For the Typeable instance
-import Hugs.Array ( Array )
-import Hugs.IOArray
-import Hugs.ConcBase ( MVar )
-#endif
-
#include "OldTypeable.h"
{-# DEPRECATED typeRepKey "TypeRep itself is now an instance of Ord" #-} -- deprecated in 7.2
diff --git a/libraries/base/Data/OldTypeable/Internal.hs b/libraries/base/Data/OldTypeable/Internal.hs
index 5a4faf69c0..305a57f6de 100644
--- a/libraries/base/Data/OldTypeable/Internal.hs
+++ b/libraries/base/Data/OldTypeable/Internal.hs
@@ -485,7 +485,7 @@ INSTANCE_TYPEABLE2((->),funTc,"->")
#endif
INSTANCE_TYPEABLE1(IO,ioTc,"IO")
-#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
+#ifdef __GLASGOW_HASKELL__
-- Types defined in GHC.MVar
INSTANCE_TYPEABLE1(MVar,mvarTc,"MVar" )
#endif
@@ -494,10 +494,6 @@ INSTANCE_TYPEABLE2(Array,arrayTc,"Array")
INSTANCE_TYPEABLE2(IOArray,iOArrayTc,"IOArray")
#ifdef __GLASGOW_HASKELL__
--- Hugs has these too, but their Typeable<n> instances are defined
--- elsewhere to keep this module within Haskell 98.
--- This is important because every invocation of runhugs or ffihugs
--- uses this module via Data.Dynamic.
INSTANCE_TYPEABLE2(ST,stTc,"ST")
INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef")
INSTANCE_TYPEABLE3(STArray,sTArrayTc,"STArray")
diff --git a/libraries/base/Data/Ratio.hs b/libraries/base/Data/Ratio.hs
index d17e0bce3f..6af9088d70 100644
--- a/libraries/base/Data/Ratio.hs
+++ b/libraries/base/Data/Ratio.hs
@@ -31,10 +31,6 @@ import Prelude
import GHC.Real -- The basic defns for Ratio
#endif
-#ifdef __HUGS__
-import Hugs.Prelude(Ratio(..), (%), numerator, denominator)
-#endif
-
-- -----------------------------------------------------------------------------
-- approxRational
diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs
index f8e6e13c58..ecedcc1989 100644
--- a/libraries/base/Data/STRef.hs
+++ b/libraries/base/Data/STRef.hs
@@ -32,14 +32,6 @@ import GHC.ST
import GHC.STRef
#endif
-#ifdef __HUGS__
-import Hugs.ST
-import Data.Typeable
-
-#include "Typeable.h"
-INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef")
-#endif
-
-- | Mutate the contents of an 'STRef'.
--
-- Be warned that 'modifySTRef' does not apply the function strictly. This
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index e34cde4334..9167331815 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -58,10 +58,8 @@ import Data.Foldable (Foldable())
import Data.Monoid (Monoid)
import Data.Proxy
-#if defined(__GLASGOW_HASKELL__)
+#ifdef __GLASGOW_HASKELL__
import GHC.Arr
-#elif defined(__HUGS__)
-import Hugs.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 6d7e2f7f6d..cc7ded374e 100644
--- a/libraries/base/Data/Tuple.hs
+++ b/libraries/base/Data/Tuple.hs
@@ -47,7 +47,6 @@ default () -- Double isn't available yet
-- ---------------------------------------------------------------------------
-- Standard functions over tuples
-#if !defined(__HUGS__)
-- | Extract the first component of a pair.
fst :: (a,b) -> a
fst (x,_) = x
@@ -63,7 +62,6 @@ 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
-- | 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 4d5837b2ff..edfb1bc43c 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -291,7 +291,7 @@ INSTANCE_TYPEABLE1(Ratio,ratioTc,"Ratio")
INSTANCE_TYPEABLE2((->),funTc,"->")
INSTANCE_TYPEABLE1(IO,ioTc,"IO")
-#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
+#ifdef __GLASGOW_HASKELL__
-- Types defined in GHC.MVar
{- INSTANCE_TYPEABLE1(MVar,mvarTc,"MVar" ) -}
#endif
@@ -300,10 +300,6 @@ INSTANCE_TYPEABLE2(Array,arrayTc,"Array")
{- INSTANCE_TYPEABLE2(IOArray,iOArrayTc,"IOArray") -}
#ifdef __GLASGOW_HASKELL__
--- Hugs has these too, but their Typeable<n> instances are defined
--- elsewhere to keep this module within Haskell 98.
--- This is important because every invocation of runhugs or ffihugs
--- uses this module via Data.Dynamic.
INSTANCE_TYPEABLE2(ST,stTc,"ST")
INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef")
INSTANCE_TYPEABLE3(STArray,sTArrayTc,"STArray")
diff --git a/libraries/base/Data/Version.hs b/libraries/base/Data/Version.hs
index 8b59589bcd..742e051c4a 100644
--- a/libraries/base/Data/Version.hs
+++ b/libraries/base/Data/Version.hs
@@ -126,10 +126,8 @@ showVersion (Version branch tags)
-- | A parser for versions in the format produced by 'showVersion'.
--
-#if __GLASGOW_HASKELL__ || __HUGS__
+#ifdef __GLASGOW_HASKELL__
parseVersion :: ReadP Version
-#else
-parseVersion :: ReadP r Version
#endif
parseVersion = do branch <- sepBy1 (liftM read $ munch1 isDigit) (char '.')
tags <- many (char '-' >> munch1 isAlphaNum)
diff --git a/libraries/base/Data/Word.hs b/libraries/base/Data/Word.hs
index c844c4dba9..8f58783379 100644
--- a/libraries/base/Data/Word.hs
+++ b/libraries/base/Data/Word.hs
@@ -34,25 +34,6 @@ module Data.Word
import GHC.Word
#endif
-#ifdef __HUGS__
-import Hugs.Word
-
-byteSwap16 :: Word16 -> Word16
-byteSwap16 w = (w `shift` -8) .|. (w `shift` 8)
-
-byteSwap32 :: Word32 -> Word32
-byteSwap32 w =
- (w `shift` -24) .|. (w `shift` 24)
- .|. ((w `shift` -8) .&. 0xff00) .|. ((w .&. 0xff00) `shift` 8)
-
-byteSwap64 :: Word64 -> Word64
-byteSwap64 w =
- (w `shift` -56) .|. (w `shift` 56)
- .|. ((w `shift` -40) .&. 0xff00) .|. ((w .&. 0xff00) `shift` 40)
- .|. ((w `shift` -24) .&. 0xff0000) .|. ((w .&. 0xff0000) `shift` 24)
- .|. ((w `shift` -8) .&. 0xff000000) .|. ((w .&. 0xff000000) `shift` 8)
-#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 d2f1580ff3..0d10201a36 100644
--- a/libraries/base/Foreign/C/Error.hs
+++ b/libraries/base/Foreign/C/Error.hs
@@ -102,9 +102,6 @@ import GHC.IO.Exception
import GHC.IO.Handle.Types
import GHC.Num
import GHC.Base
-#elif __HUGS__
-import Hugs.Prelude ( Handle, IOError, ioError )
-import System.IO.Unsafe ( unsafePerformIO )
#else
import System.IO ( Handle )
import System.IO.Error ( IOError, ioError )
@@ -112,11 +109,6 @@ import System.IO.Unsafe ( unsafePerformIO )
import Foreign.Storable ( Storable(poke,peek) )
#endif
-#ifdef __HUGS__
-{-# CFILES cbits/PrelIOUtils.c #-}
-#endif
-
-
-- "errno" type
-- ------------
diff --git a/libraries/base/Foreign/C/Types.hs b/libraries/base/Foreign/C/Types.hs
index 5f296d5f65..bde6be51a1 100644
--- a/libraries/base/Foreign/C/Types.hs
+++ b/libraries/base/Foreign/C/Types.hs
@@ -94,10 +94,6 @@ import GHC.Num
import Control.Monad ( liftM )
#endif
-#ifdef __HUGS__
-import Hugs.Ptr ( castPtr )
-#endif
-
#include "HsBaseConfig.h"
#include "CTypes.h"
diff --git a/libraries/base/Foreign/ForeignPtr.hs b/libraries/base/Foreign/ForeignPtr.hs
index b980f502cd..6219adb0eb 100644
--- a/libraries/base/Foreign/ForeignPtr.hs
+++ b/libraries/base/Foreign/ForeignPtr.hs
@@ -22,14 +22,14 @@ module Foreign.ForeignPtr (
-- * Finalised data pointers
ForeignPtr
, FinalizerPtr
-#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
+#ifdef __GLASGOW_HASKELL__
, FinalizerEnvPtr
#endif
-- ** Basic operations
, newForeignPtr
, newForeignPtr_
, addForeignPtrFinalizer
-#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
+#ifdef __GLASGOW_HASKELL__
, newForeignPtrEnv
, addForeignPtrFinalizerEnv
#endif
diff --git a/libraries/base/Foreign/ForeignPtr/Imp.hs b/libraries/base/Foreign/ForeignPtr/Imp.hs
index 19d31b8581..9499fbce8d 100644
--- a/libraries/base/Foreign/ForeignPtr/Imp.hs
+++ b/libraries/base/Foreign/ForeignPtr/Imp.hs
@@ -23,14 +23,14 @@ module Foreign.ForeignPtr.Imp
-- * Finalised data pointers
ForeignPtr
, FinalizerPtr
-#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
+#ifdef __GLASGOW_HASKELL__
, FinalizerEnvPtr
#endif
-- ** Basic operations
, newForeignPtr
, newForeignPtr_
, addForeignPtrFinalizer
-#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
+#ifdef __GLASGOW_HASKELL__
, newForeignPtrEnv
, addForeignPtrFinalizerEnv
#endif
@@ -54,11 +54,6 @@ module Foreign.ForeignPtr.Imp
where
import Foreign.Ptr
-
-#ifdef __HUGS__
-import Hugs.ForeignPtr
-#endif
-
import Foreign.Storable ( Storable(sizeOf) )
#ifdef __GLASGOW_HASKELL__
@@ -117,7 +112,7 @@ withForeignPtr fo io
touchForeignPtr fo
return r
-#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
+#ifdef __GLASGOW_HASKELL__
-- | This variant of 'newForeignPtr' adds a finalizer that expects an
-- environment in addition to the finalized pointer. The environment
-- that will be passed to the finalizer is fixed by the second argument to
@@ -128,7 +123,7 @@ newForeignPtrEnv finalizer env p
= do fObj <- newForeignPtr_ p
addForeignPtrFinalizerEnv finalizer env fObj
return fObj
-#endif /* __HUGS__ */
+#endif
#ifndef __GLASGOW_HASKELL__
mallocForeignPtr :: Storable a => IO (ForeignPtr a)
diff --git a/libraries/base/Foreign/ForeignPtr/Safe.hs b/libraries/base/Foreign/ForeignPtr/Safe.hs
index 4f1907242a..4289a98067 100644
--- a/libraries/base/Foreign/ForeignPtr/Safe.hs
+++ b/libraries/base/Foreign/ForeignPtr/Safe.hs
@@ -23,14 +23,14 @@ module Foreign.ForeignPtr.Safe (
-- * Finalised data pointers
ForeignPtr
, FinalizerPtr
-#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
+#ifdef __GLASGOW_HASKELL__
, FinalizerEnvPtr
#endif
-- ** Basic operations
, newForeignPtr
, newForeignPtr_
, addForeignPtrFinalizer
-#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
+#ifdef __GLASGOW_HASKELL__
, newForeignPtrEnv
, addForeignPtrFinalizerEnv
#endif
diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs
index 6b0bcfb418..d68988d203 100644
--- a/libraries/base/Foreign/Marshal/Alloc.hs
+++ b/libraries/base/Foreign/Marshal/Alloc.hs
@@ -79,13 +79,6 @@ import GHC.Base
import Control.Exception.Base ( bracket )
#endif
-#ifdef __HUGS__
-import Hugs.Prelude ( IOException(IOError),
- IOErrorType(ResourceExhausted) )
-import Hugs.ForeignPtr ( FinalizerPtr )
-#endif
-
-
-- exported functions
-- ------------------
@@ -223,9 +216,6 @@ failWhenNULL name f = do
#if __GLASGOW_HASKELL__
then ioError (IOError Nothing ResourceExhausted name
"out of memory" Nothing Nothing)
-#elif __HUGS__
- then ioError (IOError Nothing ResourceExhausted name
- "out of memory" Nothing)
#else
then ioError (userError (name++": out of memory"))
#endif
diff --git a/libraries/base/Foreign/Ptr.hs b/libraries/base/Foreign/Ptr.hs
index 4632714052..9c8267ed2b 100644
--- a/libraries/base/Foreign/Ptr.hs
+++ b/libraries/base/Foreign/Ptr.hs
@@ -73,10 +73,6 @@ import Data.Bits
import Data.Typeable
import Foreign.Storable ( Storable(..) )
-#ifdef __HUGS__
-import Hugs.Ptr
-#endif
-
#ifdef __GLASGOW_HASKELL__
-- | Release the storage associated with the given 'FunPtr', which
-- must have been obtained from a wrapper stub. This should be called
diff --git a/libraries/base/Foreign/StablePtr.hs b/libraries/base/Foreign/StablePtr.hs
index db27b06063..47610d6439 100644
--- a/libraries/base/Foreign/StablePtr.hs
+++ b/libraries/base/Foreign/StablePtr.hs
@@ -34,10 +34,6 @@ module Foreign.StablePtr
import GHC.Stable
#endif
-#ifdef __HUGS__
-import Hugs.StablePtr
-#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 36e0d26159..d8189a706b 100644
--- a/libraries/base/Foreign/Storable.hs
+++ b/libraries/base/Foreign/Storable.hs
@@ -56,12 +56,6 @@ import Data.Word
import Foreign.StablePtr
#endif
-#ifdef __HUGS__
-import Hugs.Prelude
-import Hugs.Ptr
-import Hugs.Storable
-#endif
-
{- |
The member functions of this class facilitate writing values of
primitive types to raw memory (which may have been allocated with the
@@ -190,9 +184,6 @@ instance Storable (T) where { \
#ifdef __GLASGOW_HASKELL__
STORABLE(Char,SIZEOF_INT32,ALIGNMENT_INT32,
readWideCharOffPtr,writeWideCharOffPtr)
-#elif defined(__HUGS__)
-STORABLE(Char,SIZEOF_HSCHAR,ALIGNMENT_HSCHAR,
- readCharOffPtr,writeCharOffPtr)
#endif
STORABLE(Int,SIZEOF_HSINT,ALIGNMENT_HSINT,
diff --git a/libraries/base/GHC/Conc/Sync.lhs b/libraries/base/GHC/Conc/Sync.lhs
index 135c1fe4ac..7cbc2088b5 100644
--- a/libraries/base/GHC/Conc/Sync.lhs
+++ b/libraries/base/GHC/Conc/Sync.lhs
@@ -150,8 +150,6 @@ a pointer to the thread itself. This means the thread itself can\'t be
garbage collected until you drop the 'ThreadId'.
This misfeature will hopefully be corrected at a later date.
-/Note/: Hugs does not provide any operations on other threads;
-it defines 'ThreadId' as a synonym for ().
-}
instance Show ThreadId where
diff --git a/libraries/base/Numeric.hs b/libraries/base/Numeric.hs
index a990cfb000..3b444e1930 100644
--- a/libraries/base/Numeric.hs
+++ b/libraries/base/Numeric.hs
@@ -71,11 +71,6 @@ import qualified Text.Read.Lex as L
import Data.Char
#endif
-#ifdef __HUGS__
-import Hugs.Prelude
-import Hugs.Numeric
-#endif
-
#ifdef __GLASGOW_HASKELL__
-- -----------------------------------------------------------------------------
-- Reading
diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs
index 8107db448e..fdfa4fb456 100644
--- a/libraries/base/Prelude.hs
+++ b/libraries/base/Prelude.hs
@@ -37,10 +37,6 @@ module Prelude (
-- *** Tuples
fst, snd, curry, uncurry,
-#ifdef __HUGS__
- (:), -- Not legal Haskell 98
-#endif
-
-- ** Basic type classes
Eq((==), (/=)),
Ord(compare, (<), (<=), (>=), (>), max, min),
@@ -138,7 +134,6 @@ module Prelude (
) where
-#ifndef __HUGS__
import Control.Monad
import System.IO
import System.IO.Error
@@ -146,7 +141,6 @@ import Data.List
import Data.Either
import Data.Maybe
import Data.Tuple
-#endif
#ifdef __GLASGOW_HASKELL__
import GHC.Base
@@ -158,13 +152,7 @@ import GHC.Float
import GHC.Show
#endif
-#ifdef __HUGS__
-import Hugs.Prelude
-#endif
-
-#ifndef __HUGS__
infixr 0 $!
-#endif
-- -----------------------------------------------------------------------------
-- Miscellaneous functions
@@ -173,7 +161,7 @@ infixr 0 $!
($!) :: (a -> b) -> a -> b
#ifdef __GLASGOW_HASKELL__
f $! x = let !vx = x in f vx -- see #2273
-#elif !defined(__HUGS__)
+#else
f $! x = x `seq` f x
#endif
diff --git a/libraries/base/System/CPUTime.hsc b/libraries/base/System/CPUTime.hsc
index ec0d792eda..ab8f86ccd6 100644
--- a/libraries/base/System/CPUTime.hsc
+++ b/libraries/base/System/CPUTime.hsc
@@ -28,10 +28,6 @@ import Prelude
import Data.Ratio
-#ifdef __HUGS__
-import Hugs.Time ( getCPUTime, clockTicks )
-#endif
-
#ifdef __GLASGOW_HASKELL__
import Foreign.Safe
import Foreign.C
diff --git a/libraries/base/System/Environment.hs b/libraries/base/System/Environment.hs
index d99d960289..25aa6f4ab7 100644
--- a/libraries/base/System/Environment.hs
+++ b/libraries/base/System/Environment.hs
@@ -52,10 +52,6 @@ import System.Posix.Internals (withFilePath)
#endif
#endif
-#ifdef __HUGS__
-import Hugs.System
-#endif
-
import System.Environment.ExecutablePath
#ifdef mingw32_HOST_OS
diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs
index 1b5b80815e..dbe2ce0ce0 100644
--- a/libraries/base/System/Exit.hs
+++ b/libraries/base/System/Exit.hs
@@ -30,11 +30,6 @@ import GHC.IO
import GHC.IO.Exception
#endif
-#ifdef __HUGS__
-import Hugs.Prelude (ExitCode(..))
-import Control.Exception.Base
-#endif
-
-- ---------------------------------------------------------------------------
-- exitWith
diff --git a/libraries/base/System/IO.hs b/libraries/base/System/IO.hs
index 616884a9e6..d6ed1f52e5 100644
--- a/libraries/base/System/IO.hs
+++ b/libraries/base/System/IO.hs
@@ -105,7 +105,7 @@ module System.IO (
hIsReadable, hIsWritable,
hIsSeekable,
- -- ** Terminal operations (not portable: GHC\/Hugs only)
+ -- ** Terminal operations (not portable: GHC only)
hIsTerminalDevice,
@@ -158,11 +158,9 @@ module System.IO (
hSetBinaryMode,
hPutBuf,
hGetBuf,
-#if !defined(__HUGS__)
hGetBufSome,
hPutBufNonBlocking,
hGetBufNonBlocking,
-#endif
-- * Temporary files
@@ -171,7 +169,6 @@ module System.IO (
openTempFileWithDefaultPermissions,
openBinaryTempFileWithDefaultPermissions,
-#if !defined(__HUGS__)
-- * Unicode encoding\/decoding
-- | A text-mode 'Handle' has an associated 'TextEncoding', which
@@ -201,9 +198,7 @@ module System.IO (
localeEncoding,
char8,
mkTextEncoding,
-#endif
-#if !defined(__HUGS__)
-- * Newline conversion
-- | In Haskell, a newline is always represented by the character
@@ -227,7 +222,6 @@ module System.IO (
Newline(..), nativeNewline,
NewlineMode(..),
noNewlineTranslation, universalNewlineMode, nativeNewlineMode,
-#endif
) where
import Control.Exception.Base
@@ -259,13 +253,6 @@ import GHC.Show
import GHC.MVar
#endif
-#ifdef __HUGS__
-import Hugs.IO
-import Hugs.IOExts
-import Hugs.IORef
-import System.IO.Unsafe ( unsafeInterleaveIO )
-#endif
-
-- -----------------------------------------------------------------------------
-- Standard IO
@@ -421,7 +408,7 @@ withBinaryFile name mode = bracket (openBinaryFile name mode) hClose
-- ---------------------------------------------------------------------------
-- fixIO
-#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
+#if defined(__GLASGOW_HASKELL__)
fixIO :: (a -> IO a) -> IO a
fixIO k = do
m <- newEmptyMVar
@@ -540,10 +527,6 @@ openTempFile' loc tmp_dir template binary mode = do
| last a == pathSeparator = a ++ b
| otherwise = a ++ [pathSeparator] ++ b
-#if __HUGS__
- fdToHandle fd = openFd (fromIntegral fd) False ReadWriteMode binary
-#endif
-
#if defined(__GLASGOW_HASKELL__)
data OpenNewFileResult
= NewFileCreated CInt
diff --git a/libraries/base/System/IO/Error.hs b/libraries/base/System/IO/Error.hs
index 6fec277f56..d76205653e 100644
--- a/libraries/base/System/IO/Error.hs
+++ b/libraries/base/System/IO/Error.hs
@@ -81,13 +81,9 @@ module System.IO.Error (
modifyIOError,
) where
-#ifndef __HUGS__
import Control.Exception.Base
-#endif
-#ifndef __HUGS__
import Data.Either
-#endif
import Data.Maybe
#ifdef __GLASGOW_HASKELL__
@@ -98,10 +94,6 @@ import GHC.IO.Handle.Types
import Text.Show
#endif
-#ifdef __HUGS__
-import Hugs.Prelude(Handle, IOException(..), IOErrorType(..), IO)
-#endif
-
-- | The construct 'tryIOError' @comp@ exposes IO errors which occur within a
-- computation, and which are not fully handled.
--
@@ -325,7 +317,6 @@ annotateIOError ioe loc hdl path =
Nothing `mplus` ys = ys
xs `mplus` _ = xs
-#ifndef __HUGS__
-- | The 'catchIOError' function establishes a handler that receives any
-- 'IOError' raised in the action protected by 'catchIOError'.
-- An 'IOError' is caught by
@@ -348,5 +339,3 @@ annotateIOError ioe loc hdl path =
-- exceptions, use 'Control.Exception.catch' from "Control.Exception".
catchIOError :: IO a -> (IOError -> IO a) -> IO a
catchIOError = catch
-#endif /* !__HUGS__ */
-
diff --git a/libraries/base/System/IO/Unsafe.hs b/libraries/base/System/IO/Unsafe.hs
index 907e9124b5..18a2d423d7 100644
--- a/libraries/base/System/IO/Unsafe.hs
+++ b/libraries/base/System/IO/Unsafe.hs
@@ -31,11 +31,6 @@ import GHC.Exception
import Control.Exception
#endif
-#ifdef __HUGS__
-import Hugs.IOExts (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 8655f89109..d387240f74 100644
--- a/libraries/base/System/Info.hs
+++ b/libraries/base/System/Info.hs
@@ -52,13 +52,6 @@ arch = HOST_ARCH
compilerName = "ghc"
compilerVersionRaw = __GLASGOW_HASKELL__
-#elif defined(__HUGS__)
-#include "platform.h"
-os = HOST_OS
-arch = HOST_ARCH
-compilerName = "hugs"
-compilerVersionRaw = 0 -- ToDo
-
#else
#error Unknown compiler name
#endif
diff --git a/libraries/base/System/Mem.hs b/libraries/base/System/Mem.hs
index c6c24b25d6..8bcf37acec 100644
--- a/libraries/base/System/Mem.hs
+++ b/libraries/base/System/Mem.hs
@@ -24,10 +24,6 @@ module System.Mem (
import Prelude
-#ifdef __HUGS__
-import Hugs.IOExts
-#endif
-
#ifdef __GLASGOW_HASKELL__
-- | Triggers an immediate garbage collection
foreign import ccall {-safe-} "performMajorGC" performGC :: IO ()
diff --git a/libraries/base/System/Mem/StableName.hs b/libraries/base/System/Mem/StableName.hs
index 18fa63d522..374f01cd37 100644
--- a/libraries/base/System/Mem/StableName.hs
+++ b/libraries/base/System/Mem/StableName.hs
@@ -44,10 +44,6 @@ import Prelude
import Data.Typeable
-#ifdef __HUGS__
-import Hugs.Stable
-#endif
-
#ifdef __GLASGOW_HASKELL__
import GHC.IO ( IO(..) )
import GHC.Base ( Int(..), StableName#, makeStableName#
diff --git a/libraries/base/System/Mem/Weak.hs b/libraries/base/System/Mem/Weak.hs
index 9691649668..f35008647c 100644
--- a/libraries/base/System/Mem/Weak.hs
+++ b/libraries/base/System/Mem/Weak.hs
@@ -70,11 +70,6 @@ module System.Mem.Weak (
-- $precise
) where
-#ifdef __HUGS__
-import Hugs.Weak
-import Prelude
-#endif
-
#ifdef __GLASGOW_HASKELL__
import GHC.Weak
#endif
diff --git a/libraries/base/System/Posix/Internals.hs b/libraries/base/System/Posix/Internals.hs
index 106616822e..156ab28e80 100644
--- a/libraries/base/System/Posix/Internals.hs
+++ b/libraries/base/System/Posix/Internals.hs
@@ -53,16 +53,8 @@ import GHC.IO.Device
import {-# SOURCE #-} GHC.IO.Encoding (getFileSystemEncoding)
import qualified GHC.Foreign as GHC
#endif
-#elif __HUGS__
-import Hugs.Prelude (IOException(..), IOErrorType(..))
-import Hugs.IO (IOMode(..))
#endif
-#ifdef __HUGS__
-{-# CFILES cbits/PrelIOUtils.c cbits/consUtils.c #-}
-#endif
-
-
-- ---------------------------------------------------------------------------
-- Debugging the base package
diff --git a/libraries/base/Text/Read.hs b/libraries/base/Text/Read.hs
index 682e9b3732..568c746e2b 100644
--- a/libraries/base/Text/Read.hs
+++ b/libraries/base/Text/Read.hs
@@ -32,7 +32,7 @@ module Text.Read (
readParen,
lex,
-#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
+#ifdef __GLASGOW_HASKELL__
-- * New parsing functions
module Text.ParserCombinators.ReadPrec,
L.Lexeme(..),
@@ -55,28 +55,11 @@ import Data.Either
import Data.Maybe
import Text.ParserCombinators.ReadP as P
#endif
-#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
+#ifdef __GLASGOW_HASKELL__
import Text.ParserCombinators.ReadPrec
import qualified Text.Read.Lex as L
#endif
-#ifdef __HUGS__
--- copied from GHC.Read
-
-lexP :: ReadPrec L.Lexeme
-lexP = lift L.lex
-
-parens :: ReadPrec a -> ReadPrec a
-parens p = optional
- where
- optional = p +++ mandatory
- mandatory = do
- L.Punc "(" <- lexP
- x <- reset optional
- L.Punc ")" <- lexP
- return x
-#endif
-
#ifdef __GLASGOW_HASKELL__
------------------------------------------------------------------------
-- utility functions
diff --git a/libraries/base/Text/Read/Lex.hs b/libraries/base/Text/Read/Lex.hs
index 9b13248fce..78f49134fe 100644
--- a/libraries/base/Text/Read/Lex.hs
+++ b/libraries/base/Text/Read/Lex.hs
@@ -50,9 +50,6 @@ import Prelude hiding ( lex )
import Data.Char( chr, ord, isSpace, isAlpha, isAlphaNum )
import Data.Ratio( Ratio, (%) )
#endif
-#ifdef __HUGS__
-import Hugs.Prelude( Ratio(..) )
-#endif
import Data.Maybe
import Control.Monad
diff --git a/libraries/base/Unsafe/Coerce.hs b/libraries/base/Unsafe/Coerce.hs
index caae4c6e55..11557c34ab 100644
--- a/libraries/base/Unsafe/Coerce.hs
+++ b/libraries/base/Unsafe/Coerce.hs
@@ -63,8 +63,3 @@ unsafeCoerce x = local_id (unsafeCoerce# x)
-- NB: Do not eta-reduce this definition, else the type checker
-- give usafeCoerce the same (dangerous) type as unsafeCoerce#
#endif
-
-#if defined(__HUGS__)
-import Hugs.IOExts (unsafeCoerce)
-#endif
-