summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorHerbert Valerio Riedel <hvr@gnu.org>2013-09-15 23:05:05 +0200
committerHerbert Valerio Riedel <hvr@gnu.org>2013-09-17 09:54:07 +0200
commit0f5eae0232a86ec57d841a83e6929361e2751270 (patch)
tree7cc7b87fce8238cd9ff6b65fb0c37f515191aa6e
parent43ece172e7045d5ba633be6193f3e908eaa81f00 (diff)
downloadhaskell-0f5eae0232a86ec57d841a83e6929361e2751270.tar.gz
Constant-fold `__GLASGOW_HASKELL__` CPP conditionals
Now that HUGS and NHC specific code has been removed, this commit "folds" the now redundant `#if((n)def)`s containing `__GLASGOW_HASKELL__`. This renders `base` officially GHC only. This commit also removes redundant `{-# LANGUAGE CPP #-}`. Signed-off-by: Herbert Valerio Riedel <hvr@gnu.org>
-rw-r--r--libraries/base/Control/Applicative.hs5
-rw-r--r--libraries/base/Control/Category.hs5
-rw-r--r--libraries/base/Control/Concurrent.hs15
-rw-r--r--libraries/base/Control/Concurrent/Chan.hs2
-rw-r--r--libraries/base/Control/Concurrent/MVar.hs9
-rw-r--r--libraries/base/Control/Concurrent/QSem.hs3
-rw-r--r--libraries/base/Control/Concurrent/QSemN.hs3
-rw-r--r--libraries/base/Control/Exception.hs11
-rw-r--r--libraries/base/Control/Exception/Base.hs25
-rw-r--r--libraries/base/Control/Monad.hs7
-rw-r--r--libraries/base/Control/Monad/Fix.hs6
-rw-r--r--libraries/base/Control/Monad/ST/Imp.hs13
-rw-r--r--libraries/base/Control/Monad/ST/Lazy/Imp.hs10
-rw-r--r--libraries/base/Data/Bits.hs74
-rw-r--r--libraries/base/Data/Bool.hs4
-rw-r--r--libraries/base/Data/Char.hs12
-rw-r--r--libraries/base/Data/Complex.hs8
-rw-r--r--libraries/base/Data/Data.hs7
-rw-r--r--libraries/base/Data/Dynamic.hs10
-rw-r--r--libraries/base/Data/Either.hs8
-rw-r--r--libraries/base/Data/Eq.hs5
-rw-r--r--libraries/base/Data/Fixed.hs2
-rw-r--r--libraries/base/Data/Foldable.hs7
-rw-r--r--libraries/base/Data/Functor.hs10
-rw-r--r--libraries/base/Data/IORef.hs8
-rw-r--r--libraries/base/Data/Int.hs4
-rw-r--r--libraries/base/Data/Ix.hs3
-rw-r--r--libraries/base/Data/List.hs33
-rw-r--r--libraries/base/Data/Maybe.hs4
-rw-r--r--libraries/base/Data/Monoid.hs6
-rw-r--r--libraries/base/Data/OldTypeable.hs3
-rw-r--r--libraries/base/Data/OldTypeable/Internal.hs96
-rw-r--r--libraries/base/Data/Ord.hs4
-rw-r--r--libraries/base/Data/Proxy.hs10
-rw-r--r--libraries/base/Data/Ratio.hs3
-rw-r--r--libraries/base/Data/STRef.hs3
-rw-r--r--libraries/base/Data/String.hs5
-rw-r--r--libraries/base/Data/Traversable.hs3
-rw-r--r--libraries/base/Data/Tuple.hs6
-rw-r--r--libraries/base/Data/Typeable.hs3
-rw-r--r--libraries/base/Data/Typeable/Internal.hs20
-rw-r--r--libraries/base/Data/Unique.hs16
-rw-r--r--libraries/base/Data/Version.hs23
-rw-r--r--libraries/base/Data/Word.hs4
-rw-r--r--libraries/base/Debug/Trace.hs21
-rw-r--r--libraries/base/Foreign/C/Error.hs11
-rw-r--r--libraries/base/Foreign/C/String.hs84
-rw-r--r--libraries/base/Foreign/C/Types.hs20
-rw-r--r--libraries/base/Foreign/Concurrent.hs5
-rw-r--r--libraries/base/Foreign/ForeignPtr.hs10
-rw-r--r--libraries/base/Foreign/ForeignPtr/Imp.hs40
-rw-r--r--libraries/base/Foreign/ForeignPtr/Safe.hs10
-rw-r--r--libraries/base/Foreign/ForeignPtr/Unsafe.hs2
-rw-r--r--libraries/base/Foreign/Marshal.hs2
-rw-r--r--libraries/base/Foreign/Marshal/Alloc.hs24
-rw-r--r--libraries/base/Foreign/Marshal/Array.hs17
-rw-r--r--libraries/base/Foreign/Marshal/Error.hs2
-rw-r--r--libraries/base/Foreign/Marshal/Pool.hs11
-rw-r--r--libraries/base/Foreign/Marshal/Safe.hs2
-rw-r--r--libraries/base/Foreign/Marshal/Unsafe.hs6
-rw-r--r--libraries/base/Foreign/Marshal/Utils.hs4
-rw-r--r--libraries/base/Foreign/Ptr.hs32
-rw-r--r--libraries/base/Foreign/StablePtr.hs4
-rw-r--r--libraries/base/Foreign/Storable.hs22
-rw-r--r--libraries/base/GHC/Constants.hs1
-rw-r--r--libraries/base/GHC/Desugar.hs3
-rw-r--r--libraries/base/GHC/Err.lhs2
-rw-r--r--libraries/base/GHC/Foreign.hs2
-rw-r--r--libraries/base/GHC/IO/Device.hs4
-rw-r--r--libraries/base/GHC/IO/Encoding/UTF16.hs3
-rw-r--r--libraries/base/GHC/Read.lhs2
-rw-r--r--libraries/base/Numeric.hs8
-rw-r--r--libraries/base/Prelude.hs6
-rw-r--r--libraries/base/System/CPUTime.hsc8
-rw-r--r--libraries/base/System/Environment.hs7
-rw-r--r--libraries/base/System/Exit.hs5
-rw-r--r--libraries/base/System/IO.hs23
-rw-r--r--libraries/base/System/IO/Error.hs6
-rw-r--r--libraries/base/System/IO/Unsafe.hs4
-rw-r--r--libraries/base/System/Info.hs16
-rw-r--r--libraries/base/System/Mem.hs6
-rw-r--r--libraries/base/System/Mem/StableName.hs5
-rw-r--r--libraries/base/System/Mem/Weak.hs3
-rw-r--r--libraries/base/System/Posix/Internals.hs15
-rw-r--r--libraries/base/System/Posix/Types.hs6
-rw-r--r--libraries/base/System/Timeout.hs12
-rw-r--r--libraries/base/Text/ParserCombinators/ReadP.hs25
-rw-r--r--libraries/base/Text/ParserCombinators/ReadPrec.hs4
-rw-r--r--libraries/base/Text/Printf.hs1
-rw-r--r--libraries/base/Text/Read.hs13
-rw-r--r--libraries/base/Text/Read/Lex.hs8
-rw-r--r--libraries/base/Text/Show.hs14
-rw-r--r--libraries/base/Text/Show/Functions.hs1
-rw-r--r--libraries/base/Unsafe/Coerce.hs5
-rw-r--r--libraries/base/include/CTypes.h160
-rw-r--r--libraries/base/include/HsBase.h4
-rw-r--r--libraries/base/include/OldTypeable.h94
-rw-r--r--libraries/base/include/Typeable.h94
-rw-r--r--libraries/base/tests/IO/hSeek001.hs1
-rw-r--r--libraries/base/tests/qsem001.hs1
-rw-r--r--libraries/base/tests/qsemn001.hs1
101 files changed, 78 insertions, 1342 deletions
diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs
index 9f6b51423f..e1ad80a0f1 100644
--- a/libraries/base/Control/Applicative.hs
+++ b/libraries/base/Control/Applicative.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -59,9 +58,7 @@ import Data.Proxy
import Text.ParserCombinators.ReadP (ReadP)
import Text.ParserCombinators.ReadPrec (ReadPrec)
-#ifdef __GLASGOW_HASKELL__
import GHC.Conc (STM, retry, orElse)
-#endif
infixl 3 <|>
infixl 4 <*>, <*, *>, <**>
@@ -181,7 +178,6 @@ instance Applicative (Lazy.ST s) where
pure = return
(<*>) = ap
-#ifdef __GLASGOW_HASKELL__
instance Applicative STM where
pure = return
(<*>) = ap
@@ -189,7 +185,6 @@ instance Applicative STM where
instance Alternative STM where
empty = retry
(<|>) = orElse
-#endif
instance Applicative ((->) a) where
pure = const
diff --git a/libraries/base/Control/Category.hs b/libraries/base/Control/Category.hs
index 9eaf38f797..76ade1d58f 100644
--- a/libraries/base/Control/Category.hs
+++ b/libraries/base/Control/Category.hs
@@ -20,10 +20,7 @@
module Control.Category where
import qualified Prelude
-
-#ifdef __GLASGOW_HASKELL__
import Data.Type.Equality
-#endif
infixr 9 .
infixr 1 >>>, <<<
@@ -50,11 +47,9 @@ instance Category (->) where
id = Prelude.id
(.) = (Prelude..)
-#ifdef __GLASGOW_HASKELL__
instance Category (:=:) where
id = Refl
Refl . Refl = Refl
-#endif
-- | Right-to-left composition
(<<<) :: Category cat => cat b c -> cat a b -> cat a c
diff --git a/libraries/base/Control/Concurrent.hs b/libraries/base/Control/Concurrent.hs
index 09674f7064..4251ef1ef4 100644
--- a/libraries/base/Control/Concurrent.hs
+++ b/libraries/base/Control/Concurrent.hs
@@ -33,17 +33,13 @@ module Control.Concurrent (
-- * Basic concurrency operations
ThreadId,
-#ifdef __GLASGOW_HASKELL__
myThreadId,
-#endif
forkIO,
-#ifdef __GLASGOW_HASKELL__
forkFinally,
forkIOWithUnmask,
killThread,
throwTo,
-#endif
-- ** Threads with affinity
forkOn,
@@ -61,14 +57,12 @@ module Control.Concurrent (
-- $blocking
-#ifdef __GLASGOW_HASKELL__
-- ** Waiting
threadDelay,
threadWaitRead,
threadWaitWrite,
threadWaitReadSTM,
threadWaitWriteSTM,
-#endif
-- * Communication abstractions
@@ -77,7 +71,6 @@ module Control.Concurrent (
module Control.Concurrent.QSem,
module Control.Concurrent.QSemN,
-#ifdef __GLASGOW_HASKELL__
-- * Bound Threads
-- $boundthreads
rtsSupportsBoundThreads,
@@ -85,7 +78,6 @@ module Control.Concurrent (
isCurrentThreadBound,
runInBoundThread,
runInUnboundThread,
-#endif
-- * Weak references to ThreadIds
mkWeakThreadId,
@@ -117,7 +109,6 @@ import Prelude
import Control.Exception.Base as Exception
-#ifdef __GLASGOW_HASKELL__
import GHC.Exception
import GHC.Conc hiding (threadWaitRead, threadWaitWrite,
threadWaitReadSTM, threadWaitWriteSTM)
@@ -136,7 +127,6 @@ import Foreign.C
import System.IO
import Data.Maybe (Maybe(..))
#endif
-#endif
import Control.Concurrent.MVar
import Control.Concurrent.Chan
@@ -211,7 +201,6 @@ forkFinally action and_then =
mask $ \restore ->
forkIO $ try (restore action) >>= and_then
-#ifdef __GLASGOW_HASKELL__
-- ---------------------------------------------------------------------------
-- Bound Threads
@@ -396,9 +385,7 @@ runInUnboundThread action = do
unsafeResult :: Either SomeException a -> IO a
unsafeResult = either Exception.throwIO return
-#endif /* __GLASGOW_HASKELL__ */
-#ifdef __GLASGOW_HASKELL__
-- ---------------------------------------------------------------------------
-- threadWaitRead/threadWaitWrite
@@ -672,5 +659,3 @@ alternative then it is possible to prevent the thread from being
considered deadlocked by making a 'StablePtr' pointing to it. Don't
forget to release the 'StablePtr' later with 'freeStablePtr'.
-}
-
-#endif /* __GLASGOW_HASKELL__ */
diff --git a/libraries/base/Control/Concurrent/Chan.hs b/libraries/base/Control/Concurrent/Chan.hs
index ca4c17cffb..0efc1728e0 100644
--- a/libraries/base/Control/Concurrent/Chan.hs
+++ b/libraries/base/Control/Concurrent/Chan.hs
@@ -1,8 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
-----------------------------------------------------------------------------
-- |
diff --git a/libraries/base/Control/Concurrent/MVar.hs b/libraries/base/Control/Concurrent/MVar.hs
index e8b2ce52b1..c9ed3e19f1 100644
--- a/libraries/base/Control/Concurrent/MVar.hs
+++ b/libraries/base/Control/Concurrent/MVar.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, UnboxedTuples, MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude, UnboxedTuples, MagicHash #-}
-----------------------------------------------------------------------------
-- |
@@ -146,20 +146,13 @@ module Control.Concurrent.MVar
, addMVarFinalizer
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.MVar ( MVar(..), newEmptyMVar, newMVar, takeMVar, putMVar,
tryTakeMVar, tryPutMVar, isEmptyMVar, readMVar,
tryReadMVar
)
import qualified GHC.MVar
import GHC.Weak
-#endif
-
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
-#else
-import Prelude
-#endif
import Control.Exception.Base
diff --git a/libraries/base/Control/Concurrent/QSem.hs b/libraries/base/Control/Concurrent/QSem.hs
index 1751a291d5..2761ef2bb1 100644
--- a/libraries/base/Control/Concurrent/QSem.hs
+++ b/libraries/base/Control/Concurrent/QSem.hs
@@ -1,8 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, BangPatterns #-}
-#endif
{-# OPTIONS_GHC -funbox-strict-fields #-}
-----------------------------------------------------------------------------
diff --git a/libraries/base/Control/Concurrent/QSemN.hs b/libraries/base/Control/Concurrent/QSemN.hs
index f0db152367..546b8f945e 100644
--- a/libraries/base/Control/Concurrent/QSemN.hs
+++ b/libraries/base/Control/Concurrent/QSemN.hs
@@ -1,8 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, BangPatterns #-}
-#endif
{-# OPTIONS_GHC -funbox-strict-fields #-}
-----------------------------------------------------------------------------
diff --git a/libraries/base/Control/Exception.hs b/libraries/base/Control/Exception.hs
index 36a8efe15b..49a39c0f26 100644
--- a/libraries/base/Control/Exception.hs
+++ b/libraries/base/Control/Exception.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, ExistentialQuantification #-}
+{-# LANGUAGE NoImplicitPrelude, ExistentialQuantification #-}
-----------------------------------------------------------------------------
-- |
@@ -44,11 +44,8 @@ module Control.Exception (
AsyncException(..), -- instance Eq, Ord, Show, Typeable, Exception
asyncExceptionToException, asyncExceptionFromException,
-#if __GLASGOW_HASKELL__
NonTermination(..),
NestedAtomically(..),
-#endif
-
BlockedIndefinitelyOnMVar(..),
BlockedIndefinitelyOnSTM(..),
Deadlock(..),
@@ -63,9 +60,7 @@ module Control.Exception (
throw,
throwIO,
ioError,
-#ifdef __GLASGOW_HASKELL__
throwTo,
-#endif
-- * Catching Exceptions
@@ -136,13 +131,9 @@ module Control.Exception (
import Control.Exception.Base
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.IO (unsafeUnmask)
import Data.Maybe
-#else
-import Prelude hiding (catch)
-#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 a16ce8e9cf..8ff5482690 100644
--- a/libraries/base/Control/Exception/Base.hs
+++ b/libraries/base/Control/Exception/Base.hs
@@ -1,8 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
#include "Typeable.h"
@@ -31,12 +29,8 @@ module Control.Exception.Base (
AssertionFailed(..),
SomeAsyncException(..), AsyncException(..),
asyncExceptionToException, asyncExceptionFromException,
-
-#ifdef __GLASGOW_HASKELL__
NonTermination(..),
NestedAtomically(..),
-#endif
-
BlockedIndefinitelyOnMVar(..),
BlockedIndefinitelyOnSTM(..),
Deadlock(..),
@@ -51,9 +45,7 @@ module Control.Exception.Base (
throwIO,
throw,
ioError,
-#ifdef __GLASGOW_HASKELL__
throwTo,
-#endif
-- * Catching Exceptions
@@ -98,16 +90,13 @@ module Control.Exception.Base (
finally,
-#ifdef __GLASGOW_HASKELL__
-- * Calls for GHC runtime
recSelError, recConError, irrefutPatError, runtimeError,
nonExhaustiveGuardsError, patError, noMethodBindingError,
absentError,
nonTermination, nestedAtomically,
-#endif
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.IO hiding (bracket,finally,onException)
import GHC.IO.Exception
@@ -115,7 +104,6 @@ import GHC.Exception
import GHC.Show
-- import GHC.Exception hiding ( Exception )
import GHC.Conc.Sync
-#endif
import Data.Dynamic
import Data.Either
@@ -161,9 +149,7 @@ catch :: Exception e
=> IO a -- ^ The computation to run
-> (e -> IO a) -- ^ Handler to invoke if an exception is raised
-> IO a
-#if __GLASGOW_HASKELL__
catch = catchException
-#endif
-- | The function 'catchJust' is like 'catch', but it takes an extra
-- argument which is an /exception predicate/, a function which
@@ -309,15 +295,8 @@ bracketOnError before after thing =
a <- before
restore (thing a) `onException` after a
-#if !__GLASGOW_HASKELL__
-assert :: Bool -> a -> a
-assert True x = x
-assert False _ = throw (AssertionFailed "")
-#endif
-
-----
-#if __GLASGOW_HASKELL__
-- |A pattern match failed. The @String@ gives information about the
-- source location of the pattern.
data PatternMatchFail = PatternMatchFail String
@@ -412,9 +391,6 @@ instance Exception NestedAtomically
-----
-#endif /* __GLASGOW_HASKELL__ */
-
-#ifdef __GLASGOW_HASKELL__
recSelError, recConError, irrefutPatError, runtimeError,
nonExhaustiveGuardsError, patError, noMethodBindingError,
absentError
@@ -438,4 +414,3 @@ nonTermination = toException NonTermination
-- GHC's RTS calls this
nestedAtomically :: SomeException
nestedAtomically = toException NestedAtomically
-#endif
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 1aa17381a7..19c9a87bde 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -78,12 +78,9 @@ module Control.Monad
import Data.Maybe
-#ifdef __GLASGOW_HASKELL__
import GHC.List
import GHC.Base
-#endif
-#ifdef __GLASGOW_HASKELL__
infixr 1 =<<
-- -----------------------------------------------------------------------------
@@ -118,8 +115,6 @@ mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
{-# INLINE mapM_ #-}
mapM_ f as = sequence_ (map f as)
-#endif /* __GLASGOW_HASKELL__ */
-
-- -----------------------------------------------------------------------------
-- The MonadPlus class definition
diff --git a/libraries/base/Control/Monad/Fix.hs b/libraries/base/Control/Monad/Fix.hs
index fb43b91d2d..8036fefcd1 100644
--- a/libraries/base/Control/Monad/Fix.hs
+++ b/libraries/base/Control/Monad/Fix.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -26,9 +25,7 @@ module Control.Monad.Fix (
import Prelude
import System.IO
import Data.Function (fix)
-#if defined(__GLASGOW_HASKELL__)
import GHC.ST
-#endif
-- | Monads having fixed points with a \'knot-tying\' semantics.
-- Instances of 'MonadFix' should satisfy the following laws:
@@ -78,8 +75,5 @@ instance MonadFix (Either e) where
where unRight (Right x) = x
unRight (Left _) = error "mfix Either: Left"
-#if defined(__GLASGOW_HASKELL__)
instance MonadFix (ST s) where
mfix = fixST
-#endif
-
diff --git a/libraries/base/Control/Monad/ST/Imp.hs b/libraries/base/Control/Monad/ST/Imp.hs
index 4876028fac..1df8628694 100644
--- a/libraries/base/Control/Monad/ST/Imp.hs
+++ b/libraries/base/Control/Monad/ST/Imp.hs
@@ -35,21 +35,8 @@ module Control.Monad.ST.Imp (
unsafeSTToIO
) where
-#if !defined(__GLASGOW_HASKELL__)
-import Control.Monad.Fix
-#endif
-
#include "Typeable.h"
-#if defined(__GLASGOW_HASKELL__)
import GHC.ST ( ST, runST, fixST, unsafeInterleaveST )
import GHC.Base ( RealWorld )
import GHC.IO ( stToIO, unsafeIOToST, unsafeSTToIO )
-#endif
-
-#if !defined(__GLASGOW_HASKELL__)
-instance MonadFix (ST s) where
- mfix = fixST
-#endif
-
-
diff --git a/libraries/base/Control/Monad/ST/Lazy/Imp.hs b/libraries/base/Control/Monad/ST/Lazy/Imp.hs
index d5e4695cbb..40f5267290 100644
--- a/libraries/base/Control/Monad/ST/Lazy/Imp.hs
+++ b/libraries/base/Control/Monad/ST/Lazy/Imp.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, MagicHash, UnboxedTuples, RankNTypes #-}
+{-# LANGUAGE MagicHash, UnboxedTuples, RankNTypes #-}
{-# OPTIONS_HADDOCK hide #-}
-----------------------------------------------------------------------------
@@ -44,12 +44,9 @@ import Control.Monad.Fix
import qualified Control.Monad.ST.Safe as ST
import qualified Control.Monad.ST.Unsafe as ST
-#ifdef __GLASGOW_HASKELL__
import qualified GHC.ST as GHC.ST
import GHC.Base
-#endif
-#ifdef __GLASGOW_HASKELL__
-- | The lazy state-transformer monad.
-- A computation of type @'ST' s a@ transforms an internal state indexed
-- by @s@, and returns a value of type @a@.
@@ -107,7 +104,6 @@ fixST m = ST (\ s ->
(r,s') = m_r s
in
(r,s'))
-#endif
instance MonadFix (ST s) where
mfix = fixST
@@ -115,7 +111,6 @@ instance MonadFix (ST s) where
-- ---------------------------------------------------------------------------
-- Strict <--> Lazy
-#ifdef __GLASGOW_HASKELL__
{-|
Convert a strict 'ST' computation into a lazy one. The strict state
thread passed to 'strictToLazyST' is not performed until the result of
@@ -136,7 +131,6 @@ Convert a lazy 'ST' computation into a strict one.
lazyToStrictST :: ST s a -> ST.ST s a
lazyToStrictST (ST m) = GHC.ST.ST $ \s ->
case (m (S# s)) of (a, S# s') -> (# s', a #)
-#endif
-- | A monad transformer embedding lazy state transformers in the 'IO'
-- monad. The 'RealWorld' parameter indicates that the internal state
@@ -148,10 +142,8 @@ stToIO = ST.stToIO . lazyToStrictST
-- ---------------------------------------------------------------------------
-- Strict <--> Lazy
-#ifdef __GLASGOW_HASKELL__
unsafeInterleaveST :: ST s a -> ST s a
unsafeInterleaveST = strictToLazyST . ST.unsafeInterleaveST . lazyToStrictST
-#endif
unsafeIOToST :: IO a -> ST s a
unsafeIOToST = strictToLazyST . ST.unsafeIOToST
diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs
index 2d13b8bb22..e2eb3fe0cf 100644
--- a/libraries/base/Data/Bits.hs
+++ b/libraries/base/Data/Bits.hs
@@ -49,16 +49,12 @@ module Data.Bits (
-- See library document for details on the semantics of the
-- individual operations.
-#ifdef __GLASGOW_HASKELL__
#include "MachDeps.h"
-#endif
-#ifdef __GLASGOW_HASKELL__
import Data.Maybe
import GHC.Enum
import GHC.Num
import GHC.Base
-#endif
infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR`
infixl 7 .&.
@@ -280,7 +276,6 @@ instance Bits Int where
{-# INLINE bit #-}
{-# INLINE testBit #-}
-#ifdef __GLASGOW_HASKELL__
bit = bitDefault
testBit = testBitDefault
@@ -314,26 +309,11 @@ instance Bits Int where
popCount (I# x#) = I# (word2Int# (popCnt# (int2Word# x#)))
-#else /* !__GLASGOW_HASKELL__ */
-
- popCount = popCountDefault
-
- x `rotate` i
- | i<0 && x<0 = let left = i+bitSize x in
- ((x `shift` i) .&. complement ((-1) `shift` left))
- .|. (x `shift` left)
- | i<0 = (x `shift` i) .|. (x `shift` (i+bitSize x))
- | i==0 = x
- | i>0 = (x `shift` i) .|. (x `shift` (i-bitSize x))
-
-#endif /* !__GLASGOW_HASKELL__ */
-
isSigned _ = True
instance FiniteBits Int where
finiteBitSize _ = WORD_SIZE_IN_BITS
-#if defined(__GLASGOW_HASKELL__)
instance Bits Word where
{-# INLINE shift #-}
{-# INLINE bit #-}
@@ -366,10 +346,8 @@ instance Bits Word where
instance FiniteBits Word where
finiteBitSize _ = WORD_SIZE_IN_BITS
-#endif
instance Bits Integer where
-#if defined(__GLASGOW_HASKELL__)
(.&.) = andInteger
(.|.) = orInteger
xor = xorInteger
@@ -377,26 +355,6 @@ instance Bits Integer where
shift x i@(I# i#) | i >= 0 = shiftLInteger x i#
| otherwise = shiftRInteger x (negateInt# i#)
testBit x (I# i) = testBitInteger x i
-#else
- -- reduce bitwise binary operations to special cases we can handle
-
- x .&. y | x<0 && y<0 = complement (complement x `posOr` complement y)
- | otherwise = x `posAnd` y
-
- x .|. y | x<0 || y<0 = complement (complement x `posAnd` complement y)
- | otherwise = x `posOr` y
-
- x `xor` y | x<0 && y<0 = complement x `posXOr` complement y
- | x<0 = complement (complement x `posXOr` y)
- | y<0 = complement (x `posXOr` complement y)
- | otherwise = x `posXOr` y
-
- -- assuming infinite 2's-complement arithmetic
- complement a = -1 - a
- shift x i | i >= 0 = x * 2^i
- | otherwise = x `div` 2^(-i)
- testBit = testBitDefault
-#endif
bit = bitDefault
popCount = popCountDefault
@@ -407,38 +365,6 @@ instance Bits Integer where
bitSize _ = error "Data.Bits.bitSize(Integer)"
isSigned _ = True
-#if !defined(__GLASGOW_HASKELL__)
--- Crude implementation of bitwise operations on Integers: convert them
--- to finite lists of Ints (least significant first), zip and convert
--- back again.
-
--- posAnd requires at least one argument non-negative
--- posOr and posXOr require both arguments non-negative
-
-posAnd, posOr, posXOr :: Integer -> Integer -> Integer
-posAnd x y = fromInts $ zipWith (.&.) (toInts x) (toInts y)
-posOr x y = fromInts $ longZipWith (.|.) (toInts x) (toInts y)
-posXOr x y = fromInts $ longZipWith xor (toInts x) (toInts y)
-
-longZipWith :: (a -> a -> a) -> [a] -> [a] -> [a]
-longZipWith f xs [] = xs
-longZipWith f [] ys = ys
-longZipWith f (x:xs) (y:ys) = f x y:longZipWith f xs ys
-
-toInts :: Integer -> [Int]
-toInts n
- | n == 0 = []
- | otherwise = mkInt (n `mod` numInts):toInts (n `div` numInts)
- where mkInt n | n > toInteger(maxBound::Int) = fromInteger (n-numInts)
- | otherwise = fromInteger n
-
-fromInts :: [Int] -> Integer
-fromInts = foldr catInt 0
- where catInt d n = (if d<0 then n+1 else n)*numInts + toInteger d
-
-numInts = toInteger (maxBound::Int) - toInteger (minBound::Int) + 1
-#endif /* !__GLASGOW_HASKELL__ */
-
{- Note [Constant folding for rotate]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The INLINE on the Int instance of rotate enables it to be constant
diff --git a/libraries/base/Data/Bool.hs b/libraries/base/Data/Bool.hs
index 9f6ce04ad0..0dd8198dc2 100644
--- a/libraries/base/Data/Bool.hs
+++ b/libraries/base/Data/Bool.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -26,9 +26,7 @@ module Data.Bool (
bool,
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
-#endif
-- | Case analysis for the 'Bool' type.
-- @bool a b p@ evaluates to @a@ when @p@ is @False@, and evaluates to @b@
diff --git a/libraries/base/Data/Char.hs b/libraries/base/Data/Char.hs
index ad38c12c9b..aa4a59485c 100644
--- a/libraries/base/Data/Char.hs
+++ b/libraries/base/Data/Char.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -52,7 +52,6 @@ module Data.Char
, readLitChar
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Arr (Ix)
import GHC.Char
@@ -62,7 +61,6 @@ import GHC.Read (Read, readLitChar, lexLitChar)
import GHC.Unicode
import GHC.Num
import GHC.Enum
-#endif
-- | Convert a single digit 'Char' to the corresponding 'Int'.
-- This function fails unless its argument satisfies 'isHexDigit',
@@ -75,12 +73,6 @@ digitToInt c
| c >= 'A' && c <= 'F' = ord c - ord 'A' + 10
| otherwise = error ("Char.digitToInt: not a digit " ++ show c) -- sigh
-#ifndef __GLASGOW_HASKELL__
-isAsciiUpper, isAsciiLower :: Char -> Bool
-isAsciiLower c = c >= 'a' && c <= 'z'
-isAsciiUpper c = c >= 'A' && c <= 'Z'
-#endif
-
-- | Unicode General Categories (column 2 of the UnicodeData table)
-- in the order they are listed in the Unicode standard.
@@ -119,9 +111,7 @@ data GeneralCategory
-- | The Unicode general category of the character.
generalCategory :: Char -> GeneralCategory
-#if defined(__GLASGOW_HASKELL__)
generalCategory c = toEnum $ fromIntegral $ wgencat $ fromIntegral $ ord c
-#endif
-- derived character classifiers
diff --git a/libraries/base/Data/Complex.hs b/libraries/base/Data/Complex.hs
index 95bb9a2aff..c852df9276 100644
--- a/libraries/base/Data/Complex.hs
+++ b/libraries/base/Data/Complex.hs
@@ -1,8 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, DeriveDataTypeable #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE StandaloneDeriving #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -39,9 +37,7 @@ module Data.Complex
import Prelude
import Data.Typeable
-#ifdef __GLASGOW_HASKELL__
import Data.Data (Data)
-#endif
infix 6 :+
@@ -56,11 +52,7 @@ infix 6 :+
data Complex a
= !a :+ !a -- ^ forms a complex number from its real and imaginary
-- rectangular components.
-# if __GLASGOW_HASKELL__
deriving (Eq, Show, Read, Data)
-# else
- deriving (Eq, Show, Read)
-# endif
-- -----------------------------------------------------------------------------
-- Functions over Complex
diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs
index 309b704643..762d96b32f 100644
--- a/libraries/base/Data/Data.hs
+++ b/libraries/base/Data/Data.hs
@@ -116,7 +116,6 @@ import Control.Monad
-- Imports for the instances
import Data.Int -- So we can give Data instance for Int8, ...
import Data.Word -- So we can give Data instance for Word8, ...
-#ifdef __GLASGOW_HASKELL__
import GHC.Real( Ratio(..) ) -- So we can give Data instance for Ratio
--import GHC.IOBase -- So we can give Data instance for IO, Handle
import GHC.Ptr -- So we can give Data instance for Ptr
@@ -125,12 +124,6 @@ import GHC.ForeignPtr -- So we can give Data instance for ForeignPtr
--import GHC.ST -- So we can give Data instance for ST
--import GHC.Conc -- So we can give Data instance for MVar & Co.
import GHC.Arr -- So we can give Data instance for Array
-#else
-import Foreign.Ptr
-import Foreign.ForeignPtr
-import Data.Array
-import Data.Proxy
-#endif
#include "Typeable.h"
diff --git a/libraries/base/Data/Dynamic.hs b/libraries/base/Data/Dynamic.hs
index 4492dd39bb..ccf78f35d0 100644
--- a/libraries/base/Data/Dynamic.hs
+++ b/libraries/base/Data/Dynamic.hs
@@ -1,8 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -49,11 +47,9 @@ import Data.Typeable
import Data.Maybe
import Unsafe.Coerce
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Show
import GHC.Exception
-#endif
#include "Typeable.h"
@@ -84,12 +80,9 @@ instance Show Dynamic where
showsPrec 0 t .
showString ">>"
-#ifdef __GLASGOW_HASKELL__
-- here so that it isn't an orphan:
instance Exception Dynamic
-#endif
-#ifdef __GLASGOW_HASKELL__
type Obj = Any
-- Use GHC's primitive 'Any' type to hold the dynamically typed value.
--
@@ -98,9 +91,6 @@ 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.
-#else
-data Obj = Obj
-#endif
-- | Converts an arbitrary value into an object of type 'Dynamic'.
--
diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs
index 166c4f2741..ac8656e263 100644
--- a/libraries/base/Data/Either.hs
+++ b/libraries/base/Data/Either.hs
@@ -1,8 +1,6 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
-#ifdef __GLASGOW_HASKELL__
+{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -30,15 +28,12 @@ module Data.Either (
#include "Typeable.h"
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Show
import GHC.Read
-#endif
import Data.Typeable
-#ifdef __GLASGOW_HASKELL__
{-
-- just for testing
import Test.QuickCheck
@@ -72,7 +67,6 @@ instance Monad (Either e) where
either :: (a -> c) -> (b -> c) -> Either a b -> c
either f _ (Left x) = f x
either _ g (Right y) = g y
-#endif /* __GLASGOW_HASKELL__ */
INSTANCE_TYPEABLE2(Either,eitherTc,"Either")
diff --git a/libraries/base/Data/Eq.hs b/libraries/base/Data/Eq.hs
index 0c45c78e1d..fe487bf454 100644
--- a/libraries/base/Data/Eq.hs
+++ b/libraries/base/Data/Eq.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -19,7 +19,4 @@ module Data.Eq (
Eq(..),
) where
-#if __GLASGOW_HASKELL__
import GHC.Base
-#endif
-
diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs
index 6ea9bcdfbe..d027354151 100644
--- a/libraries/base/Data/Fixed.hs
+++ b/libraries/base/Data/Fixed.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, ScopedTypeVariables, PatternGuards #-}
+{-# LANGUAGE ScopedTypeVariables, PatternGuards #-}
{-# OPTIONS -Wall -fno-warn-unused-binds #-}
{-# LANGUAGE DeriveDataTypeable #-}
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index 3bc521481c..de6c0562cb 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -69,10 +68,8 @@ import Data.Maybe (fromMaybe, listToMaybe)
import Data.Monoid
import Data.Proxy
-#ifdef __GLASGOW_HASKELL__
import GHC.Exts (build)
import GHC.Arr
-#endif
-- | Data structures that can be folded.
--
@@ -260,11 +257,7 @@ msum = foldr mplus mzero
-- | List of elements of a structure.
toList :: Foldable t => t a -> [a]
{-# INLINE toList #-}
-#ifdef __GLASGOW_HASKELL__
toList t = build (\ c n -> foldr c n t)
-#else
-toList = foldr (:) []
-#endif
-- | The concatenation of all the elements of a container of lists.
concat :: Foldable t => t [a] -> [a]
diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs
index bac14641c8..a578bdd231 100644
--- a/libraries/base/Data/Functor.hs
+++ b/libraries/base/Data/Functor.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -24,16 +23,7 @@ module Data.Functor
) where
import Control.Monad
-#ifdef __GLASGOW_HASKELL__
import GHC.Base (Functor(..))
-#endif
-
-#ifndef __GLASGOW_HASKELL__
-infixl 4 <$
-
-(<$) :: Functor f => a -> f b -> f a
-(<$) = fmap . const
-#endif
infixl 4 <$>
diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs
index 131c73a6d9..f4eb9ec143 100644
--- a/libraries/base/Data/IORef.hs
+++ b/libraries/base/Data/IORef.hs
@@ -28,7 +28,7 @@ module Data.IORef
atomicModifyIORef',
atomicWriteIORef,
-#if !defined(__PARALLEL_HASKELL__) && defined(__GLASGOW_HASKELL__)
+#if !defined(__PARALLEL_HASKELL__)
mkWeakIORef,
#endif
-- ** Memory Model
@@ -37,7 +37,6 @@ module Data.IORef
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.STRef
import GHC.IORef hiding (atomicModifyIORef)
@@ -45,9 +44,8 @@ import qualified GHC.IORef
#if !defined(__PARALLEL_HASKELL__)
import GHC.Weak
#endif
-#endif /* __GLASGOW_HASKELL__ */
-#if defined(__GLASGOW_HASKELL__) && !defined(__PARALLEL_HASKELL__)
+#if !defined(__PARALLEL_HASKELL__)
-- |Make a 'Weak' pointer to an 'IORef', using the second argument as a finalizer
-- to run when 'IORef' is garbage-collected
mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a))
@@ -98,9 +96,7 @@ modifyIORef' ref f = do
-- Use 'atomicModifyIORef'' or 'atomicWriteIORef' to avoid this problem.
--
atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
-#ifdef __GLASGOW_HASKELL__
atomicModifyIORef = GHC.IORef.atomicModifyIORef
-#endif
-- | Strict version of 'atomicModifyIORef'. This forces both the value stored
-- in the 'IORef' as well as the value returned.
diff --git a/libraries/base/Data/Int.hs b/libraries/base/Data/Int.hs
index 810bd32745..8ca822142c 100644
--- a/libraries/base/Data/Int.hs
+++ b/libraries/base/Data/Int.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -26,10 +26,8 @@ module Data.Int
-- $notes
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base ( Int )
import GHC.Int ( Int8, Int16, Int32, Int64 )
-#endif
{- $notes
diff --git a/libraries/base/Data/Ix.hs b/libraries/base/Data/Ix.hs
index 2eb42c1394..bdfea60b73 100644
--- a/libraries/base/Data/Ix.hs
+++ b/libraries/base/Data/Ix.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -64,6 +63,4 @@ module Data.Ix
-- import Prelude
-#ifdef __GLASGOW_HASKELL__
import GHC.Arr
-#endif
diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs
index e7e8602cba..7998976baa 100644
--- a/libraries/base/Data/List.hs
+++ b/libraries/base/Data/List.hs
@@ -208,12 +208,10 @@ module Data.List
import Data.Maybe
import Data.Char ( isSpace )
-#ifdef __GLASGOW_HASKELL__
import GHC.Num
import GHC.Real
import GHC.List
import GHC.Base
-#endif
infix 5 \\ -- comment to fool cpp
@@ -270,8 +268,7 @@ findIndex p = listToMaybe . findIndices p
-- | The 'findIndices' function extends 'findIndex', by returning the
-- indices of all elements satisfying the predicate, in ascending order.
findIndices :: (a -> Bool) -> [a] -> [Int]
-
-#if defined(USE_REPORT_PRELUDE) || !defined(__GLASGOW_HASKELL__)
+#ifdef USE_REPORT_PRELUDE
findIndices p xs = [ i | (x,i) <- zip xs [0..], p x]
#else
-- Efficient definition
@@ -516,8 +513,6 @@ insertBy cmp x ys@(y:ys')
GT -> y : insertBy cmp x ys'
_ -> x : ys
-#ifdef __GLASGOW_HASKELL__
-
-- | 'maximum' returns the maximum value from a list,
-- which must be non-empty, finite, and of an ordered type.
-- It is a special case of 'Data.List.maximumBy', which allows the
@@ -557,8 +552,6 @@ strictMinimum :: (Ord a) => [a] -> a
strictMinimum [] = errorEmptyList "minimum"
strictMinimum xs = foldl1' min xs
-#endif /* __GLASGOW_HASKELL__ */
-
-- | The 'maximumBy' function takes a comparison function and a list
-- and returns the greatest element of the list by the comparison function.
-- The list must be finite and non-empty.
@@ -996,29 +989,21 @@ unfoldr f b =
-- | A strict version of 'foldl'.
foldl' :: (b -> a -> b) -> b -> [a] -> b
-#ifdef __GLASGOW_HASKELL__
foldl' f z0 xs0 = lgo z0 xs0
where lgo z [] = z
lgo z (x:xs) = let z' = f z x in z' `seq` lgo z' xs
-#else
-foldl' f a [] = a
-foldl' f a (x:xs) = let a' = f a x in a' `seq` foldl' f a' xs
-#endif
-#ifdef __GLASGOW_HASKELL__
-- | 'foldl1' is a variant of 'foldl' that has no starting value argument,
-- and thus must be applied to non-empty lists.
foldl1 :: (a -> a -> a) -> [a] -> a
foldl1 f (x:xs) = foldl f x xs
foldl1 _ [] = errorEmptyList "foldl1"
-#endif /* __GLASGOW_HASKELL__ */
-- | A strict version of 'foldl1'
foldl1' :: (a -> a -> a) -> [a] -> a
foldl1' f (x:xs) = foldl' f x xs
foldl1' _ [] = errorEmptyList "foldl1'"
-#ifdef __GLASGOW_HASKELL__
-- -----------------------------------------------------------------------------
-- List sum and product
@@ -1056,7 +1041,6 @@ product l = prod l 1
-- characters. The resulting strings do not contain newlines.
lines :: String -> [String]
lines "" = []
-#ifdef __GLASGOW_HASKELL__
-- Somehow GHC doesn't detect the selector thunks in the below code,
-- so s' keeps a reference to the first line via the pair and we have
-- a space leak (cf. #4334).
@@ -1067,12 +1051,6 @@ lines s = cons (case break (== '\n') s of
_:s'' -> lines s''))
where
cons ~(h, t) = h : t
-#else
-lines s = let (l, s') = break (== '\n') s
- in l : case s' of
- [] -> []
- (_:s'') -> lines s''
-#endif
-- | 'unlines' is an inverse operation to 'lines'.
-- It joins lines, after appending a terminating newline to each.
@@ -1108,12 +1086,3 @@ unwords [] = ""
unwords [w] = w
unwords (w:ws) = w ++ ' ' : unwords ws
#endif
-
-#else /* !__GLASGOW_HASKELL__ */
-
-errorEmptyList :: String -> a
-errorEmptyList fun =
- error ("Prelude." ++ fun ++ ": empty list")
-
-#endif /* !__GLASGOW_HASKELL__ */
-
diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs
index 05e6a87cb9..245e30753d 100644
--- a/libraries/base/Data/Maybe.hs
+++ b/libraries/base/Data/Maybe.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -31,9 +31,7 @@ module Data.Maybe
, mapMaybe
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
-#endif
-- ---------------------------------------------------------------------------
-- The Maybe type, and instances
diff --git a/libraries/base/Data/Monoid.hs b/libraries/base/Data/Monoid.hs
index 90bd437b10..1a17a323dc 100644
--- a/libraries/base/Data/Monoid.hs
+++ b/libraries/base/Data/Monoid.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -36,16 +36,12 @@ module Data.Monoid (
) where
-- Push down the module in the dependency hierarchy.
-#if defined(__GLASGOW_HASKELL__)
import GHC.Base hiding (Any)
import GHC.Enum
import GHC.Num
import GHC.Read
import GHC.Show
import Data.Maybe
-#else
-import Prelude
-#endif
{-
-- just for testing
diff --git a/libraries/base/Data/OldTypeable.hs b/libraries/base/Data/OldTypeable.hs
index 3690f97473..ab936c4216 100644
--- a/libraries/base/Data/OldTypeable.hs
+++ b/libraries/base/Data/OldTypeable.hs
@@ -95,14 +95,11 @@ import Data.OldTypeable.Internal hiding (mkTyCon)
import Unsafe.Coerce
import Data.Maybe
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Fingerprint.Type
import GHC.Fingerprint
-#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 305a57f6de..9718237fd1 100644
--- a/libraries/base/Data/OldTypeable/Internal.hs
+++ b/libraries/base/Data/OldTypeable/Internal.hs
@@ -17,10 +17,9 @@
, OverlappingInstances
, ScopedTypeVariables
, FlexibleInstances
- , MagicHash #-}
-#ifdef __GLASGOW_HASKELL__
-{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
+ , MagicHash
+ , DeriveDataTypeable
+ , StandaloneDeriving #-}
module Data.OldTypeable.Internal {-# DEPRECATED "Use Data.Typeable.Internal instead" #-} ( -- deprecated in 7.8
TypeRep(..),
@@ -51,9 +50,7 @@ module Data.OldTypeable.Internal {-# DEPRECATED "Use Data.Typeable.Internal inst
typeRepArgs,
showsTypeRep,
tyConString,
-#if defined(__GLASGOW_HASKELL__)
listTc, funTc
-#endif
) where
import GHC.Base
@@ -223,7 +220,6 @@ class Typeable a where
class Typeable1 t where
typeOf1 :: t a -> TypeRep
-#ifdef __GLASGOW_HASKELL__
-- | For defining a 'Typeable' instance from any 'Typeable1' instance.
typeOfDefault :: forall t a. (Typeable1 t, Typeable a) => t a -> TypeRep
typeOfDefault = \_ -> rep
@@ -231,20 +227,11 @@ typeOfDefault = \_ -> rep
rep = typeOf1 (undefined :: t a) `mkAppTy`
typeOf (undefined :: a)
-- Note [Memoising typeOf]
-#else
--- | For defining a 'Typeable' instance from any 'Typeable1' instance.
-typeOfDefault :: (Typeable1 t, Typeable a) => t a -> TypeRep
-typeOfDefault x = typeOf1 x `mkAppTy` typeOf (argType x)
- where
- argType :: t a -> a
- argType = undefined
-#endif
-- | Variant for binary type constructors
class Typeable2 t where
typeOf2 :: t a b -> TypeRep
-#ifdef __GLASGOW_HASKELL__
-- | For defining a 'Typeable1' instance from any 'Typeable2' instance.
typeOf1Default :: forall t a b. (Typeable2 t, Typeable a) => t a b -> TypeRep
typeOf1Default = \_ -> rep
@@ -252,20 +239,11 @@ typeOf1Default = \_ -> rep
rep = typeOf2 (undefined :: t a b) `mkAppTy`
typeOf (undefined :: a)
-- Note [Memoising typeOf]
-#else
--- | For defining a 'Typeable1' instance from any 'Typeable2' instance.
-typeOf1Default :: (Typeable2 t, Typeable a) => t a b -> TypeRep
-typeOf1Default x = typeOf2 x `mkAppTy` typeOf (argType x)
- where
- argType :: t a b -> a
- argType = undefined
-#endif
-- | Variant for 3-ary type constructors
class Typeable3 t where
typeOf3 :: t a b c -> TypeRep
-#ifdef __GLASGOW_HASKELL__
-- | For defining a 'Typeable2' instance from any 'Typeable3' instance.
typeOf2Default :: forall t a b c. (Typeable3 t, Typeable a) => t a b c -> TypeRep
typeOf2Default = \_ -> rep
@@ -273,20 +251,11 @@ typeOf2Default = \_ -> rep
rep = typeOf3 (undefined :: t a b c) `mkAppTy`
typeOf (undefined :: a)
-- Note [Memoising typeOf]
-#else
--- | For defining a 'Typeable2' instance from any 'Typeable3' instance.
-typeOf2Default :: (Typeable3 t, Typeable a) => t a b c -> TypeRep
-typeOf2Default x = typeOf3 x `mkAppTy` typeOf (argType x)
- where
- argType :: t a b c -> a
- argType = undefined
-#endif
-- | Variant for 4-ary type constructors
class Typeable4 t where
typeOf4 :: t a b c d -> TypeRep
-#ifdef __GLASGOW_HASKELL__
-- | For defining a 'Typeable3' instance from any 'Typeable4' instance.
typeOf3Default :: forall t a b c d. (Typeable4 t, Typeable a) => t a b c d -> TypeRep
typeOf3Default = \_ -> rep
@@ -294,20 +263,11 @@ typeOf3Default = \_ -> rep
rep = typeOf4 (undefined :: t a b c d) `mkAppTy`
typeOf (undefined :: a)
-- Note [Memoising typeOf]
-#else
--- | For defining a 'Typeable3' instance from any 'Typeable4' instance.
-typeOf3Default :: (Typeable4 t, Typeable a) => t a b c d -> TypeRep
-typeOf3Default x = typeOf4 x `mkAppTy` typeOf (argType x)
- where
- argType :: t a b c d -> a
- argType = undefined
-#endif
-- | Variant for 5-ary type constructors
class Typeable5 t where
typeOf5 :: t a b c d e -> TypeRep
-#ifdef __GLASGOW_HASKELL__
-- | For defining a 'Typeable4' instance from any 'Typeable5' instance.
typeOf4Default :: forall t a b c d e. (Typeable5 t, Typeable a) => t a b c d e -> TypeRep
typeOf4Default = \_ -> rep
@@ -315,20 +275,11 @@ typeOf4Default = \_ -> rep
rep = typeOf5 (undefined :: t a b c d e) `mkAppTy`
typeOf (undefined :: a)
-- Note [Memoising typeOf]
-#else
--- | For defining a 'Typeable4' instance from any 'Typeable5' instance.
-typeOf4Default :: (Typeable5 t, Typeable a) => t a b c d e -> TypeRep
-typeOf4Default x = typeOf5 x `mkAppTy` typeOf (argType x)
- where
- argType :: t a b c d e -> a
- argType = undefined
-#endif
-- | Variant for 6-ary type constructors
class Typeable6 t where
typeOf6 :: t a b c d e f -> TypeRep
-#ifdef __GLASGOW_HASKELL__
-- | For defining a 'Typeable5' instance from any 'Typeable6' instance.
typeOf5Default :: forall t a b c d e f. (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep
typeOf5Default = \_ -> rep
@@ -336,20 +287,11 @@ typeOf5Default = \_ -> rep
rep = typeOf6 (undefined :: t a b c d e f) `mkAppTy`
typeOf (undefined :: a)
-- Note [Memoising typeOf]
-#else
--- | For defining a 'Typeable5' instance from any 'Typeable6' instance.
-typeOf5Default :: (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep
-typeOf5Default x = typeOf6 x `mkAppTy` typeOf (argType x)
- where
- argType :: t a b c d e f -> a
- argType = undefined
-#endif
-- | Variant for 7-ary type constructors
class Typeable7 t where
typeOf7 :: t a b c d e f g -> TypeRep
-#ifdef __GLASGOW_HASKELL__
-- | For defining a 'Typeable6' instance from any 'Typeable7' instance.
typeOf6Default :: forall t a b c d e f g. (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep
typeOf6Default = \_ -> rep
@@ -357,16 +299,7 @@ typeOf6Default = \_ -> rep
rep = typeOf7 (undefined :: t a b c d e f g) `mkAppTy`
typeOf (undefined :: a)
-- Note [Memoising typeOf]
-#else
--- | For defining a 'Typeable6' instance from any 'Typeable7' instance.
-typeOf6Default :: (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep
-typeOf6Default x = typeOf7 x `mkAppTy` typeOf (argType x)
- where
- argType :: t a b c d e f g -> a
- argType = undefined
-#endif
-#ifdef __GLASGOW_HASKELL__
-- Given a @Typeable@/n/ instance for an /n/-ary type constructor,
-- define the instances for partial applications.
-- Programmers using non-GHC implementations must do this manually
@@ -408,8 +341,6 @@ instance (Typeable7 s, Typeable a)
=> Typeable6 (s a) where
typeOf6 = typeOf6Default
-#endif /* __GLASGOW_HASKELL__ */
-
----------------- Showing TypeReps --------------------
instance Show TypeRep where
@@ -451,13 +382,11 @@ showTuple args = showChar '('
$ map (showsPrec 10) args)
. showChar ')'
-#if defined(__GLASGOW_HASKELL__)
listTc :: TyCon
listTc = typeRepTyCon (typeOf [()])
funTc :: TyCon
funTc = mkTyCon3 "ghc-prim" "GHC.Types" "->"
-#endif
-------------------------------------------------------------
--
@@ -471,7 +400,7 @@ INSTANCE_TYPEABLE0((),unitTc,"()")
INSTANCE_TYPEABLE1([],listTc,"[]")
INSTANCE_TYPEABLE1(Maybe,maybeTc,"Maybe")
INSTANCE_TYPEABLE1(Ratio,ratioTc,"Ratio")
-#if defined(__GLASGOW_HASKELL__)
+
{-
TODO: Deriving this instance fails with:
libraries/base/Data/Typeable.hs:589:1:
@@ -480,24 +409,18 @@ libraries/base/Data/Typeable.hs:589:1:
In the stand-alone deriving instance for `Typeable2 (->)'
-}
instance Typeable2 (->) where { typeOf2 _ = mkTyConApp funTc [] }
-#else
-INSTANCE_TYPEABLE2((->),funTc,"->")
-#endif
+
INSTANCE_TYPEABLE1(IO,ioTc,"IO")
-#ifdef __GLASGOW_HASKELL__
-- Types defined in GHC.MVar
INSTANCE_TYPEABLE1(MVar,mvarTc,"MVar" )
-#endif
INSTANCE_TYPEABLE2(Array,arrayTc,"Array")
INSTANCE_TYPEABLE2(IOArray,iOArrayTc,"IOArray")
-#ifdef __GLASGOW_HASKELL__
INSTANCE_TYPEABLE2(ST,stTc,"ST")
INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef")
INSTANCE_TYPEABLE3(STArray,sTArrayTc,"STArray")
-#endif
INSTANCE_TYPEABLE2((,),pairTc,"(,)")
INSTANCE_TYPEABLE3((,,),tup3Tc,"(,,)")
@@ -508,9 +431,6 @@ INSTANCE_TYPEABLE7((,,,,,,),tup7Tc,"(,,,,,,)")
INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr")
INSTANCE_TYPEABLE1(FunPtr,funPtrTc,"FunPtr")
-#ifndef __GLASGOW_HASKELL__
-INSTANCE_TYPEABLE1(ForeignPtr,foreignPtrTc,"ForeignPtr")
-#endif
INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr")
INSTANCE_TYPEABLE1(IORef,iORefTc,"IORef")
@@ -528,9 +448,6 @@ INSTANCE_TYPEABLE0(Int,intTc,"Int")
INSTANCE_TYPEABLE0(Word,wordTc,"Word" )
INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
-#ifndef __GLASGOW_HASKELL__
-INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
-#endif
INSTANCE_TYPEABLE0(Int8,int8Tc,"Int8")
INSTANCE_TYPEABLE0(Int16,int16Tc,"Int16")
@@ -545,7 +462,6 @@ INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
-#ifdef __GLASGOW_HASKELL__
{-
TODO: This can't be derived currently:
libraries/base/Data/Typeable.hs:674:1:
@@ -556,5 +472,3 @@ libraries/base/Data/Typeable.hs:674:1:
realWorldTc :: TyCon; \
realWorldTc = mkTyCon3 "ghc-prim" "GHC.Types" "RealWorld"; \
instance Typeable RealWorld where { typeOf _ = mkTyConApp realWorldTc [] }
-
-#endif
diff --git a/libraries/base/Data/Ord.hs b/libraries/base/Data/Ord.hs
index c594c683aa..174855519e 100644
--- a/libraries/base/Data/Ord.hs
+++ b/libraries/base/Data/Ord.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -22,9 +22,7 @@ module Data.Ord (
comparing,
) where
-#if __GLASGOW_HASKELL__
import GHC.Base
-#endif
-- |
-- > comparing p x y = compare (p x) (p y)
diff --git a/libraries/base/Data/Proxy.hs b/libraries/base/Data/Proxy.hs
index bda295e41f..083db91291 100644
--- a/libraries/base/Data/Proxy.hs
+++ b/libraries/base/Data/Proxy.hs
@@ -1,7 +1,5 @@
{-# LANGUAGE NoImplicitPrelude, Trustworthy #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE PolyKinds #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -19,9 +17,7 @@
module Data.Proxy
(
Proxy(..), asProxyTypeOf
-#ifdef __GLASGOW_HASKELL__
, KProxy(..)
-#endif
) where
import Data.Monoid
@@ -35,11 +31,9 @@ import GHC.Arr
-- | A concrete, poly-kinded proxy type
data Proxy t = Proxy
-#ifdef __GLASGOW_HASKELL__
-- | A concrete, promotable proxy type, for use at the kind level
-- There are no instances for this because it is intended at the kind level only
data KProxy (t :: *) = KProxy
-#endif
instance Eq (Proxy s) where
_ == _ = True
@@ -69,10 +63,8 @@ instance Ix (Proxy s) where
index _ _ = 0
inRange _ _ = True
rangeSize _ = 1
-#ifdef __GLASGOW_HASKELL__
unsafeIndex _ _ = 0
unsafeRangeSize _ = 1
-#endif
instance Bounded (Proxy s) where
minBound = Proxy
@@ -102,4 +94,4 @@ instance Monad Proxy where
-- of the second.
asProxyTypeOf :: a -> Proxy a -> a
asProxyTypeOf = const
-{-# INLINE asProxyTypeOf #-} \ No newline at end of file
+{-# INLINE asProxyTypeOf #-}
diff --git a/libraries/base/Data/Ratio.hs b/libraries/base/Data/Ratio.hs
index 6af9088d70..6a16e9a260 100644
--- a/libraries/base/Data/Ratio.hs
+++ b/libraries/base/Data/Ratio.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Safe #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -27,9 +26,7 @@ module Data.Ratio
import Prelude
-#ifdef __GLASGOW_HASKELL__
import GHC.Real -- The basic defns for Ratio
-#endif
-- -----------------------------------------------------------------------------
-- approxRational
diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs
index ecedcc1989..486cc4b3de 100644
--- a/libraries/base/Data/STRef.hs
+++ b/libraries/base/Data/STRef.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -27,10 +26,8 @@ module Data.STRef (
import Prelude
-#ifdef __GLASGOW_HASKELL__
import GHC.ST
import GHC.STRef
-#endif
-- | Mutate the contents of an 'STRef'.
--
diff --git a/libraries/base/Data/String.hs b/libraries/base/Data/String.hs
index 8c24fb9e6e..a03569f21f 100644
--- a/libraries/base/Data/String.hs
+++ b/libraries/base/Data/String.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, FlexibleInstances #-}
+{-# LANGUAGE NoImplicitPrelude, FlexibleInstances #-}
-----------------------------------------------------------------------------
-- |
@@ -26,10 +26,7 @@ module Data.String (
, unwords
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
-#endif
-
import Data.List (lines, words, unlines, unwords)
-- | Class for string-like datastructures; used by the overloaded string
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index 9167331815..7872a617cc 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -58,9 +57,7 @@ import Data.Foldable (Foldable())
import Data.Monoid (Monoid)
import Data.Proxy
-#ifdef __GLASGOW_HASKELL__
import GHC.Arr
-#endif
-- | Functors representing data structures that can be traversed from
-- left to right.
diff --git a/libraries/base/Data/Tuple.hs b/libraries/base/Data/Tuple.hs
index cc7ded374e..ec8478a6ff 100644
--- a/libraries/base/Data/Tuple.hs
+++ b/libraries/base/Data/Tuple.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
-- XXX -fno-warn-unused-imports needed for the GHC.Tuple import below. Sigh.
@@ -26,8 +26,6 @@ module Data.Tuple
)
where
-#ifdef __GLASGOW_HASKELL__
-
import GHC.Base
-- We need to depend on GHC.Base so that
-- a) so that we get GHC.Classes, GHC.Types
@@ -40,8 +38,6 @@ import GHC.Tuple
-- data constructors of `(,)' are in scope when we do
-- the standalone deriving instance for Eq (a,b) etc
-#endif /* __GLASGOW_HASKELL__ */
-
default () -- Double isn't available yet
-- ---------------------------------------------------------------------------
diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs
index af8c672555..355f17bb5b 100644
--- a/libraries/base/Data/Typeable.hs
+++ b/libraries/base/Data/Typeable.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP
- , NoImplicitPrelude
+{-# LANGUAGE NoImplicitPrelude
, OverlappingInstances
, ScopedTypeVariables
, ForeignFunctionInterface
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index edfb1bc43c..4831ce6205 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -19,10 +19,9 @@
, FlexibleInstances
, MagicHash
, KindSignatures
- , PolyKinds #-}
-#ifdef __GLASGOW_HASKELL__
-{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
+ , PolyKinds
+ , DeriveDataTypeable
+ , StandaloneDeriving #-}
module Data.Typeable.Internal (
Proxy (..),
@@ -291,19 +290,15 @@ INSTANCE_TYPEABLE1(Ratio,ratioTc,"Ratio")
INSTANCE_TYPEABLE2((->),funTc,"->")
INSTANCE_TYPEABLE1(IO,ioTc,"IO")
-#ifdef __GLASGOW_HASKELL__
-- Types defined in GHC.MVar
{- INSTANCE_TYPEABLE1(MVar,mvarTc,"MVar" ) -}
-#endif
INSTANCE_TYPEABLE2(Array,arrayTc,"Array")
{- INSTANCE_TYPEABLE2(IOArray,iOArrayTc,"IOArray") -}
-#ifdef __GLASGOW_HASKELL__
INSTANCE_TYPEABLE2(ST,stTc,"ST")
INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef")
INSTANCE_TYPEABLE3(STArray,sTArrayTc,"STArray")
-#endif
INSTANCE_TYPEABLE2((,),pairTc,"(,)")
INSTANCE_TYPEABLE3((,,),tup3Tc,"(,,)")
@@ -314,9 +309,7 @@ INSTANCE_TYPEABLE7((,,,,,,),tup7Tc,"(,,,,,,)")
INSTANCE_TYPEABLE1(Ptr,ptrTc,"Ptr")
INSTANCE_TYPEABLE1(FunPtr,funPtrTc,"FunPtr")
-#ifndef __GLASGOW_HASKELL__
-INSTANCE_TYPEABLE1(ForeignPtr,foreignPtrTc,"ForeignPtr")
-#endif
+
{-
INSTANCE_TYPEABLE1(StablePtr,stablePtrTc,"StablePtr")
INSTANCE_TYPEABLE1(IORef,iORefTc,"IORef")
@@ -336,9 +329,6 @@ INSTANCE_TYPEABLE0(Int,intTc,"Int")
INSTANCE_TYPEABLE0(Word,wordTc,"Word" )
INSTANCE_TYPEABLE0(Integer,integerTc,"Integer")
INSTANCE_TYPEABLE0(Ordering,orderingTc,"Ordering")
-#ifndef __GLASGOW_HASKELL__
-INSTANCE_TYPEABLE0(Handle,handleTc,"Handle")
-#endif
{-
INSTANCE_TYPEABLE0(Int8,int8Tc,"Int8")
@@ -355,8 +345,6 @@ INSTANCE_TYPEABLE0(Word64,word64Tc,"Word64")
INSTANCE_TYPEABLE0(TyCon,tyconTc,"TyCon")
INSTANCE_TYPEABLE0(TypeRep,typeRepTc,"TypeRep")
-#ifdef __GLASGOW_HASKELL__
deriving instance Typeable RealWorld
deriving instance Typeable Proxy
deriving instance Typeable (:=:)
-#endif
diff --git a/libraries/base/Data/Unique.hs b/libraries/base/Data/Unique.hs
index ffd45f9427..2d30cc18e9 100644
--- a/libraries/base/Data/Unique.hs
+++ b/libraries/base/Data/Unique.hs
@@ -1,9 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE MagicHash, DeriveDataTypeable #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -30,20 +26,14 @@ import Prelude
import System.IO.Unsafe (unsafePerformIO)
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Num
import Data.Typeable
import Data.IORef
-#endif
-- | An abstract unique object. Objects of type 'Unique' may be
-- compared for equality and ordering and hashed into 'Int'.
-newtype Unique = Unique Integer deriving (Eq,Ord
-#ifdef __GLASGOW_HASKELL__
- ,Typeable
-#endif
- )
+newtype Unique = Unique Integer deriving (Eq,Ord,Typeable)
uniqSource :: IORef Integer
uniqSource = unsafePerformIO (newIORef 0)
@@ -81,8 +71,4 @@ newUnique = do
-- same value, although in practice this is unlikely. The 'Int'
-- returned makes a good hash key.
hashUnique :: Unique -> Int
-#if defined(__GLASGOW_HASKELL__)
hashUnique (Unique i) = I# (hashInteger i)
-#else
-hashUnique (Unique u) = fromInteger (u `mod` (toInteger (maxBound :: Int) + 1))
-#endif
diff --git a/libraries/base/Data/Version.hs b/libraries/base/Data/Version.hs
index 742e051c4a..23d217634e 100644
--- a/libraries/base/Data/Version.hs
+++ b/libraries/base/Data/Version.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, DeriveDataTypeable #-}
+{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
@@ -37,12 +37,7 @@ import Prelude -- necessary to get dependencies right
import Text.ParserCombinators.ReadP
-#if !__GLASGOW_HASKELL__
-import Data.Typeable ( Typeable, TyCon, mkTyCon, mkTyConApp )
-#else
import Data.Typeable ( Typeable )
-#endif
-
import Data.List ( intersperse, sort )
import Control.Monad ( liftM )
import Data.Char ( isDigit, isAlphaNum )
@@ -90,19 +85,7 @@ data Version =
-- The interpretation of the list of tags is entirely dependent
-- on the entity that this version applies to.
}
- deriving (Read,Show
-#if __GLASGOW_HASKELL__
- ,Typeable
-#endif
- )
-
-#if !__GLASGOW_HASKELL__
-versionTc :: TyCon
-versionTc = mkTyCon "Version"
-
-instance Typeable Version where
- typeOf _ = mkTyConApp versionTc []
-#endif
+ deriving (Read,Show,Typeable)
instance Eq Version where
v1 == v2 = versionBranch v1 == versionBranch v2
@@ -126,9 +109,7 @@ showVersion (Version branch tags)
-- | A parser for versions in the format produced by 'showVersion'.
--
-#ifdef __GLASGOW_HASKELL__
parseVersion :: ReadP Version
-#endif
parseVersion = do branch <- sepBy1 (liftM read $ munch1 isDigit) (char '.')
tags <- many (char '-' >> munch1 isAlphaNum)
return Version{versionBranch=branch, versionTags=tags}
diff --git a/libraries/base/Data/Word.hs b/libraries/base/Data/Word.hs
index 8f58783379..8af39b6d4d 100644
--- a/libraries/base/Data/Word.hs
+++ b/libraries/base/Data/Word.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Safe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -30,9 +30,7 @@ module Data.Word
-- $notes
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Word
-#endif
{- $notes
diff --git a/libraries/base/Debug/Trace.hs b/libraries/base/Debug/Trace.hs
index d4df4d90ef..7f78a85c0c 100644
--- a/libraries/base/Debug/Trace.hs
+++ b/libraries/base/Debug/Trace.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, ForeignFunctionInterface, MagicHash, UnboxedTuples #-}
+{-# LANGUAGE ForeignFunctionInterface, MagicHash, UnboxedTuples #-}
-----------------------------------------------------------------------------
-- |
@@ -46,16 +46,12 @@ import Prelude
import System.IO.Unsafe
import Control.Monad
-#ifdef __GLASGOW_HASKELL__
import Foreign.C.String
import GHC.Base
import qualified GHC.Foreign
import GHC.IO.Encoding
import GHC.Ptr
import GHC.Stack
-#else
-import System.IO (hPutStrLn,stderr)
-#endif
-- $tracing
--
@@ -73,9 +69,6 @@ import System.IO (hPutStrLn,stderr)
--
traceIO :: String -> IO ()
traceIO msg = do
-#ifndef __GLASGOW_HASKELL__
- hPutStrLn stderr msg
-#else
withCString "%s\n" $ \cfmt ->
withCString msg $ \cmsg ->
debugBelch cfmt cmsg
@@ -84,8 +77,6 @@ traceIO msg = do
-- using the FFI.
foreign import ccall unsafe "HsBase.h debugBelch2"
debugBelch :: CString -> CString -> IO ()
-#endif
-
-- | Deprecated. Use 'traceIO'.
putTraceMsg :: String -> IO ()
@@ -219,14 +210,9 @@ traceEvent msg expr = unsafeDupablePerformIO $ do
-- other IO actions.
--
traceEventIO :: String -> IO ()
-#ifdef __GLASGOW_HASKELL__
traceEventIO msg =
GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
case traceEvent# p s of s' -> (# s', () #)
-#else
-traceEventIO msg = (return $! length msg) >> return ()
-#endif
-
-- $markers
--
@@ -272,11 +258,6 @@ traceMarker msg expr = unsafeDupablePerformIO $ do
-- other IO actions.
--
traceMarkerIO :: String -> IO ()
-#ifdef __GLASGOW_HASKELL__
traceMarkerIO msg =
GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
case traceMarker# p s of s' -> (# s', () #)
-#else
-traceMarkerIO msg = (return $! length msg) >> return ()
-#endif
-
diff --git a/libraries/base/Foreign/C/Error.hs b/libraries/base/Foreign/C/Error.hs
index 0d10201a36..ad15edbb52 100644
--- a/libraries/base/Foreign/C/Error.hs
+++ b/libraries/base/Foreign/C/Error.hs
@@ -96,18 +96,11 @@ import Foreign.C.String
import Control.Monad ( void )
import Data.Maybe
-#if __GLASGOW_HASKELL__
import GHC.IO
import GHC.IO.Exception
import GHC.IO.Handle.Types
import GHC.Num
import GHC.Base
-#else
-import System.IO ( Handle )
-import System.IO.Error ( IOError, ioError )
-import System.IO.Unsafe ( unsafePerformIO )
-import Foreign.Storable ( Storable(poke,peek) )
-#endif
-- "errno" type
-- ------------
@@ -472,7 +465,6 @@ errnoToIOError :: String -- ^ the location where the error occurred
-> IOError
errnoToIOError loc errno maybeHdl maybeName = unsafePerformIO $ do
str <- strerror errno >>= peekCString
-#if __GLASGOW_HASKELL__
return (IOError maybeHdl errType loc str (Just errno') maybeName)
where
Errno errno' = errno
@@ -577,9 +569,6 @@ errnoToIOError loc errno maybeHdl maybeName = unsafePerformIO $ do
| errno == eWOULDBLOCK = OtherError
| errno == eXDEV = UnsupportedOperation
| otherwise = OtherError
-#else
- return (userError (loc ++ ": " ++ str ++ maybe "" (": "++) maybeName))
-#endif
foreign import ccall unsafe "string.h" strerror :: Errno -> IO (Ptr CChar)
diff --git a/libraries/base/Foreign/C/String.hs b/libraries/base/Foreign/C/String.hs
index 8be917ac07..cdbd241db5 100644
--- a/libraries/base/Foreign/C/String.hs
+++ b/libraries/base/Foreign/C/String.hs
@@ -31,14 +31,9 @@ module Foreign.C.String ( -- representation of strings in C
-- ** Using a locale-dependent encoding
-#ifndef __GLASGOW_HASKELL__
- -- | Currently these functions are identical to their @CAString@ counterparts;
- -- eventually they will use an encoding determined by the current locale.
-#else
-- | These functions are different from their @CAString@ counterparts
-- in that they will use an encoding determined by the current locale,
-- rather than always assuming ASCII.
-#endif
-- conversion of C strings into Haskell strings
--
@@ -107,7 +102,6 @@ import Foreign.Storable
import Data.Word
-#ifdef __GLASGOW_HASKELL__
import Control.Monad
import GHC.Char
@@ -118,10 +112,6 @@ import GHC.Base
import {-# SOURCE #-} GHC.IO.Encoding
import qualified GHC.Foreign as GHC
-#else
-import Data.Char ( chr, ord )
-#define unsafeChr chr
-#endif
-----------------------------------------------------------------------------
-- Strings
@@ -145,20 +135,12 @@ type CStringLen = (Ptr CChar, Int)
-- | Marshal a NUL terminated C string into a Haskell string.
--
peekCString :: CString -> IO String
-#ifndef __GLASGOW_HASKELL__
-peekCString = peekCAString
-#else
peekCString s = getForeignEncoding >>= flip GHC.peekCString s
-#endif
-- | Marshal a C string with explicit length into a Haskell string.
--
peekCStringLen :: CStringLen -> IO String
-#ifndef __GLASGOW_HASKELL__
-peekCStringLen = peekCAStringLen
-#else
peekCStringLen s = getForeignEncoding >>= flip GHC.peekCStringLen s
-#endif
-- | Marshal a Haskell string into a NUL terminated C string.
--
@@ -169,11 +151,7 @@ peekCStringLen s = getForeignEncoding >>= flip GHC.peekCStringLen s
-- 'Foreign.Marshal.Alloc.finalizerFree'.
--
newCString :: String -> IO CString
-#ifndef __GLASGOW_HASKELL__
-newCString = newCAString
-#else
newCString s = getForeignEncoding >>= flip GHC.newCString s
-#endif
-- | Marshal a Haskell string into a C string (ie, character array) with
-- explicit length information.
@@ -183,11 +161,7 @@ newCString s = getForeignEncoding >>= flip GHC.newCString s
-- 'Foreign.Marshal.Alloc.finalizerFree'.
--
newCStringLen :: String -> IO CStringLen
-#ifndef __GLASGOW_HASKELL__
-newCStringLen = newCAStringLen
-#else
newCStringLen s = getForeignEncoding >>= flip GHC.newCStringLen s
-#endif
-- | Marshal a Haskell string into a NUL terminated C string using temporary
-- storage.
@@ -199,11 +173,7 @@ newCStringLen s = getForeignEncoding >>= flip GHC.newCStringLen s
-- storage must /not/ be used after this.
--
withCString :: String -> (CString -> IO a) -> IO a
-#ifndef __GLASGOW_HASKELL__
-withCString = withCAString
-#else
withCString s f = getForeignEncoding >>= \enc -> GHC.withCString enc s f
-#endif
-- | Marshal a Haskell string into a C string (ie, character array)
-- in temporary storage, with explicit length information.
@@ -213,26 +183,12 @@ withCString s f = getForeignEncoding >>= \enc -> GHC.withCString enc s f
-- storage must /not/ be used after this.
--
withCStringLen :: String -> (CStringLen -> IO a) -> IO a
-#ifndef __GLASGOW_HASKELL__
-withCStringLen = withCAStringLen
-#else
withCStringLen s f = getForeignEncoding >>= \enc -> GHC.withCStringLen enc s f
-#endif
-
-#ifndef __GLASGOW_HASKELL__
--- | Determines whether a character can be accurately encoded in a 'CString'.
--- Unrepresentable characters are converted to @\'?\'@.
---
--- Currently only Latin-1 characters are representable.
-charIsRepresentable :: Char -> IO Bool
-charIsRepresentable c = return (ord c < 256)
-#else
-- -- | Determines whether a character can be accurately encoded in a 'CString'.
-- -- Unrepresentable characters are converted to '?' or their nearest visual equivalent.
charIsRepresentable :: Char -> IO Bool
charIsRepresentable c = getForeignEncoding >>= flip GHC.charIsRepresentable c
-#endif
-- single byte characters
-- ----------------------
@@ -272,11 +228,6 @@ castCharToCSChar ch = fromIntegral (ord ch)
-- | Marshal a NUL terminated C string into a Haskell string.
--
peekCAString :: CString -> IO String
-#ifndef __GLASGOW_HASKELL__
-peekCAString cp = do
- cs <- peekArray0 nUL cp
- return (cCharsToChars cs)
-#else
peekCAString cp = do
l <- lengthArray0 nUL cp
if l <= 0 then return "" else loop "" (l-1)
@@ -285,16 +236,10 @@ peekCAString cp = do
xval <- peekElemOff cp i
let val = castCCharToChar xval
val `seq` if i <= 0 then return (val:s) else loop (val:s) (i-1)
-#endif
-- | Marshal a C string with explicit length into a Haskell string.
--
peekCAStringLen :: CStringLen -> IO String
-#ifndef __GLASGOW_HASKELL__
-peekCAStringLen (cp, len) = do
- cs <- peekArray len cp
- return (cCharsToChars cs)
-#else
peekCAStringLen (cp, len)
| len <= 0 = return "" -- being (too?) nice.
| otherwise = loop [] (len-1)
@@ -306,7 +251,6 @@ peekCAStringLen (cp, len)
if (val `seq` (i == 0))
then return (val:acc)
else loop (val:acc) (i-1)
-#endif
-- | Marshal a Haskell string into a NUL terminated C string.
--
@@ -317,9 +261,6 @@ peekCAStringLen (cp, len)
-- 'Foreign.Marshal.Alloc.finalizerFree'.
--
newCAString :: String -> IO CString
-#ifndef __GLASGOW_HASKELL__
-newCAString = newArray0 nUL . charsToCChars
-#else
newCAString str = do
ptr <- mallocArray0 (length str)
let
@@ -327,7 +268,6 @@ newCAString str = do
go (c:cs) n = do pokeElemOff ptr n (castCharToCChar c); go cs (n+1)
go str 0
return ptr
-#endif
-- | Marshal a Haskell string into a C string (ie, character array) with
-- explicit length information.
@@ -337,9 +277,6 @@ newCAString str = do
-- 'Foreign.Marshal.Alloc.finalizerFree'.
--
newCAStringLen :: String -> IO CStringLen
-#ifndef __GLASGOW_HASKELL__
-newCAStringLen str = newArrayLen (charsToCChars str)
-#else
newCAStringLen str = do
ptr <- mallocArray0 len
let
@@ -349,7 +286,6 @@ newCAStringLen str = do
return (ptr, len)
where
len = length str
-#endif
-- | Marshal a Haskell string into a NUL terminated C string using temporary
-- storage.
@@ -361,9 +297,6 @@ newCAStringLen str = do
-- storage must /not/ be used after this.
--
withCAString :: String -> (CString -> IO a) -> IO a
-#ifndef __GLASGOW_HASKELL__
-withCAString = withArray0 nUL . charsToCChars
-#else
withCAString str f =
allocaArray0 (length str) $ \ptr ->
let
@@ -372,7 +305,6 @@ withCAString str f =
in do
go str 0
f ptr
-#endif
-- | Marshal a Haskell string into a C string (ie, character array)
-- in temporary storage, with explicit length information.
@@ -383,9 +315,6 @@ withCAString str f =
--
withCAStringLen :: String -> (CStringLen -> IO a) -> IO a
withCAStringLen str f =
-#ifndef __GLASGOW_HASKELL__
- withArrayLen (charsToCChars str) $ \ len ptr -> f (ptr, len)
-#else
allocaArray len $ \ptr ->
let
go [] n = n `seq` return () -- make it strict in n
@@ -395,7 +324,6 @@ withCAStringLen str f =
f (ptr,len)
where
len = length str
-#endif
-- auxiliary definitions
-- ----------------------
@@ -411,18 +339,6 @@ newArrayLen xs = do
a <- newArray xs
return (a, length xs)
-#ifndef __GLASGOW_HASKELL__
--- cast [CChar] to [Char]
---
-cCharsToChars :: [CChar] -> [Char]
-cCharsToChars xs = map castCCharToChar xs
-
--- cast [Char] to [CChar]
---
-charsToCChars :: [Char] -> [CChar]
-charsToCChars xs = map castCharToCChar xs
-#endif
-
-----------------------------------------------------------------------------
-- Wide strings
diff --git a/libraries/base/Foreign/C/Types.hs b/libraries/base/Foreign/C/Types.hs
index bde6be51a1..9951515816 100644
--- a/libraries/base/Foreign/C/Types.hs
+++ b/libraries/base/Foreign/C/Types.hs
@@ -5,9 +5,7 @@
, GeneralizedNewtypeDeriving
#-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
-- XXX -fno-warn-unused-binds stops us warning about unused constructors,
-- but really we should just remove them if we don't want them
@@ -66,10 +64,9 @@ module Foreign.C.Types
-- 'Prelude.Real', 'Prelude.Fractional', 'Prelude.Floating',
-- 'Prelude.RealFrac' and 'Prelude.RealFloat'.
, CFloat(..), CDouble(..)
--- GHC doesn't support CLDouble yet
-#ifndef __GLASGOW_HASKELL__
- , CLDouble(..)
-#endif
+ -- XXX GHC doesn't support CLDouble yet
+ -- , CLDouble(..)
+
-- ** Other types
-- Instances of: Eq and Storable
@@ -82,7 +79,6 @@ import Data.Int ( Int8, Int16, Int32, Int64 )
import Data.Word ( Word8, Word16, Word32, Word64 )
import Data.Typeable
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Float
import GHC.Enum
@@ -90,9 +86,6 @@ import GHC.Real
import GHC.Show
import GHC.Read
import GHC.Num
-#else
-import Control.Monad ( liftM )
-#endif
#include "HsBaseConfig.h"
#include "CTypes.h"
@@ -154,12 +147,7 @@ INTEGRAL_TYPE(CULLong,tyConCULLong,"CULLong",HTYPE_UNSIGNED_LONG_LONG)
FLOATING_TYPE(CFloat,tyConCFloat,"CFloat",HTYPE_FLOAT)
-- | Haskell type representing the C @double@ type.
FLOATING_TYPE(CDouble,tyConCDouble,"CDouble",HTYPE_DOUBLE)
--- GHC doesn't support CLDouble yet
-#ifndef __GLASGOW_HASKELL__
--- HACK: Currently no long double in the FFI, so we simply re-use double
--- | Haskell type representing the C @long double@ type.
-FLOATING_TYPE(CLDouble,tyConCLDouble,"CLDouble",HTYPE_DOUBLE)
-#endif
+-- XXX GHC doesn't support CLDouble yet
{-# RULES
"realToFrac/a->CFloat" realToFrac = \x -> CFloat (realToFrac x)
diff --git a/libraries/base/Foreign/Concurrent.hs b/libraries/base/Foreign/Concurrent.hs
index 6a21b792dd..9d27166fde 100644
--- a/libraries/base/Foreign/Concurrent.hs
+++ b/libraries/base/Foreign/Concurrent.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -29,7 +29,6 @@ module Foreign.Concurrent
addForeignPtrFinalizer,
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.IO ( IO )
import GHC.Ptr ( Ptr )
import GHC.ForeignPtr ( ForeignPtr )
@@ -50,5 +49,3 @@ addForeignPtrFinalizer :: ForeignPtr a -> IO () -> IO ()
-- is dropped, but /before/ all previously registered finalizers for the
-- same object.
addForeignPtrFinalizer = GHC.ForeignPtr.addForeignPtrConcFinalizer
-#endif
-
diff --git a/libraries/base/Foreign/ForeignPtr.hs b/libraries/base/Foreign/ForeignPtr.hs
index 6219adb0eb..0017c0e8ac 100644
--- a/libraries/base/Foreign/ForeignPtr.hs
+++ b/libraries/base/Foreign/ForeignPtr.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_HADDOCK hide #-}
-----------------------------------------------------------------------------
@@ -22,22 +22,16 @@ module Foreign.ForeignPtr (
-- * Finalised data pointers
ForeignPtr
, FinalizerPtr
-#ifdef __GLASGOW_HASKELL__
, FinalizerEnvPtr
-#endif
+
-- ** Basic operations
, newForeignPtr
, newForeignPtr_
, addForeignPtrFinalizer
-#ifdef __GLASGOW_HASKELL__
, newForeignPtrEnv
, addForeignPtrFinalizerEnv
-#endif
, withForeignPtr
-
-#ifdef __GLASGOW_HASKELL__
, finalizeForeignPtr
-#endif
-- ** Low-level operations
, touchForeignPtr
diff --git a/libraries/base/Foreign/ForeignPtr/Imp.hs b/libraries/base/Foreign/ForeignPtr/Imp.hs
index 9499fbce8d..2c3f39365b 100644
--- a/libraries/base/Foreign/ForeignPtr/Imp.hs
+++ b/libraries/base/Foreign/ForeignPtr/Imp.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_HADDOCK hide #-}
-----------------------------------------------------------------------------
@@ -23,22 +23,16 @@ module Foreign.ForeignPtr.Imp
-- * Finalised data pointers
ForeignPtr
, FinalizerPtr
-#ifdef __GLASGOW_HASKELL__
, FinalizerEnvPtr
-#endif
+
-- ** Basic operations
, newForeignPtr
, newForeignPtr_
, addForeignPtrFinalizer
-#ifdef __GLASGOW_HASKELL__
, newForeignPtrEnv
, addForeignPtrFinalizerEnv
-#endif
, withForeignPtr
-
-#ifdef __GLASGOW_HASKELL__
, finalizeForeignPtr
-#endif
-- ** Low-level operations
, unsafeForeignPtrToPtr
@@ -56,25 +50,9 @@ module Foreign.ForeignPtr.Imp
import Foreign.Ptr
import Foreign.Storable ( Storable(sizeOf) )
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Num
import GHC.ForeignPtr
-#endif
-
-#if !defined(__GLASGOW_HASKELL__)
-import Foreign.Marshal.Alloc ( malloc, mallocBytes, finalizerFree )
-
-instance Eq (ForeignPtr a) where
- p == q = unsafeForeignPtrToPtr p == unsafeForeignPtrToPtr q
-
-instance Ord (ForeignPtr a) where
- compare p q = compare (unsafeForeignPtrToPtr p) (unsafeForeignPtrToPtr q)
-
-instance Show (ForeignPtr a) where
- showsPrec p f = showsPrec p (unsafeForeignPtrToPtr f)
-#endif
-
newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
-- ^Turns a plain memory reference into a foreign pointer, and
@@ -112,7 +90,6 @@ withForeignPtr fo io
touchForeignPtr fo
return r
-#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
@@ -123,19 +100,6 @@ newForeignPtrEnv finalizer env p
= do fObj <- newForeignPtr_ p
addForeignPtrFinalizerEnv finalizer env fObj
return fObj
-#endif
-
-#ifndef __GLASGOW_HASKELL__
-mallocForeignPtr :: Storable a => IO (ForeignPtr a)
-mallocForeignPtr = do
- r <- malloc
- newForeignPtr finalizerFree r
-
-mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
-mallocForeignPtrBytes n = do
- r <- mallocBytes n
- newForeignPtr finalizerFree r
-#endif /* !__GLASGOW_HASKELL__ */
-- | This function is similar to 'Foreign.Marshal.Array.mallocArray',
-- but yields a memory area that has a finalizer attached that releases
diff --git a/libraries/base/Foreign/ForeignPtr/Safe.hs b/libraries/base/Foreign/ForeignPtr/Safe.hs
index 4289a98067..190e8b680a 100644
--- a/libraries/base/Foreign/ForeignPtr/Safe.hs
+++ b/libraries/base/Foreign/ForeignPtr/Safe.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -23,22 +23,16 @@ module Foreign.ForeignPtr.Safe (
-- * Finalised data pointers
ForeignPtr
, FinalizerPtr
-#ifdef __GLASGOW_HASKELL__
, FinalizerEnvPtr
-#endif
+
-- ** Basic operations
, newForeignPtr
, newForeignPtr_
, addForeignPtrFinalizer
-#ifdef __GLASGOW_HASKELL__
, newForeignPtrEnv
, addForeignPtrFinalizerEnv
-#endif
, withForeignPtr
-
-#ifdef __GLASGOW_HASKELL__
, finalizeForeignPtr
-#endif
-- ** Low-level operations
, touchForeignPtr
diff --git a/libraries/base/Foreign/ForeignPtr/Unsafe.hs b/libraries/base/Foreign/ForeignPtr/Unsafe.hs
index 7cc9a25cdd..5a36a7e12b 100644
--- a/libraries/base/Foreign/ForeignPtr/Unsafe.hs
+++ b/libraries/base/Foreign/ForeignPtr/Unsafe.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
diff --git a/libraries/base/Foreign/Marshal.hs b/libraries/base/Foreign/Marshal.hs
index 799596e464..9336549c6f 100644
--- a/libraries/base/Foreign/Marshal.hs
+++ b/libraries/base/Foreign/Marshal.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs
index d68988d203..9069e8aa19 100644
--- a/libraries/base/Foreign/Marshal/Alloc.hs
+++ b/libraries/base/Foreign/Marshal/Alloc.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP
- , NoImplicitPrelude
+{-# LANGUAGE NoImplicitPrelude
, MagicHash
, UnboxedTuples
, ForeignFunctionInterface
@@ -64,20 +63,11 @@ module Foreign.Marshal.Alloc (
import Data.Maybe
import Foreign.C.Types ( CSize(..) )
import Foreign.Storable ( Storable(sizeOf,alignment) )
-
-#ifndef __GLASGOW_HASKELL__
-import Foreign.Ptr ( Ptr, nullPtr, FunPtr )
-#endif
-
-#ifdef __GLASGOW_HASKELL__
import Foreign.ForeignPtr ( FinalizerPtr )
import GHC.IO.Exception
import GHC.Real
import GHC.Ptr
import GHC.Base
-#else
-import Control.Exception.Base ( bracket )
-#endif
-- exported functions
-- ------------------
@@ -128,7 +118,6 @@ alloca = doAlloca undefined
-- The memory is freed when @f@ terminates (either normally or via an
-- exception), so the pointer passed to @f@ must /not/ be used after this.
--
-#ifdef __GLASGOW_HASKELL__
allocaBytes :: Int -> (Ptr a -> IO b) -> IO b
allocaBytes (I# size) action = IO $ \ s0 ->
case newPinnedByteArray# size s0 of { (# s1, mbarr# #) ->
@@ -150,13 +139,6 @@ allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 ->
case touch# barr# s3 of { s4 ->
(# s4, r #)
}}}}}
-#else
-allocaBytes :: Int -> (Ptr a -> IO b) -> IO b
-allocaBytes size = bracket (mallocBytes size) free
-
-allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b
-allocaBytesAligned size align = allocaBytes size -- wrong
-#endif
-- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes'
-- to the size needed to store values of type @b@. The returned pointer
@@ -213,12 +195,8 @@ failWhenNULL :: String -> IO (Ptr a) -> IO (Ptr a)
failWhenNULL name f = do
addr <- f
if addr == nullPtr
-#if __GLASGOW_HASKELL__
then ioError (IOError Nothing ResourceExhausted name
"out of memory" Nothing Nothing)
-#else
- then ioError (userError (name++": out of memory"))
-#endif
else return addr
-- basic C routines needed for memory allocation
diff --git a/libraries/base/Foreign/Marshal/Array.hs b/libraries/base/Foreign/Marshal/Array.hs
index d6a004109c..8d7dcfb560 100644
--- a/libraries/base/Foreign/Marshal/Array.hs
+++ b/libraries/base/Foreign/Marshal/Array.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude, MagicHash #-}
-----------------------------------------------------------------------------
-- |
@@ -69,13 +69,9 @@ import Foreign.Storable (Storable(alignment,sizeOf,peekElemOff,pokeElemOff))
import Foreign.Marshal.Alloc (mallocBytes, allocaBytesAligned, reallocBytes)
import Foreign.Marshal.Utils (copyBytes, moveBytes)
-#ifdef __GLASGOW_HASKELL__
import GHC.Num
import GHC.List
import GHC.Base
-#else
-import Control.Monad (zipWithM_)
-#endif
-- allocation
-- ----------
@@ -151,28 +147,17 @@ peekArray0 marker ptr = do
-- |Write the list elements consecutive into memory
--
pokeArray :: Storable a => Ptr a -> [a] -> IO ()
-#ifndef __GLASGOW_HASKELL__
-pokeArray ptr vals = zipWithM_ (pokeElemOff ptr) [0..] vals
-#else
pokeArray ptr vals0 = go vals0 0#
where go [] _ = return ()
go (val:vals) n# = do pokeElemOff ptr (I# n#) val; go vals (n# +# 1#)
-#endif
-- |Write the list elements consecutive into memory and terminate them with the
-- given marker element
--
pokeArray0 :: Storable a => a -> Ptr a -> [a] -> IO ()
-#ifndef __GLASGOW_HASKELL__
-pokeArray0 marker ptr vals = do
- pokeArray ptr vals
- pokeElemOff ptr (length vals) marker
-#else
pokeArray0 marker ptr vals0 = go vals0 0#
where go [] n# = pokeElemOff ptr (I# n#) marker
go (val:vals) n# = do pokeElemOff ptr (I# n#) val; go vals (n# +# 1#)
-#endif
-
-- combined allocation and marshalling
-- -----------------------------------
diff --git a/libraries/base/Foreign/Marshal/Error.hs b/libraries/base/Foreign/Marshal/Error.hs
index e26716cfdf..ab90e6d23e 100644
--- a/libraries/base/Foreign/Marshal/Error.hs
+++ b/libraries/base/Foreign/Marshal/Error.hs
@@ -30,7 +30,6 @@ module Foreign.Marshal.Error (
import Foreign.Ptr
-#ifdef __GLASGOW_HASKELL__
#ifdef __HADDOCK__
import Data.Bool
import System.IO.Error
@@ -38,7 +37,6 @@ import System.IO.Error
import GHC.Base
import GHC.Num
import GHC.IO.Exception
-#endif
-- exported functions
-- ------------------
diff --git a/libraries/base/Foreign/Marshal/Pool.hs b/libraries/base/Foreign/Marshal/Pool.hs
index bc35dcf925..8dc57ae753 100644
--- a/libraries/base/Foreign/Marshal/Pool.hs
+++ b/libraries/base/Foreign/Marshal/Pool.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
--------------------------------------------------------------------------------
-- |
@@ -46,7 +46,6 @@ module Foreign.Marshal.Pool (
pooledNewArray0
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base ( Int, Monad(..), (.), not )
import GHC.Err ( undefined )
import GHC.Exception ( throw )
@@ -54,10 +53,6 @@ import GHC.IO ( IO, mask, catchAny )
import GHC.IORef ( IORef, newIORef, readIORef, writeIORef )
import GHC.List ( elem, length )
import GHC.Num ( Num(..) )
-#else
-import Data.IORef ( IORef, newIORef, readIORef, writeIORef )
-import Control.Exception.Base ( bracket )
-#endif
import Control.Monad ( liftM )
import Data.List ( delete )
@@ -93,7 +88,6 @@ freePool (Pool pool) = readIORef pool >>= freeAll
-- deallocated (including its contents) after the action has finished.
withPool :: (Pool -> IO b) -> IO b
-#ifdef __GLASGOW_HASKELL__
withPool act = -- ATTENTION: cut-n-paste from Control.Exception below!
mask (\restore -> do
pool <- newPool
@@ -102,9 +96,6 @@ withPool act = -- ATTENTION: cut-n-paste from Control.Exception below!
(\e -> do freePool pool; throw e)
freePool pool
return val)
-#else
-withPool = bracket newPool freePool
-#endif
--------------------------------------------------------------------------------
diff --git a/libraries/base/Foreign/Marshal/Safe.hs b/libraries/base/Foreign/Marshal/Safe.hs
index 73132176da..85bad2bdd7 100644
--- a/libraries/base/Foreign/Marshal/Safe.hs
+++ b/libraries/base/Foreign/Marshal/Safe.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Safe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
diff --git a/libraries/base/Foreign/Marshal/Unsafe.hs b/libraries/base/Foreign/Marshal/Unsafe.hs
index ee05fd45d0..7e986f99e8 100644
--- a/libraries/base/Foreign/Marshal/Unsafe.hs
+++ b/libraries/base/Foreign/Marshal/Unsafe.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -20,11 +20,7 @@ module Foreign.Marshal.Unsafe (
unsafeLocalState
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.IO
-#else
-import System.IO.Unsafe
-#endif
{- |
Sometimes an external entity is a pure function, except that it passes
diff --git a/libraries/base/Foreign/Marshal/Utils.hs b/libraries/base/Foreign/Marshal/Utils.hs
index dc6471ad17..491bd125b4 100644
--- a/libraries/base/Foreign/Marshal/Utils.hs
+++ b/libraries/base/Foreign/Marshal/Utils.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, ForeignFunctionInterface #-}
+{-# LANGUAGE NoImplicitPrelude, ForeignFunctionInterface #-}
-----------------------------------------------------------------------------
-- |
@@ -51,11 +51,9 @@ import Foreign.Storable ( Storable(poke) )
import Foreign.C.Types ( CSize(..) )
import Foreign.Marshal.Alloc ( malloc, alloca )
-#ifdef __GLASGOW_HASKELL__
import GHC.Real ( fromIntegral )
import GHC.Num
import GHC.Base
-#endif
-- combined allocation and marshalling
-- -----------------------------------
diff --git a/libraries/base/Foreign/Ptr.hs b/libraries/base/Foreign/Ptr.hs
index 9c8267ed2b..808fff636a 100644
--- a/libraries/base/Foreign/Ptr.hs
+++ b/libraries/base/Foreign/Ptr.hs
@@ -5,9 +5,7 @@
, MagicHash
, GeneralizedNewtypeDeriving
#-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -56,7 +54,6 @@ module Foreign.Ptr (
wordPtrToPtr
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Ptr
import GHC.Base
import GHC.Num
@@ -64,28 +61,21 @@ import GHC.Read
import GHC.Real
import GHC.Show
import GHC.Enum
-#else
-import Control.Monad ( liftM )
-import Foreign.C.Types
-#endif
import Data.Bits
import Data.Typeable
import Foreign.Storable ( Storable(..) )
-#ifdef __GLASGOW_HASKELL__
-- | Release the storage associated with the given 'FunPtr', which
-- must have been obtained from a wrapper stub. This should be called
-- whenever the return value from a foreign import wrapper function is
-- no longer required; otherwise, the storage it uses will leak.
foreign import ccall unsafe "freeHaskellFunctionPtr"
freeHaskellFunPtr :: FunPtr a -> IO ()
-#endif
#include "HsBaseConfig.h"
#include "CTypes.h"
-#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.
@@ -113,25 +103,3 @@ ptrToIntPtr (Ptr a#) = IntPtr (I# (addr2Int# a#))
-- | casts an @IntPtr@ to a @Ptr@
intPtrToPtr :: IntPtr -> Ptr a
intPtrToPtr (IntPtr (I# i#)) = Ptr (int2Addr# i#)
-
-#else /* !__GLASGOW_HASKELL__ */
-
-INTEGRAL_TYPE(WordPtr,tyConWordPtr,"WordPtr",CUIntPtr)
-INTEGRAL_TYPE(IntPtr,tyConIntPtr,"IntPtr",CIntPtr)
-
-{-# CFILES cbits/PrelIOUtils.c #-}
-
-foreign import ccall unsafe "__hscore_to_uintptr"
- ptrToWordPtr :: Ptr a -> WordPtr
-
-foreign import ccall unsafe "__hscore_from_uintptr"
- wordPtrToPtr :: WordPtr -> Ptr a
-
-foreign import ccall unsafe "__hscore_to_intptr"
- ptrToIntPtr :: Ptr a -> IntPtr
-
-foreign import ccall unsafe "__hscore_from_intptr"
- intPtrToPtr :: IntPtr -> Ptr a
-
-#endif /* !__GLASGOW_HASKELL__ */
-
diff --git a/libraries/base/Foreign/StablePtr.hs b/libraries/base/Foreign/StablePtr.hs
index 47610d6439..acd89e5428 100644
--- a/libraries/base/Foreign/StablePtr.hs
+++ b/libraries/base/Foreign/StablePtr.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -30,9 +30,7 @@ module Foreign.StablePtr
-- $cinterface
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Stable
-#endif
-- $cinterface
--
diff --git a/libraries/base/Foreign/Storable.hs b/libraries/base/Foreign/Storable.hs
index d8189a706b..86e65f8ad7 100644
--- a/libraries/base/Foreign/Storable.hs
+++ b/libraries/base/Foreign/Storable.hs
@@ -1,8 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE BangPatterns #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -39,7 +37,6 @@ import Control.Monad ( liftM )
#include "MachDeps.h"
#include "HsBaseConfig.h"
-#ifdef __GLASGOW_HASKELL__
import GHC.Storable
import GHC.Stable ( StablePtr )
import GHC.Num
@@ -50,11 +47,6 @@ import GHC.Base
import GHC.Fingerprint.Type
import Data.Bits
import GHC.Real
-#else
-import Data.Int
-import Data.Word
-import Foreign.StablePtr
-#endif
{- |
The member functions of this class facilitate writing values of
@@ -146,13 +138,9 @@ class Storable a where
-- restrictions might apply; see 'peek'.
-- circular default instances
-#ifdef __GLASGOW_HASKELL__
peekElemOff = peekElemOff_ undefined
where peekElemOff_ :: a -> Ptr a -> Int -> IO a
peekElemOff_ undef ptr off = peekByteOff ptr (off * sizeOf undef)
-#else
- peekElemOff ptr off = peekByteOff ptr (off * sizeOfPtr ptr undefined)
-#endif
pokeElemOff ptr off val = pokeByteOff ptr (off * sizeOf val) val
peekByteOff ptr off = peek (ptr `plusPtr` off)
@@ -161,11 +149,6 @@ class Storable a where
peek ptr = peekElemOff ptr 0
poke ptr = pokeElemOff ptr 0
-#ifndef __GLASGOW_HASKELL__
-sizeOfPtr :: Storable a => Ptr a -> a -> Int
-sizeOfPtr px x = sizeOf x
-#endif
-
-- System-dependent, but rather obvious instances
instance Storable Bool where
@@ -181,10 +164,8 @@ instance Storable (T) where { \
peekElemOff = read; \
pokeElemOff = write }
-#ifdef __GLASGOW_HASKELL__
STORABLE(Char,SIZEOF_INT32,ALIGNMENT_INT32,
readWideCharOffPtr,writeWideCharOffPtr)
-#endif
STORABLE(Int,SIZEOF_HSINT,ALIGNMENT_HSINT,
readIntOffPtr,writeIntOffPtr)
@@ -232,7 +213,6 @@ STORABLE(Int64,SIZEOF_INT64,ALIGNMENT_INT64,
readInt64OffPtr,writeInt64OffPtr)
-- XXX: here to avoid orphan instance in GHC.Fingerprint
-#ifdef __GLASGOW_HASKELL__
instance Storable Fingerprint where
sizeOf _ = 16
alignment _ = 8
@@ -263,5 +243,3 @@ pokeFingerprint p0 (Fingerprint high low) = do
pokeW64 (castPtr p0) 8 high
pokeW64 (castPtr p0 `plusPtr` 8) 8 low
-#endif
-
diff --git a/libraries/base/GHC/Constants.hs b/libraries/base/GHC/Constants.hs
index fcea20b438..d8efd7228c 100644
--- a/libraries/base/GHC/Constants.hs
+++ b/libraries/base/GHC/Constants.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
module GHC.Constants where
diff --git a/libraries/base/GHC/Desugar.hs b/libraries/base/GHC/Desugar.hs
index 8c1070264a..72553bf089 100644
--- a/libraries/base/GHC/Desugar.hs
+++ b/libraries/base/GHC/Desugar.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP
- , NoImplicitPrelude
+{-# LANGUAGE NoImplicitPrelude
, RankNTypes
, ExistentialQuantification
#-}
diff --git a/libraries/base/GHC/Err.lhs b/libraries/base/GHC/Err.lhs
index e9f1212d20..2ec7ab5594 100644
--- a/libraries/base/GHC/Err.lhs
+++ b/libraries/base/GHC/Err.lhs
@@ -1,6 +1,6 @@
\begin{code}
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude, MagicHash #-}
{-# OPTIONS_HADDOCK hide #-}
-----------------------------------------------------------------------------
diff --git a/libraries/base/GHC/Foreign.hs b/libraries/base/GHC/Foreign.hs
index 742bcef010..ef64d48572 100644
--- a/libraries/base/GHC/Foreign.hs
+++ b/libraries/base/GHC/Foreign.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
diff --git a/libraries/base/GHC/IO/Device.hs b/libraries/base/GHC/IO/Device.hs
index 963cb9f9e5..e20cdf0770 100644
--- a/libraries/base/GHC/IO/Device.hs
+++ b/libraries/base/GHC/IO/Device.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns #-}
+{-# LANGUAGE NoImplicitPrelude, BangPatterns #-}
-----------------------------------------------------------------------------
-- |
@@ -22,7 +22,6 @@ module GHC.IO.Device (
SeekMode(..)
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Word
import GHC.Arr
@@ -34,7 +33,6 @@ import Data.Maybe
import GHC.Num
import GHC.IO
import {-# SOURCE #-} GHC.IO.Exception ( unsupportedOperation )
-#endif
-- | A low-level I/O provider where the data is bytes in memory.
class RawIO a where
diff --git a/libraries/base/GHC/IO/Encoding/UTF16.hs b/libraries/base/GHC/IO/Encoding/UTF16.hs
index ca231caddb..3b1d072f5d 100644
--- a/libraries/base/GHC/IO/Encoding/UTF16.hs
+++ b/libraries/base/GHC/IO/Encoding/UTF16.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP
- , NoImplicitPrelude
+{-# LANGUAGE NoImplicitPrelude
, BangPatterns
, NondecreasingIndentation
, MagicHash
diff --git a/libraries/base/GHC/Read.lhs b/libraries/base/GHC/Read.lhs
index 0729ff2145..05ee4f90ad 100644
--- a/libraries/base/GHC/Read.lhs
+++ b/libraries/base/GHC/Read.lhs
@@ -1,6 +1,6 @@
\begin{code}
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, StandaloneDeriving, PatternGuards,
+{-# LANGUAGE NoImplicitPrelude, StandaloneDeriving, PatternGuards,
ScopedTypeVariables #-}
{-# OPTIONS_HADDOCK hide #-}
diff --git a/libraries/base/Numeric.hs b/libraries/base/Numeric.hs
index 3b444e1930..600c82f8ec 100644
--- a/libraries/base/Numeric.hs
+++ b/libraries/base/Numeric.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude, MagicHash #-}
-----------------------------------------------------------------------------
-- |
@@ -57,7 +57,6 @@ module Numeric (
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Read
import GHC.Real
@@ -67,11 +66,7 @@ import GHC.Show
import Data.Maybe
import Text.ParserCombinators.ReadP( ReadP, readP_to_S, pfail )
import qualified Text.Read.Lex as L
-#else
-import Data.Char
-#endif
-#ifdef __GLASGOW_HASKELL__
-- -----------------------------------------------------------------------------
-- Reading
@@ -184,7 +179,6 @@ showGFloat :: (RealFloat a) => Maybe Int -> a -> ShowS
showEFloat d x = showString (formatRealFloat FFExponent d x)
showFFloat d x = showString (formatRealFloat FFFixed d x)
showGFloat d x = showString (formatRealFloat FFGeneric d x)
-#endif /* __GLASGOW_HASKELL__ */
-- ---------------------------------------------------------------------------
-- Integer printing functions
diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs
index fdfa4fb456..6be784603c 100644
--- a/libraries/base/Prelude.hs
+++ b/libraries/base/Prelude.hs
@@ -142,7 +142,6 @@ import Data.Either
import Data.Maybe
import Data.Tuple
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import Text.Read
import GHC.Enum
@@ -150,7 +149,6 @@ import GHC.Num
import GHC.Real
import GHC.Float
import GHC.Show
-#endif
infixr 0 $!
@@ -159,11 +157,7 @@ infixr 0 $!
-- | Strict (call-by-value) application, defined in terms of 'seq'.
($!) :: (a -> b) -> a -> b
-#ifdef __GLASGOW_HASKELL__
f $! x = let !vx = x in f vx -- see #2273
-#else
-f $! x = x `seq` f x
-#endif
#ifdef __HADDOCK__
-- | The value of @'seq' a b@ is bottom if @a@ is bottom, and otherwise
diff --git a/libraries/base/System/CPUTime.hsc b/libraries/base/System/CPUTime.hsc
index ab8f86ccd6..0ea6dfbf04 100644
--- a/libraries/base/System/CPUTime.hsc
+++ b/libraries/base/System/CPUTime.hsc
@@ -28,7 +28,6 @@ import Prelude
import Data.Ratio
-#ifdef __GLASGOW_HASKELL__
import Foreign.Safe
import Foreign.C
@@ -49,8 +48,6 @@ import Foreign.C
#include <sys/times.h>
#endif
-#endif
-
##ifdef mingw32_HOST_OS
## if defined(i386_HOST_ARCH)
## define WINDOWS_CCONV stdcall
@@ -69,7 +66,6 @@ realToInteger ct = round (realToFrac ct :: Double)
-- so we must convert to Double before we can round it
#endif
-#ifdef __GLASGOW_HASKELL__
-- -----------------------------------------------------------------------------
-- |Computation 'getCPUTime' returns the number of picoseconds CPU time
-- used by the current program. The precision of this result is
@@ -152,7 +148,7 @@ foreign import WINDOWS_CCONV unsafe "GetCurrentProcess" getCurrentProcess :: IO
foreign import WINDOWS_CCONV unsafe "GetProcessTimes" getProcessTimes :: Ptr HANDLE -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> IO CInt
#endif /* not _WIN32 */
-#endif /* __GLASGOW_HASKELL__ */
+
-- |The 'cpuTimePrecision' constant is the smallest measurable difference
-- in CPU time that the implementation can record, and is given as an
@@ -161,9 +157,7 @@ foreign import WINDOWS_CCONV unsafe "GetProcessTimes" getProcessTimes :: Ptr HAN
cpuTimePrecision :: Integer
cpuTimePrecision = round ((1000000000000::Integer) % fromIntegral (clockTicks))
-#ifdef __GLASGOW_HASKELL__
foreign import ccall unsafe clk_tck :: CLong
clockTicks :: Int
clockTicks = fromIntegral clk_tck
-#endif /* __GLASGOW_HASKELL__ */
diff --git a/libraries/base/System/Environment.hs b/libraries/base/System/Environment.hs
index 25aa6f4ab7..8397fc30b5 100644
--- a/libraries/base/System/Environment.hs
+++ b/libraries/base/System/Environment.hs
@@ -26,14 +26,11 @@ module System.Environment
unsetEnv,
withArgs,
withProgName,
-#ifdef __GLASGOW_HASKELL__
getEnvironment,
-#endif
) where
import Prelude
-#ifdef __GLASGOW_HASKELL__
import Foreign.Safe
import Foreign.C
import System.IO.Error (mkIOError)
@@ -50,7 +47,6 @@ import GHC.Windows
#else
import System.Posix.Internals (withFilePath)
#endif
-#endif
import System.Environment.ExecutablePath
@@ -64,8 +60,6 @@ import System.Environment.ExecutablePath
# endif
#endif
-#ifdef __GLASGOW_HASKELL__
-
#include "HsBaseConfig.h"
-- ---------------------------------------------------------------------------
@@ -449,4 +443,3 @@ divvy str =
case break (=='=') str of
(xs,[]) -> (xs,[]) -- don't barf (like Posix.getEnvironment)
(name,_:value) -> (name,value)
-#endif /* __GLASGOW_HASKELL__ */
diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs
index dbe2ce0ce0..a3059fcf9b 100644
--- a/libraries/base/System/Exit.hs
+++ b/libraries/base/System/Exit.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -25,10 +24,8 @@ module System.Exit
import Prelude
-#ifdef __GLASGOW_HASKELL__
import GHC.IO
import GHC.IO.Exception
-#endif
-- ---------------------------------------------------------------------------
-- exitWith
@@ -63,9 +60,7 @@ exitWith :: ExitCode -> IO a
exitWith ExitSuccess = throwIO ExitSuccess
exitWith code@(ExitFailure n)
| n /= 0 = throwIO code
-#ifdef __GLASGOW_HASKELL__
| otherwise = ioError (IOError Nothing InvalidArgument "exitWith" "ExitFailure 0" Nothing Nothing)
-#endif
-- | The computation 'exitFailure' is equivalent to
-- 'exitWith' @(@'ExitFailure' /exitfail/@)@,
diff --git a/libraries/base/System/IO.hs b/libraries/base/System/IO.hs
index d6ed1f52e5..93245d39fe 100644
--- a/libraries/base/System/IO.hs
+++ b/libraries/base/System/IO.hs
@@ -73,9 +73,7 @@ module System.IO (
-- ** Determining and changing the size of a file
hFileSize,
-#ifdef __GLASGOW_HASKELL__
hSetFileSize,
-#endif
-- ** Detecting the end of input
@@ -114,9 +112,7 @@ module System.IO (
-- ** Showing handle state (not portable: GHC only)
-#ifdef __GLASGOW_HASKELL__
hShow,
-#endif
-- * Text input and output
@@ -237,7 +233,6 @@ import Foreign.C.Types
import System.Posix.Internals
import System.Posix.Types
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.IO hiding ( bracket, onException )
import GHC.IO.IOMode
@@ -251,12 +246,10 @@ import GHC.Num
import Text.Read
import GHC.Show
import GHC.MVar
-#endif
-- -----------------------------------------------------------------------------
-- Standard IO
-#ifdef __GLASGOW_HASKELL__
-- | Write a character to the standard output device
-- (same as 'hPutChar' 'stdout').
@@ -364,7 +357,6 @@ readIO s = case (do { (x,t) <- reads s ;
-- 'GHC.IO.Encoding.setLocaleEncoding' this value will not reflect that change.
localeEncoding :: TextEncoding
localeEncoding = initLocaleEncoding
-#endif /* __GLASGOW_HASKELL__ */
-- | Computation 'hReady' @hdl@ indicates whether at least one item is
-- available for input from handle @hdl@.
@@ -408,7 +400,6 @@ withBinaryFile name mode = bracket (openBinaryFile name mode) hClose
-- ---------------------------------------------------------------------------
-- fixIO
-#if defined(__GLASGOW_HASKELL__)
fixIO :: (a -> IO a) -> IO a
fixIO k = do
m <- newEmptyMVar
@@ -431,7 +422,6 @@ fixIO k = do
--
-- See also System.IO.Unsafe.unsafeFixIO.
--
-#endif
-- | The function creates a temporary file in ReadWrite mode.
-- The created file isn\'t deleted automatically, so you need to delete it manually.
@@ -496,7 +486,6 @@ openTempFile' loc tmp_dir template binary mode = do
-- beginning with '.' as the second component.
_ -> error "bug in System.IO.openTempFile"
-#if defined(__GLASGOW_HASKELL__)
findTempName x = do
r <- openNewFile filepath binary mode
case r of
@@ -511,10 +500,6 @@ openTempFile' loc tmp_dir template binary mode = do
h <- mkHandleFromFD fD fd_type filepath ReadWriteMode False{-set non-block-} (Just enc)
return (filepath, h)
-#else
- h <- fdToHandle fd `onException` c_close fd
- return (filepath, h)
-#endif
where
filename = prefix ++ show x ++ suffix
@@ -527,7 +512,6 @@ openTempFile' loc tmp_dir template binary mode = do
| last a == pathSeparator = a ++ b
| otherwise = a ++ [pathSeparator] ++ b
-#if defined(__GLASGOW_HASKELL__)
data OpenNewFileResult
= NewFileCreated CInt
| FileExists
@@ -549,7 +533,7 @@ openNewFile filepath binary mode = do
errno <- getErrno
case errno of
_ | errno == eEXIST -> return FileExists
-# ifdef mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
-- If c_open throws EACCES on windows, it could mean that filepath is a
-- directory. In this case, we want to return FileExists so that the
-- enclosing openTempFile can try again instead of failing outright.
@@ -564,13 +548,12 @@ openNewFile filepath binary mode = do
return $ if exists
then FileExists
else OpenNewError errno
-# endif
+#endif
_ -> return (OpenNewError errno)
else return (NewFileCreated fd)
-# ifdef mingw32_HOST_OS
+#ifdef mingw32_HOST_OS
foreign import ccall "file_exists" c_fileExists :: CString -> IO Bool
-# endif
#endif
-- XXX Should use filepath library
diff --git a/libraries/base/System/IO/Error.hs b/libraries/base/System/IO/Error.hs
index d76205653e..3486769275 100644
--- a/libraries/base/System/IO/Error.hs
+++ b/libraries/base/System/IO/Error.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -86,13 +86,11 @@ import Control.Exception.Base
import Data.Either
import Data.Maybe
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.IO
import GHC.IO.Exception
import GHC.IO.Handle.Types
import Text.Show
-#endif
-- | The construct 'tryIOError' @comp@ exposes IO errors which occur within a
-- computation, and which are not fully handled.
@@ -116,9 +114,7 @@ mkIOError t location maybe_hdl maybe_filename =
IOError{ ioe_type = t,
ioe_location = location,
ioe_description = "",
-#if defined(__GLASGOW_HASKELL__)
ioe_errno = Nothing,
-#endif
ioe_handle = maybe_hdl,
ioe_filename = maybe_filename
}
diff --git a/libraries/base/System/IO/Unsafe.hs b/libraries/base/System/IO/Unsafe.hs
index 18a2d423d7..eb6eef654e 100644
--- a/libraries/base/System/IO/Unsafe.hs
+++ b/libraries/base/System/IO/Unsafe.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -23,13 +23,11 @@ module System.IO.Unsafe (
unsafeFixIO,
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.IO
import GHC.IORef
import GHC.Exception
import Control.Exception
-#endif
-- | A slightly faster version of `System.IO.fixIO` that may not be
-- safe to use with multiple threads. The unsafety arises when used
diff --git a/libraries/base/System/Info.hs b/libraries/base/System/Info.hs
index d387240f74..1d251bc37c 100644
--- a/libraries/base/System/Info.hs
+++ b/libraries/base/System/Info.hs
@@ -33,26 +33,20 @@ compilerVersion :: Version
compilerVersion = Version {versionBranch=[major, minor], versionTags=[]}
where (major, minor) = compilerVersionRaw `divMod` 100
+#include "ghcplatform.h"
+
-- | The operating system on which the program is running.
os :: String
+os = HOST_OS
-- | The machine architecture on which the program is running.
arch :: String
+arch = HOST_ARCH
-- | The Haskell implementation with which the program was compiled
-- or is being interpreted.
compilerName :: String
+compilerName = "ghc"
compilerVersionRaw :: Int
-
-#if defined(__GLASGOW_HASKELL__)
-#include "ghcplatform.h"
-os = HOST_OS
-arch = HOST_ARCH
-compilerName = "ghc"
compilerVersionRaw = __GLASGOW_HASKELL__
-
-#else
-#error Unknown compiler name
-#endif
-
diff --git a/libraries/base/System/Mem.hs b/libraries/base/System/Mem.hs
index 8bcf37acec..05d9d006db 100644
--- a/libraries/base/System/Mem.hs
+++ b/libraries/base/System/Mem.hs
@@ -1,8 +1,5 @@
{-# LANGUAGE Safe #-}
-{-# LANGUAGE CPP #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE ForeignFunctionInterface #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -24,8 +21,5 @@ module System.Mem (
import Prelude
-#ifdef __GLASGOW_HASKELL__
-- | Triggers an immediate garbage collection
foreign import ccall {-safe-} "performMajorGC" performGC :: IO ()
-#endif
-
diff --git a/libraries/base/System/Mem/StableName.hs b/libraries/base/System/Mem/StableName.hs
index 374f01cd37..2cd09feb79 100644
--- a/libraries/base/System/Mem/StableName.hs
+++ b/libraries/base/System/Mem/StableName.hs
@@ -1,12 +1,10 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
{-# LANGUAGE MagicHash #-}
#if !defined(__PARALLEL_HASKELL__)
{-# LANGUAGE UnboxedTuples #-}
#endif
-#endif
-----------------------------------------------------------------------------
-- |
@@ -44,7 +42,6 @@ import Prelude
import Data.Typeable
-#ifdef __GLASGOW_HASKELL__
import GHC.IO ( IO(..) )
import GHC.Base ( Int(..), StableName#, makeStableName#
, eqStableName#, stableNameToInt# )
@@ -127,8 +124,6 @@ eqStableName (StableName sn1) (StableName sn2) =
-- Requested by Emil Axelsson on glasgow-haskell-users, who wants to
-- use it for implementing observable sharing.
-#endif /* __GLASGOW_HASKELL__ */
-
#include "Typeable.h"
INSTANCE_TYPEABLE1(StableName,stableNameTc,"StableName")
diff --git a/libraries/base/System/Mem/Weak.hs b/libraries/base/System/Mem/Weak.hs
index f35008647c..fc69019e65 100644
--- a/libraries/base/System/Mem/Weak.hs
+++ b/libraries/base/System/Mem/Weak.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
@@ -70,9 +69,7 @@ module System.Mem.Weak (
-- $precise
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Weak
-#endif
-- | A specialised version of 'mkWeak', where the key and the value are
-- the same object:
diff --git a/libraries/base/System/Posix/Internals.hs b/libraries/base/System/Posix/Internals.hs
index 156ab28e80..833366e042 100644
--- a/libraries/base/System/Posix/Internals.hs
+++ b/libraries/base/System/Posix/Internals.hs
@@ -41,7 +41,6 @@ import Data.Maybe
import System.IO.Error
#endif
-#if __GLASGOW_HASKELL__
import GHC.Base
import GHC.Num
import GHC.Real
@@ -53,7 +52,6 @@ import GHC.IO.Device
import {-# SOURCE #-} GHC.IO.Encoding (getFileSystemEncoding)
import qualified GHC.Foreign as GHC
#endif
-#endif
-- ---------------------------------------------------------------------------
-- Debugging the base package
@@ -137,9 +135,7 @@ statGetType p_stat = do
ioe_unknownfiletype :: IOException
ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
"unknown file type"
-#if __GLASGOW_HASKELL__
Nothing
-#endif
Nothing
fdGetMode :: FD -> IO IOMode
@@ -182,17 +178,10 @@ newFilePath :: FilePath -> IO CString
peekFilePath :: CString -> IO FilePath
peekFilePathLen :: CStringLen -> IO FilePath
-#if __GLASGOW_HASKELL__
withFilePath fp f = getFileSystemEncoding >>= \enc -> GHC.withCString enc fp f
newFilePath fp = getFileSystemEncoding >>= \enc -> GHC.newCString enc fp
peekFilePath fp = getFileSystemEncoding >>= \enc -> GHC.peekCString enc fp
peekFilePathLen fp = getFileSystemEncoding >>= \enc -> GHC.peekCStringLen enc fp
-#else
-withFilePath = withCString
-newFilePath = newCString
-peekFilePath = peekCString
-peekFilePathLen = peekCStringLen
-#endif
#endif
@@ -240,7 +229,6 @@ tcSetAttr fd fun = do
throwErrnoIfMinus1Retry_ "tcSetAttr"
(c_tcgetattr fd p_tios)
-#ifdef __GLASGOW_HASKELL__
-- Save a copy of termios, if this is a standard file descriptor.
-- These terminal settings are restored in hs_exit().
when (fd <= 2) $ do
@@ -249,7 +237,6 @@ tcSetAttr fd fun = do
saved_tios <- mallocBytes sizeof_termios
copyBytes saved_tios p_tios sizeof_termios
set_saved_termios fd saved_tios
-#endif
-- tcsetattr() when invoked by a background process causes the process
-- to be sent SIGTTOU regardless of whether the process has TOSTOP set
@@ -271,13 +258,11 @@ tcSetAttr fd fun = do
c_sigprocmask const_sig_setmask p_old_sigset nullPtr
return r
-#ifdef __GLASGOW_HASKELL__
foreign import ccall unsafe "HsBase.h __hscore_get_saved_termios"
get_saved_termios :: CInt -> IO (Ptr CTermios)
foreign import ccall unsafe "HsBase.h __hscore_set_saved_termios"
set_saved_termios :: CInt -> (Ptr CTermios) -> IO ()
-#endif
#else
diff --git a/libraries/base/System/Posix/Types.hs b/libraries/base/System/Posix/Types.hs
index 82760c51fd..dd5b98771b 100644
--- a/libraries/base/System/Posix/Types.hs
+++ b/libraries/base/System/Posix/Types.hs
@@ -4,9 +4,7 @@
, MagicHash
, GeneralizedNewtypeDeriving
#-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -97,7 +95,6 @@ import Foreign.C
import Data.Typeable
-- import Data.Bits
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Enum
import GHC.Num
@@ -105,9 +102,6 @@ import GHC.Real
-- import GHC.Prim
import GHC.Read
import GHC.Show
-#else
-import Control.Monad
-#endif
#include "CTypes.h"
diff --git a/libraries/base/System/Timeout.hs b/libraries/base/System/Timeout.hs
index 559ca42cdd..a7b124abc8 100644
--- a/libraries/base/System/Timeout.hs
+++ b/libraries/base/System/Timeout.hs
@@ -1,8 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
-#endif
-------------------------------------------------------------------------------
-- |
@@ -18,13 +16,10 @@
--
-------------------------------------------------------------------------------
-#ifdef __GLASGOW_HASKELL__
#include "Typeable.h"
-#endif
module System.Timeout ( timeout ) where
-#ifdef __GLASGOW_HASKELL__
#ifndef mingw32_HOST_OS
import Control.Monad
import GHC.Event (getSystemTimerManager,
@@ -54,8 +49,6 @@ instance Exception Timeout where
toException = asyncExceptionToException
fromException = asyncExceptionFromException
-#endif /* !__GLASGOW_HASKELL__ */
-
-- |Wrap an 'IO' computation to time out and return @Nothing@ in case no result
-- is available within @n@ microseconds (@1\/10^6@ seconds). In case a result
-- is available before the timeout expires, @Just a@ is returned. A negative
@@ -86,7 +79,6 @@ instance Exception Timeout where
-- I\/O or file I\/O using this combinator.
timeout :: Int -> IO a -> IO (Maybe a)
-#ifdef __GLASGOW_HASKELL__
timeout n f
| n < 0 = fmap Just f
| n == 0 = return Nothing
@@ -131,7 +123,3 @@ timeout n f
(uninterruptibleMask_ . killThread)
(\_ -> fmap Just f))
-- #7719 explains why we need uninterruptibleMask_ above.
-#else
-timeout n f = fmap Just f
-#endif /* !__GLASGOW_HASKELL__ */
-
diff --git a/libraries/base/Text/ParserCombinators/ReadP.hs b/libraries/base/Text/ParserCombinators/ReadP.hs
index 72338848dd..a0e6e22062 100644
--- a/libraries/base/Text/ParserCombinators/ReadP.hs
+++ b/libraries/base/Text/ParserCombinators/ReadP.hs
@@ -1,9 +1,7 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
-#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE MagicHash #-}
-#endif
-----------------------------------------------------------------------------
-- |
@@ -75,17 +73,12 @@ module Text.ParserCombinators.ReadP
import Control.Monad( MonadPlus(..), sequence, liftM2 )
-#ifdef __GLASGOW_HASKELL__
import {-# SOURCE #-} GHC.Unicode ( isSpace )
import GHC.List ( replicate, null )
import GHC.Base
-#else
-import Data.Char( isSpace )
-#endif
infixr 5 +++, <++
-#ifdef __GLASGOW_HASKELL__
------------------------------------------------------------------------
-- ReadS
@@ -95,7 +88,6 @@ infixr 5 +++, <++
-- Note that this kind of backtracking parser is very inefficient;
-- reading a large structure may be quite slow (cf 'ReadP').
type ReadS a = String -> [(a,String)]
-#endif
-- ---------------------------------------------------------------------------
-- The P type
@@ -209,7 +201,6 @@ R f1 +++ R f2 = R (\k -> f1 k `mplus` f2 k)
-- ^ Local, exclusive, left-biased choice: If left parser
-- locally produces any result at all, then right parser is
-- not used.
-#ifdef __GLASGOW_HASKELL__
R f0 <++ q =
do s <- look
probe (f0 return) s 0#
@@ -222,20 +213,6 @@ R f0 <++ q =
discard 0# = return ()
discard n = get >> discard (n-#1#)
-#else
-R f <++ q =
- do s <- look
- probe (f return) s 0
- where
- probe (Get f) (c:s) n = probe (f c) s (n+1)
- probe (Look f) s n = probe (f s) s n
- probe p@(Result _ _) _ n = discard n >> R (p >>=)
- probe (Final r) _ _ = R (Final r >>=)
- probe _ _ _ = q
-
- discard 0 = return ()
- discard n = get >> discard (n-1)
-#endif
gather :: ReadP a -> ReadP (String, a)
-- ^ Transforms a parser into one that does the same, but
diff --git a/libraries/base/Text/ParserCombinators/ReadPrec.hs b/libraries/base/Text/ParserCombinators/ReadPrec.hs
index ba59facb8b..235436c4d6 100644
--- a/libraries/base/Text/ParserCombinators/ReadPrec.hs
+++ b/libraries/base/Text/ParserCombinators/ReadPrec.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -62,10 +62,8 @@ import qualified Text.ParserCombinators.ReadP as ReadP
)
import Control.Monad( MonadPlus(..) )
-#ifdef __GLASGOW_HASKELL__
import GHC.Num( Num(..) )
import GHC.Base
-#endif
-- ---------------------------------------------------------------------------
-- The readPrec type
diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs
index 4e9c65d685..1766f9ba23 100644
--- a/libraries/base/Text/Printf.hs
+++ b/libraries/base/Text/Printf.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Safe #-}
-{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
diff --git a/libraries/base/Text/Read.hs b/libraries/base/Text/Read.hs
index 568c746e2b..b2c3d6bfc7 100644
--- a/libraries/base/Text/Read.hs
+++ b/libraries/base/Text/Read.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -32,35 +32,26 @@ module Text.Read (
readParen,
lex,
-#ifdef __GLASGOW_HASKELL__
-- * New parsing functions
module Text.ParserCombinators.ReadPrec,
L.Lexeme(..),
lexP,
parens,
-#endif
-#ifdef __GLASGOW_HASKELL__
readListDefault,
readListPrecDefault,
readEither,
readMaybe
-#endif
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Read
import Data.Either
import Data.Maybe
import Text.ParserCombinators.ReadP as P
-#endif
-#ifdef __GLASGOW_HASKELL__
import Text.ParserCombinators.ReadPrec
import qualified Text.Read.Lex as L
-#endif
-#ifdef __GLASGOW_HASKELL__
------------------------------------------------------------------------
-- utility functions
@@ -94,5 +85,3 @@ readMaybe s = case readEither s of
-- completely consumed by the input process.
read :: Read a => String -> a
read s = either error id (readEither s)
-#endif
-
diff --git a/libraries/base/Text/Read/Lex.hs b/libraries/base/Text/Read/Lex.hs
index 78f49134fe..637299ac98 100644
--- a/libraries/base/Text/Read/Lex.hs
+++ b/libraries/base/Text/Read/Lex.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -35,7 +35,6 @@ module Text.Read.Lex
import Text.ParserCombinators.ReadP
-#ifdef __GLASGOW_HASKELL__
import GHC.Base
import GHC.Char
import GHC.Num( Num(..), Integer )
@@ -45,11 +44,6 @@ import GHC.Real( Rational, (%), fromIntegral,
toInteger, (^) )
import GHC.List
import GHC.Enum( minBound, maxBound )
-#else
-import Prelude hiding ( lex )
-import Data.Char( chr, ord, isSpace, isAlpha, isAlphaNum )
-import Data.Ratio( Ratio, (%) )
-#endif
import Data.Maybe
import Control.Monad
diff --git a/libraries/base/Text/Show.hs b/libraries/base/Text/Show.hs
index d37f71594e..6978a0ef62 100644
--- a/libraries/base/Text/Show.hs
+++ b/libraries/base/Text/Show.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Safe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude #-}
+{-# LANGUAGE NoImplicitPrelude #-}
-----------------------------------------------------------------------------
-- |
@@ -26,21 +26,9 @@ module Text.Show (
showListWith,
) where
-#ifdef __GLASGOW_HASKELL__
import GHC.Show
-#endif
-- | Show a list (using square brackets and commas), given a function
-- for showing elements.
showListWith :: (a -> ShowS) -> [a] -> ShowS
showListWith = showList__
-
-#ifndef __GLASGOW_HASKELL__
-showList__ :: (a -> ShowS) -> [a] -> ShowS
-showList__ _ [] s = "[]" ++ s
-showList__ showx (x:xs) s = '[' : showx x (showl xs)
- where
- showl [] = ']' : s
- showl (y:ys) = ',' : showx y (showl ys)
-#endif
-
diff --git a/libraries/base/Text/Show/Functions.hs b/libraries/base/Text/Show/Functions.hs
index 27cdd60034..b34cbc67ce 100644
--- a/libraries/base/Text/Show/Functions.hs
+++ b/libraries/base/Text/Show/Functions.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE Safe #-}
-{-# LANGUAGE CPP #-}
-- This module deliberately declares orphan instances:
{-# OPTIONS_GHC -fno-warn-orphans #-}
diff --git a/libraries/base/Unsafe/Coerce.hs b/libraries/base/Unsafe/Coerce.hs
index 11557c34ab..1cd70a6d1d 100644
--- a/libraries/base/Unsafe/Coerce.hs
+++ b/libraries/base/Unsafe/Coerce.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Unsafe #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude, MagicHash #-}
-----------------------------------------------------------------------------
-- |
@@ -31,8 +31,6 @@
module Unsafe.Coerce (unsafeCoerce) where
-
-#if defined(__GLASGOW_HASKELL__)
import GHC.Integer () -- for build ordering
import GHC.Prim (unsafeCoerce#)
@@ -62,4 +60,3 @@ unsafeCoerce x = local_id (unsafeCoerce# x)
-- See Note [Unsafe coerce magic] in basicTypes/MkId
-- NB: Do not eta-reduce this definition, else the type checker
-- give usafeCoerce the same (dangerous) type as unsafeCoerce#
-#endif
diff --git a/libraries/base/include/CTypes.h b/libraries/base/include/CTypes.h
index 14ec79dcc2..a33d1faab5 100644
--- a/libraries/base/include/CTypes.h
+++ b/libraries/base/include/CTypes.h
@@ -16,164 +16,6 @@
// macros below are modified, otherwise the layout rule will bite you.
-}
--- // A hacked version for GHC follows the Haskell 98 version...
-#ifndef __GLASGOW_HASKELL__
-
-#define ARITHMETIC_TYPE(T,C,S,B) \
-newtype T = T B deriving (Eq, Ord) ; \
-INSTANCE_NUM(T) ; \
-INSTANCE_REAL(T) ; \
-INSTANCE_READ(T,B) ; \
-INSTANCE_SHOW(T,B) ; \
-INSTANCE_ENUM(T) ; \
-INSTANCE_STORABLE(T) ; \
-INSTANCE_TYPEABLE0(T,C,S) ;
-
-#define INTEGRAL_TYPE(T,C,S,B) \
-ARITHMETIC_TYPE(T,C,S,B) ; \
-INSTANCE_BOUNDED(T) ; \
-INSTANCE_INTEGRAL(T) ; \
-INSTANCE_BITS(T)
-
-#define FLOATING_TYPE(T,C,S,B) \
-ARITHMETIC_TYPE(T,C,S,B) ; \
-INSTANCE_FRACTIONAL(T) ; \
-INSTANCE_FLOATING(T) ; \
-INSTANCE_REALFRAC(T) ; \
-INSTANCE_REALFLOAT(T)
-
-#ifndef __GLASGOW_HASKELL__
-#define fakeMap map
-#endif
-
-#define INSTANCE_READ(T,B) \
-instance Read T where { \
- readsPrec p s = fakeMap (\(x, t) -> (T x, t)) (readsPrec p s) }
-
-#define INSTANCE_SHOW(T,B) \
-instance Show T where { \
- showsPrec p (T x) = showsPrec p x }
-
-#define INSTANCE_NUM(T) \
-instance Num T where { \
- (T i) + (T j) = T (i + j) ; \
- (T i) - (T j) = T (i - j) ; \
- (T i) * (T j) = T (i * j) ; \
- negate (T i) = T (negate i) ; \
- abs (T i) = T (abs i) ; \
- signum (T i) = T (signum i) ; \
- fromInteger x = T (fromInteger x) }
-
-#define INSTANCE_BOUNDED(T) \
-instance Bounded T where { \
- minBound = T minBound ; \
- maxBound = T maxBound }
-
-#define INSTANCE_ENUM(T) \
-instance Enum T where { \
- succ (T i) = T (succ i) ; \
- pred (T i) = T (pred i) ; \
- toEnum x = T (toEnum x) ; \
- fromEnum (T i) = fromEnum i ; \
- enumFrom (T i) = fakeMap T (enumFrom i) ; \
- enumFromThen (T i) (T j) = fakeMap T (enumFromThen i j) ; \
- enumFromTo (T i) (T j) = fakeMap T (enumFromTo i j) ; \
- enumFromThenTo (T i) (T j) (T k) = fakeMap T (enumFromThenTo i j k) }
-
-#define INSTANCE_REAL(T) \
-instance Real T where { \
- toRational (T i) = toRational i }
-
-#define INSTANCE_INTEGRAL(T) \
-instance Integral T where { \
- (T i) `quot` (T j) = T (i `quot` j) ; \
- (T i) `rem` (T j) = T (i `rem` j) ; \
- (T i) `div` (T j) = T (i `div` j) ; \
- (T i) `mod` (T j) = T (i `mod` j) ; \
- (T i) `quotRem` (T j) = let (q,r) = i `quotRem` j in (T q, T r) ; \
- (T i) `divMod` (T j) = let (d,m) = i `divMod` j in (T d, T m) ; \
- toInteger (T i) = toInteger i }
-
-#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) ; \
- unsafeShiftL (T x) n = T (unsafeShiftL x n) ; \
- unsafeShiftR (T x) n = T (unsafeShiftR 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 }
-
-#define INSTANCE_FRACTIONAL(T) \
-instance Fractional T where { \
- (T x) / (T y) = T (x / y) ; \
- recip (T x) = T (recip x) ; \
- fromRational r = T (fromRational r) }
-
-#define INSTANCE_FLOATING(T) \
-instance Floating T where { \
- pi = pi ; \
- exp (T x) = T (exp x) ; \
- log (T x) = T (log x) ; \
- sqrt (T x) = T (sqrt x) ; \
- (T x) ** (T y) = T (x ** y) ; \
- (T x) `logBase` (T y) = T (x `logBase` y) ; \
- sin (T x) = T (sin x) ; \
- cos (T x) = T (cos x) ; \
- tan (T x) = T (tan x) ; \
- asin (T x) = T (asin x) ; \
- acos (T x) = T (acos x) ; \
- atan (T x) = T (atan x) ; \
- sinh (T x) = T (sinh x) ; \
- cosh (T x) = T (cosh x) ; \
- tanh (T x) = T (tanh x) ; \
- asinh (T x) = T (asinh x) ; \
- acosh (T x) = T (acosh x) ; \
- atanh (T x) = T (atanh x) }
-
-#define INSTANCE_REALFRAC(T) \
-instance RealFrac T where { \
- properFraction (T x) = let (m,y) = properFraction x in (m, T y) ; \
- truncate (T x) = truncate x ; \
- round (T x) = round x ; \
- ceiling (T x) = ceiling x ; \
- floor (T x) = floor x }
-
-#define INSTANCE_REALFLOAT(T) \
-instance RealFloat T where { \
- floatRadix (T x) = floatRadix x ; \
- floatDigits (T x) = floatDigits x ; \
- floatRange (T x) = floatRange x ; \
- decodeFloat (T x) = decodeFloat x ; \
- encodeFloat m n = T (encodeFloat m n) ; \
- exponent (T x) = exponent x ; \
- significand (T x) = T (significand x) ; \
- scaleFloat n (T x) = T (scaleFloat n x) ; \
- isNaN (T x) = isNaN x ; \
- isInfinite (T x) = isInfinite x ; \
- isDenormalized (T x) = isDenormalized x ; \
- isNegativeZero (T x) = isNegativeZero x ; \
- isIEEE (T x) = isIEEE x ; \
- (T x) `atan2` (T y) = T (x `atan2` y) }
-
-#define INSTANCE_STORABLE(T) \
-instance Storable T where { \
- sizeOf (T x) = sizeOf x ; \
- alignment (T x) = alignment x ; \
- peekElemOff a i = liftM T (peekElemOff (castPtr a) i) ; \
- pokeElemOff a i (T x) = pokeElemOff (castPtr a) i x }
-
-#else /* __GLASGOW_HASKELL__ */
-
-- // GHC can derive any class for a newtype, so we make use of that here...
#define ARITHMETIC_CLASSES Eq,Ord,Num,Enum,Storable,Real
@@ -215,6 +57,4 @@ instance Show T where { \
show = unsafeCoerce# (show :: B -> String); \
showList = unsafeCoerce# (showList :: [B] -> ShowS); }
-#endif /* __GLASGOW_HASKELL__ */
-
#endif
diff --git a/libraries/base/include/HsBase.h b/libraries/base/include/HsBase.h
index b70a7295da..46d0f0c102 100644
--- a/libraries/base/include/HsBase.h
+++ b/libraries/base/include/HsBase.h
@@ -305,10 +305,6 @@ __hscore_setmode( int fd, HsBool toBin )
#endif
}
-#if __GLASGOW_HASKELL__
-
-#endif /* __GLASGOW_HASKELL__ */
-
#if defined(__MINGW32__)
// We want the versions of stat/fstat/lseek that use 64-bit offsets,
// and you have to ask for those explicitly. Unfortunately there
diff --git a/libraries/base/include/OldTypeable.h b/libraries/base/include/OldTypeable.h
index 38fe90f220..311edffe29 100644
--- a/libraries/base/include/OldTypeable.h
+++ b/libraries/base/include/OldTypeable.h
@@ -14,8 +14,6 @@
#ifndef TYPEABLE_H
#define TYPEABLE_H
-#ifdef __GLASGOW_HASKELL__
-
-- // For GHC, we can use DeriveDataTypeable + StandaloneDeriving to
-- // generate the instances.
@@ -28,96 +26,4 @@
#define INSTANCE_TYPEABLE6(tycon,tcname,str) deriving instance Typeable6 tycon
#define INSTANCE_TYPEABLE7(tycon,tcname,str) deriving instance Typeable7 tycon
-#else /* !__GLASGOW_HASKELL__ */
-
-#define INSTANCE_TYPEABLE0(tycon,tcname,str) \
-tcname :: TyCon; \
-tcname = mkTyCon str; \
-instance Typeable tycon where { typeOf _ = mkTyConApp tcname [] }
-
-#define INSTANCE_TYPEABLE1(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable1 tycon where { typeOf1 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable (tycon a) where { typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE2(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable2 tycon where { typeOf2 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable1 (tycon a) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b) => Typeable (tycon a b) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE3(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable3 tycon where { typeOf3 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable2 (tycon a) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b) => Typeable1 (tycon a b) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable (tycon a b c) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE4(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable4 tycon where { typeOf4 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable3 (tycon a) where { \
- typeOf3 = typeOf3Default }; \
-instance (Typeable a, Typeable b) => Typeable2 (tycon a b) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable1 (tycon a b c) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable (tycon a b c d) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE5(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable5 tycon where { typeOf5 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable4 (tycon a) where { \
- typeOf4 = typeOf4Default }; \
-instance (Typeable a, Typeable b) => Typeable3 (tycon a b) where { \
- typeOf3 = typeOf3Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable2 (tycon a b c) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable1 (tycon a b c d) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable (tycon a b c d e) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE6(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable6 tycon where { typeOf6 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable5 (tycon a) where { \
- typeOf5 = typeOf5Default }; \
-instance (Typeable a, Typeable b) => Typeable4 (tycon a b) where { \
- typeOf4 = typeOf4Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable3 (tycon a b c) where { \
- typeOf3 = typeOf3Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable2 (tycon a b c d) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable1 (tycon a b c d e) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => Typeable (tycon a b c d e f) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE7(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable7 tycon where { typeOf7 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable6 (tycon a) where { \
- typeOf6 = typeOf6Default }; \
-instance (Typeable a, Typeable b) => Typeable5 (tycon a b) where { \
- typeOf5 = typeOf5Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable4 (tycon a b c) where { \
- typeOf4 = typeOf4Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable3 (tycon a b c d) where { \
- typeOf3 = typeOf3Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable2 (tycon a b c d e) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => Typeable1 (tycon a b c d e f) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f, Typeable g) => Typeable (tycon a b c d e f g) where { \
- typeOf = typeOfDefault }
-
-#endif /* !__GLASGOW_HASKELL__ */
-
#endif
diff --git a/libraries/base/include/Typeable.h b/libraries/base/include/Typeable.h
index f8ea998ed3..ae04142014 100644
--- a/libraries/base/include/Typeable.h
+++ b/libraries/base/include/Typeable.h
@@ -14,8 +14,6 @@
#ifndef TYPEABLE_H
#define TYPEABLE_H
-#ifdef __GLASGOW_HASKELL__
-
-- // For GHC, we can use DeriveDataTypeable + StandaloneDeriving to
-- // generate the instances.
@@ -28,96 +26,4 @@
#define INSTANCE_TYPEABLE6(tycon,tcname,str) deriving instance Typeable tycon
#define INSTANCE_TYPEABLE7(tycon,tcname,str) deriving instance Typeable tycon
-#else /* !__GLASGOW_HASKELL__ */
-
-#define INSTANCE_TYPEABLE0(tycon,tcname,str) \
-tcname :: TyCon; \
-tcname = mkTyCon str; \
-instance Typeable tycon where { typeOf _ = mkTyConApp tcname [] }
-
-#define INSTANCE_TYPEABLE1(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable1 tycon where { typeOf1 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable (tycon a) where { typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE2(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable2 tycon where { typeOf2 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable1 (tycon a) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b) => Typeable (tycon a b) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE3(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable3 tycon where { typeOf3 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable2 (tycon a) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b) => Typeable1 (tycon a b) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable (tycon a b c) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE4(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable4 tycon where { typeOf4 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable3 (tycon a) where { \
- typeOf3 = typeOf3Default }; \
-instance (Typeable a, Typeable b) => Typeable2 (tycon a b) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable1 (tycon a b c) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable (tycon a b c d) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE5(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable5 tycon where { typeOf5 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable4 (tycon a) where { \
- typeOf4 = typeOf4Default }; \
-instance (Typeable a, Typeable b) => Typeable3 (tycon a b) where { \
- typeOf3 = typeOf3Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable2 (tycon a b c) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable1 (tycon a b c d) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable (tycon a b c d e) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE6(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable6 tycon where { typeOf6 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable5 (tycon a) where { \
- typeOf5 = typeOf5Default }; \
-instance (Typeable a, Typeable b) => Typeable4 (tycon a b) where { \
- typeOf4 = typeOf4Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable3 (tycon a b c) where { \
- typeOf3 = typeOf3Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable2 (tycon a b c d) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable1 (tycon a b c d e) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => Typeable (tycon a b c d e f) where { \
- typeOf = typeOfDefault }
-
-#define INSTANCE_TYPEABLE7(tycon,tcname,str) \
-tcname = mkTyCon str; \
-instance Typeable7 tycon where { typeOf7 _ = mkTyConApp tcname [] }; \
-instance Typeable a => Typeable6 (tycon a) where { \
- typeOf6 = typeOf6Default }; \
-instance (Typeable a, Typeable b) => Typeable5 (tycon a b) where { \
- typeOf5 = typeOf5Default }; \
-instance (Typeable a, Typeable b, Typeable c) => Typeable4 (tycon a b c) where { \
- typeOf4 = typeOf4Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable3 (tycon a b c d) where { \
- typeOf3 = typeOf3Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable2 (tycon a b c d e) where { \
- typeOf2 = typeOf2Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => Typeable1 (tycon a b c d e f) where { \
- typeOf1 = typeOf1Default }; \
-instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f, Typeable g) => Typeable (tycon a b c d e f g) where { \
- typeOf = typeOfDefault }
-
-#endif /* !__GLASGOW_HASKELL__ */
-
#endif
diff --git a/libraries/base/tests/IO/hSeek001.hs b/libraries/base/tests/IO/hSeek001.hs
index d05068e955..dc7313face 100644
--- a/libraries/base/tests/IO/hSeek001.hs
+++ b/libraries/base/tests/IO/hSeek001.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
-- !!! Test seeking
import System.IO
diff --git a/libraries/base/tests/qsem001.hs b/libraries/base/tests/qsem001.hs
index 95b240d0dc..0088c6e989 100644
--- a/libraries/base/tests/qsem001.hs
+++ b/libraries/base/tests/qsem001.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
import Control.Concurrent.QSem as OldQ
import Control.Concurrent.Chan
diff --git a/libraries/base/tests/qsemn001.hs b/libraries/base/tests/qsemn001.hs
index d45c09d14a..165efa5083 100644
--- a/libraries/base/tests/qsemn001.hs
+++ b/libraries/base/tests/qsemn001.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
import Control.Concurrent
import Control.Exception
import Control.Monad