summaryrefslogtreecommitdiff
path: root/libraries/base/Data
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/Data')
-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
19 files changed, 7 insertions, 134 deletions
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