[commit: packages/haskell98] master: Kill CPP conditionals for HUGS and old GHCs (401283a)

git at git.haskell.org git at git.haskell.org
Sun Sep 21 09:19:07 UTC 2014


Repository : ssh://git@git.haskell.org/haskell98

On branch  : master
Link       : http://git.haskell.org/packages/haskell98.git/commitdiff/401283a98a818f66f856939f939562de5c4a2b47

>---------------------------------------------------------------

commit 401283a98a818f66f856939f939562de5c4a2b47
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sun Sep 21 11:13:02 2014 +0200

    Kill CPP conditionals for HUGS and old GHCs
    
    This commit removes that bitrotting part of Prelude.hs. This reduces the
    CPP clutter to the point of not requiring any CPP processing altogether
    anymore. The same clanup was performed in the haskell2010 package
    recently.


>---------------------------------------------------------------

401283a98a818f66f856939f939562de5c4a2b47
 Prelude.hs      | 47 ++++-------------------------------------------
 haskell98.cabal |  9 +++------
 2 files changed, 7 insertions(+), 49 deletions(-)

diff --git a/Prelude.hs b/Prelude.hs
index bed225f..508f735 100644
--- a/Prelude.hs
+++ b/Prelude.hs
@@ -1,7 +1,4 @@
-{-# LANGUAGE BangPatterns, CPP, NoImplicitPrelude, PackageImports #-}
-#if __GLASGOW_HASKELL__ >= 701
-{-# LANGUAGE Trustworthy #-}
-#endif
+{-# LANGUAGE BangPatterns, NoImplicitPrelude, PackageImports, Trustworthy #-}
 
 -- |
 -- The Haskell 98 Prelude: a standard module imported by default
@@ -28,10 +25,6 @@ module Prelude (
         -- *** Tuples
         fst, snd, curry, uncurry,
 
-#ifdef __HUGS__
-        (:),                -- Not legal Haskell 98
-#endif
-
         -- ** Basic type classes
         Eq((==), (/=)),
         Ord(compare, (<), (<=), (>=), (>), max, min),
@@ -129,7 +122,6 @@ module Prelude (
 
     ) where
 
-#ifndef __HUGS__
 import qualified "base" Control.Exception.Base as New (catch)
 import "base" Control.Monad
 import "base" System.IO
@@ -138,12 +130,10 @@ import "base" Data.OldList hiding ( splitAt )
 import "base" Data.Either
 import "base" Data.Maybe
 import "base" Data.Tuple
-#endif
 
-#ifdef __GLASGOW_HASKELL__
-import GHC.Base hiding ( ($!) )
--- import GHC.IO
--- import GHC.IO.Exception
+import GHC.Base (($), ($!), (&&), (.), (||), Bool(..), Char, Eq(..), Int,
+                 Ord(..), Ordering(..), String, asTypeOf, const, error, flip,
+                 id, not, otherwise, seq, undefined, until)
 import Text.Read
 import GHC.Enum
 import GHC.Num
@@ -151,35 +141,10 @@ import GHC.Real hiding ( gcd )
 import qualified GHC.Real ( gcd )
 import GHC.Float
 import GHC.Show
-#endif
-
-#ifdef __HUGS__
-import Hugs.Prelude
-#endif
-
-#ifndef __HUGS__
-infixr 0 $!
-#endif
 
 -- -----------------------------------------------------------------------------
 -- Miscellaneous functions
 
--- | 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
-#elif !defined(__HUGS__)
-f $! x  = x `seq` f x
-#endif
-
-#ifdef __HADDOCK__
--- | The value of @'seq' a b@ is bottom if @a@ is bottom, and otherwise
--- equal to @b at .  'seq' is usually introduced to improve performance by
--- avoiding unneeded laziness.
-seq :: a -> b -> b
-seq _ y = y
-#endif
-
 -- | The 'catch' function establishes a handler that receives any
 -- 'IOError' raised in the action protected by 'catch'.
 -- An 'IOError' is caught by
@@ -203,16 +168,13 @@ seq _ y = y
 catch :: IO a -> (IOError -> IO a) -> IO a
 catch = New.catch
 
-#ifdef __GLASGOW_HASKELL__
 -- | @'gcd' x y@ is the greatest (positive) integer that divides both @x@
 -- and @y@; for example @'gcd' (-3) 6@ = @3@, @'gcd' (-3) (-6)@ = @3@,
 -- @'gcd' 0 4@ = @4 at .  @'gcd' 0 0@ raises a runtime error.
 gcd             :: (Integral a) => a -> a -> a
 gcd 0 0         =  error "Prelude.gcd: gcd 0 0 is undefined"
 gcd x y         = GHC.Real.gcd x y
-#endif
 
-#ifndef __HUGS__
 -- The GHC's version of 'splitAt' is too strict in 'n' compared to
 -- Haskell98/2010 version. Ticket #1182.
 
@@ -232,4 +194,3 @@ gcd x y         = GHC.Real.gcd x y
 -- in which @n@ may be of any integral type.
 splitAt                :: Int -> [a] -> ([a],[a])
 splitAt n xs           =  (take n xs, drop n xs)
-#endif
diff --git a/haskell98.cabal b/haskell98.cabal
index d89087f..728879d 100644
--- a/haskell98.cabal
+++ b/haskell98.cabal
@@ -28,17 +28,14 @@ Library
     default-language: Haskell98
     other-extensions:
         BangPatterns
-        CPP
         NoImplicitPrelude
         PackageImports
-    if impl(ghc)
-        other-extensions:
-            Safe
-            Trustworthy
+        Safe
+        Trustworthy
 
     build-depends:
         array       >= 0.5 && < 0.6,
-        base        >= 4.7 && < 4.9,
+        base        >= 4.8 && < 4.9,
         directory   >= 1.2 && < 1.3,
         old-locale  >= 1.0 && < 1.1,
         old-time    >= 1.1 && < 1.2,



More information about the ghc-commits mailing list